aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Fullscreen.hs
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2012-11-09 02:23:16 +0100
committerAdam Vogt <vogt.adam@gmail.com>2012-11-09 02:23:16 +0100
commitfff5ddb53f4eda07c3cbd1caae236e5edd8ea4bc (patch)
tree9f158730016f24578b11960dee6a7dcb11961e38 /XMonad/Layout/Fullscreen.hs
parentf1c0b28a5c40186f8723772a9e30d1107a4c884b (diff)
downloadXMonadContrib-fff5ddb53f4eda07c3cbd1caae236e5edd8ea4bc.tar.gz
XMonadContrib-fff5ddb53f4eda07c3cbd1caae236e5edd8ea4bc.tar.xz
XMonadContrib-fff5ddb53f4eda07c3cbd1caae236e5edd8ea4bc.zip
Rename variables "state" to avoid warnings about shadowing
Ignore-this: cd063d632412f758ca9fed6393521c8f XMonad core re-exports Control.Monad.State, which includes a function "state" if you happen to use mtl-2. Since there's a chance xmonad still works with mtl-1 avoid imports like: import XMonad hiding (state) darcs-hash:20121109012316-1499c-539514f4cd97ba8b18a8fbfd1a15333b46d962e1.gz
Diffstat (limited to 'XMonad/Layout/Fullscreen.hs')
-rw-r--r--XMonad/Layout/Fullscreen.hs14
1 files changed, 7 insertions, 7 deletions
diff --git a/XMonad/Layout/Fullscreen.hs b/XMonad/Layout/Fullscreen.hs
index d6dd589..1b9b0b9 100644
--- a/XMonad/Layout/Fullscreen.hs
+++ b/XMonad/Layout/Fullscreen.hs
@@ -124,11 +124,11 @@ instance LayoutModifier FullscreenFloat Window where
-- Modify the floating member of the stack set directly; this is the hackish part.
Just FullscreenChanged -> do
- state <- get
- let ws = windowset state
+ st <- get
+ let ws = windowset st
flt = W.floating ws
flt' = M.intersectionWith doFull fulls flt
- put state {windowset = ws {W.floating = M.union flt' flt}}
+ put st {windowset = ws {W.floating = M.union flt' flt}}
return $ Just $ FullscreenFloat frect $ M.filter snd fulls
where doFull (_, True) _ = frect
doFull (rect, False) _ = rect
@@ -174,9 +174,9 @@ fullscreenFloatRect r = ModifiedLayout $ FullscreenFloat r M.empty
-- | The event hook required for the layout modifiers to work
fullscreenEventHook :: Event -> X All
fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
- state <- getAtom "_NET_WM_STATE"
+ wmstate <- getAtom "_NET_WM_STATE"
fullsc <- getAtom "_NET_WM_STATE_FULLSCREEN"
- wstate <- fromMaybe [] `fmap` getProp32 state win
+ wstate <- fromMaybe [] `fmap` getProp32 wmstate win
let fi :: (Integral i, Num n) => i -> n
fi = fromIntegral
isFull = fi fullsc `elem` wstate
@@ -184,8 +184,8 @@ fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
add = 1
toggle = 2
ptype = 4
- chWState f = io $ changeProperty32 dpy win state ptype propModeReplace (f wstate)
- when (typ == state && fi fullsc `elem` dats) $ do
+ chWState f = io $ changeProperty32 dpy win wmstate ptype propModeReplace (f wstate)
+ when (typ == wmstate && fi fullsc `elem` dats) $ do
when (action == add || (action == toggle && not isFull)) $ do
chWState (fi fullsc:)
broadcastMessage $ AddFullscreen win