aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions
diff options
context:
space:
mode:
authorLukas Mai <l.mai@web.de>2008-04-05 00:05:58 +0200
committerLukas Mai <l.mai@web.de>2008-04-05 00:05:58 +0200
commitb9fb7f750e00e35363832fdd398366621eabb2d3 (patch)
tree75bcecb0786330bd29780184a277ef49b46079c7 /XMonad/Actions
parent80a15fa2d0e0d0bc9e70ff4bbe1ee3b0e3194bff (diff)
downloadXMonadContrib-b9fb7f750e00e35363832fdd398366621eabb2d3.tar.gz
XMonadContrib-b9fb7f750e00e35363832fdd398366621eabb2d3.tar.xz
XMonadContrib-b9fb7f750e00e35363832fdd398366621eabb2d3.zip
update contrib for applySizeHints changes
darcs-hash:20080404220558-462cf-2d7837b574aec854a158213d45a34cca75e38438.gz
Diffstat (limited to 'XMonad/Actions')
-rw-r--r--XMonad/Actions/ConstrainedResize.hs2
-rw-r--r--XMonad/Actions/FlexibleManipulate.hs2
-rw-r--r--XMonad/Actions/FlexibleResize.hs2
-rw-r--r--XMonad/Actions/FloatKeys.hs4
4 files changed, 5 insertions, 5 deletions
diff --git a/XMonad/Actions/ConstrainedResize.hs b/XMonad/Actions/ConstrainedResize.hs
index a0a412c..8e79ffc 100644
--- a/XMonad/Actions/ConstrainedResize.hs
+++ b/XMonad/Actions/ConstrainedResize.hs
@@ -53,5 +53,5 @@ mouseResizeWindow w c = whenX (isClient w) $ withDisplay $ \d -> do
y = ey - fromIntegral (wa_y wa)
sz = if c then (max x y, max x y) else (x,y)
io $ resizeWindow d w `uncurry`
- applySizeHints sh sz)
+ applySizeHintsContents sh sz)
(float w)
diff --git a/XMonad/Actions/FlexibleManipulate.hs b/XMonad/Actions/FlexibleManipulate.hs
index 083b661..0966818 100644
--- a/XMonad/Actions/FlexibleManipulate.hs
+++ b/XMonad/Actions/FlexibleManipulate.hs
@@ -92,7 +92,7 @@ mouseWindow f w = whenX (isClient w) $ withDisplay $ \d -> do
npos = wpos + offset * atl
nbr = (wpos + wsize) + offset * abr
ntl = minP (nbr - (32, 32)) npos --minimum size
- nwidth = applySizeHints sh $ mapP (round :: Double -> Integer) (nbr - ntl)
+ nwidth = applySizeHintsContents sh $ mapP (round :: Double -> Integer) (nbr - ntl)
moveResizeWindow d w (round $ fst ntl) (round $ snd ntl) `uncurry` nwidth
return ())
(float w)
diff --git a/XMonad/Actions/FlexibleResize.hs b/XMonad/Actions/FlexibleResize.hs
index cc99dcf..534bcaf 100644
--- a/XMonad/Actions/FlexibleResize.hs
+++ b/XMonad/Actions/FlexibleResize.hs
@@ -53,7 +53,7 @@ mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
let [px, py] = map (fromIntegral . ($ wa')) [wa_x, wa_y]
io $ moveResizeWindow d w (fx px (fromIntegral ex))
(fy py (fromIntegral ey))
- `uncurry` applySizeHints sh (gx $ fromIntegral ex, gy $ fromIntegral ey))
+ `uncurry` applySizeHintsContents sh (gx $ fromIntegral ex, gy $ fromIntegral ey))
(float w)
where
firstHalf :: CInt -> Position -> Bool
diff --git a/XMonad/Actions/FloatKeys.hs b/XMonad/Actions/FloatKeys.hs
index 5e38b7e..c2343bf 100644
--- a/XMonad/Actions/FloatKeys.hs
+++ b/XMonad/Actions/FloatKeys.hs
@@ -94,7 +94,7 @@ keysAbsResizeWindow = keysMoveResize keysAbsResizeWindow'
keysAbsResizeWindow' :: SizeHints -> P -> D -> D -> D -> (P,D)
keysAbsResizeWindow' sh (x,y) (w,h) (dx,dy) (ax, ay) = ((round nx, round ny), (nw, nh))
where
- (nw, nh) = applySizeHints sh (w + dx, h + dy)
+ (nw, nh) = applySizeHintsContents sh (w + dx, h + dy)
nx :: Rational
nx = fromIntegral (ax * w + nw * (fromIntegral x - ax)) / fromIntegral w
ny :: Rational
@@ -103,7 +103,7 @@ keysAbsResizeWindow' sh (x,y) (w,h) (dx,dy) (ax, ay) = ((round nx, round ny), (n
keysResizeWindow' :: SizeHints -> P -> D -> D -> G -> (P,D)
keysResizeWindow' sh (x,y) (w,h) (dx,dy) (gx, gy) = ((nx, ny), (nw, nh))
where
- (nw, nh) = applySizeHints sh (w + dx, h + dy)
+ (nw, nh) = applySizeHintsContents sh (w + dx, h + dy)
nx = round $ fromIntegral x + gx * fromIntegral w - gx * fromIntegral nw
ny = round $ fromIntegral y + gy * fromIntegral h - gy * fromIntegral nh