mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 03:20:21 -07:00
Rename variables "state" to avoid warnings about shadowing
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)
This commit is contained in:
parent
e776260133
commit
1716ffd9d0
@ -110,7 +110,7 @@ plane ::
|
|||||||
(WorkspaceId -> WindowSet -> WindowSet) -> Lines -> Limits -> Direction ->
|
(WorkspaceId -> WindowSet -> WindowSet) -> Lines -> Limits -> Direction ->
|
||||||
X ()
|
X ()
|
||||||
plane function numberLines_ limits direction = do
|
plane function numberLines_ limits direction = do
|
||||||
state <- get
|
st <- get
|
||||||
xconf <- ask
|
xconf <- ask
|
||||||
|
|
||||||
numberLines <-
|
numberLines <-
|
||||||
@ -205,7 +205,7 @@ plane function numberLines_ limits direction = do
|
|||||||
preColumns = div areas numberLines
|
preColumns = div areas numberLines
|
||||||
|
|
||||||
mCurrentWS :: Maybe Int
|
mCurrentWS :: Maybe Int
|
||||||
mCurrentWS = elemIndex (currentTag $ windowset state) areaNames
|
mCurrentWS = elemIndex (currentTag $ windowset st) areaNames
|
||||||
|
|
||||||
areas :: Int
|
areas :: Int
|
||||||
areas = length areaNames
|
areas = length areaNames
|
||||||
|
@ -112,11 +112,11 @@ multiPP focusPP unfocusPP = do
|
|||||||
|
|
||||||
multiPP' :: (PP -> X String) -> PP -> PP -> [Handle] -> X ()
|
multiPP' :: (PP -> X String) -> PP -> PP -> [Handle] -> X ()
|
||||||
multiPP' dynlStr focusPP unfocusPP handles = do
|
multiPP' dynlStr focusPP unfocusPP handles = do
|
||||||
state <- get
|
st <- get
|
||||||
let pickPP :: WorkspaceId -> WriterT (Last XState) X String
|
let pickPP :: WorkspaceId -> WriterT (Last XState) X String
|
||||||
pickPP ws = do
|
pickPP ws = do
|
||||||
let isFoc = (ws ==) . W.tag . W.workspace . W.current $ windowset state
|
let isFoc = (ws ==) . W.tag . W.workspace . W.current $ windowset st
|
||||||
put state{ windowset = W.view ws $ windowset state }
|
put st{ windowset = W.view ws $ windowset st }
|
||||||
out <- lift $ dynlStr $ if isFoc then focusPP else unfocusPP
|
out <- lift $ dynlStr $ if isFoc then focusPP else unfocusPP
|
||||||
when isFoc $ get >>= tell . Last . Just
|
when isFoc $ get >>= tell . Last . Just
|
||||||
return out
|
return out
|
||||||
|
@ -170,9 +170,9 @@ handle _ _ = return ()
|
|||||||
-- Note this is not included in 'ewmh'.
|
-- Note this is not included in 'ewmh'.
|
||||||
fullscreenEventHook :: Event -> X All
|
fullscreenEventHook :: Event -> X All
|
||||||
fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
|
fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
|
||||||
state <- getAtom "_NET_WM_STATE"
|
wmstate <- getAtom "_NET_WM_STATE"
|
||||||
fullsc <- getAtom "_NET_WM_STATE_FULLSCREEN"
|
fullsc <- getAtom "_NET_WM_STATE_FULLSCREEN"
|
||||||
wstate <- fromMaybe [] `fmap` getProp32 state win
|
wstate <- fromMaybe [] `fmap` getProp32 wmstate win
|
||||||
|
|
||||||
let isFull = fromIntegral fullsc `elem` wstate
|
let isFull = fromIntegral fullsc `elem` wstate
|
||||||
|
|
||||||
@ -181,9 +181,9 @@ fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
|
|||||||
add = 1
|
add = 1
|
||||||
toggle = 2
|
toggle = 2
|
||||||
ptype = 4 -- The atom property type for changeProperty
|
ptype = 4 -- The atom property type for changeProperty
|
||||||
chWstate f = io $ changeProperty32 dpy win state ptype propModeReplace (f wstate)
|
chWstate f = io $ changeProperty32 dpy win wmstate ptype propModeReplace (f wstate)
|
||||||
|
|
||||||
when (typ == state && fi fullsc `elem` dats) $ do
|
when (typ == wmstate && fi fullsc `elem` dats) $ do
|
||||||
when (action == add || (action == toggle && not isFull)) $ do
|
when (action == add || (action == toggle && not isFull)) $ do
|
||||||
chWstate (fi fullsc:)
|
chWstate (fi fullsc:)
|
||||||
windows $ W.float win $ W.RationalRect 0 0 1 1
|
windows $ W.float win $ W.RationalRect 0 0 1 1
|
||||||
|
@ -124,11 +124,11 @@ instance LayoutModifier FullscreenFloat Window where
|
|||||||
|
|
||||||
-- Modify the floating member of the stack set directly; this is the hackish part.
|
-- Modify the floating member of the stack set directly; this is the hackish part.
|
||||||
Just FullscreenChanged -> do
|
Just FullscreenChanged -> do
|
||||||
state <- get
|
st <- get
|
||||||
let ws = windowset state
|
let ws = windowset st
|
||||||
flt = W.floating ws
|
flt = W.floating ws
|
||||||
flt' = M.intersectionWith doFull fulls flt
|
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
|
return $ Just $ FullscreenFloat frect $ M.filter snd fulls
|
||||||
where doFull (_, True) _ = frect
|
where doFull (_, True) _ = frect
|
||||||
doFull (rect, False) _ = rect
|
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
|
-- | The event hook required for the layout modifiers to work
|
||||||
fullscreenEventHook :: Event -> X All
|
fullscreenEventHook :: Event -> X All
|
||||||
fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
|
fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
|
||||||
state <- getAtom "_NET_WM_STATE"
|
wmstate <- getAtom "_NET_WM_STATE"
|
||||||
fullsc <- getAtom "_NET_WM_STATE_FULLSCREEN"
|
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
|
let fi :: (Integral i, Num n) => i -> n
|
||||||
fi = fromIntegral
|
fi = fromIntegral
|
||||||
isFull = fi fullsc `elem` wstate
|
isFull = fi fullsc `elem` wstate
|
||||||
@ -184,8 +184,8 @@ fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
|
|||||||
add = 1
|
add = 1
|
||||||
toggle = 2
|
toggle = 2
|
||||||
ptype = 4
|
ptype = 4
|
||||||
chWState f = io $ changeProperty32 dpy win state ptype propModeReplace (f wstate)
|
chWState f = io $ changeProperty32 dpy win wmstate ptype propModeReplace (f wstate)
|
||||||
when (typ == state && fi fullsc `elem` dats) $ do
|
when (typ == wmstate && fi fullsc `elem` dats) $ do
|
||||||
when (action == add || (action == toggle && not isFull)) $ do
|
when (action == add || (action == toggle && not isFull)) $ do
|
||||||
chWState (fi fullsc:)
|
chWState (fi fullsc:)
|
||||||
broadcastMessage $ AddFullscreen win
|
broadcastMessage $ AddFullscreen win
|
||||||
|
@ -136,55 +136,55 @@ mouseResizableTileMirrored :: MouseResizableTile a
|
|||||||
mouseResizableTileMirrored = mouseResizableTile { isMirrored = True }
|
mouseResizableTileMirrored = mouseResizableTile { isMirrored = True }
|
||||||
|
|
||||||
instance LayoutClass MouseResizableTile Window where
|
instance LayoutClass MouseResizableTile Window where
|
||||||
doLayout state sr (W.Stack w l r) = do
|
doLayout st sr (W.Stack w l r) = do
|
||||||
drg <- draggerGeometry $ draggerType state
|
drg <- draggerGeometry $ draggerType st
|
||||||
let wins = reverse l ++ w : r
|
let wins = reverse l ++ w : r
|
||||||
num = length wins
|
num = length wins
|
||||||
sr' = mirrorAdjust sr (mirrorRect sr)
|
sr' = mirrorAdjust sr (mirrorRect sr)
|
||||||
(rects, preparedDraggers) = tile (nmaster state) (masterFrac state)
|
(rects, preparedDraggers) = tile (nmaster st) (masterFrac st)
|
||||||
(leftFracs state ++ repeat (slaveFrac state))
|
(leftFracs st ++ repeat (slaveFrac st))
|
||||||
(rightFracs state ++ repeat (slaveFrac state)) sr' num drg
|
(rightFracs st ++ repeat (slaveFrac st)) sr' num drg
|
||||||
rects' = map (mirrorAdjust id mirrorRect . sanitizeRectangle sr') rects
|
rects' = map (mirrorAdjust id mirrorRect . sanitizeRectangle sr') rects
|
||||||
mapM_ deleteDragger $ draggers state
|
mapM_ deleteDragger $ draggers st
|
||||||
(draggerWrs, newDraggers) <- unzip <$> mapM
|
(draggerWrs, newDraggers) <- unzip <$> mapM
|
||||||
(createDragger sr . adjustForMirror (isMirrored state))
|
(createDragger sr . adjustForMirror (isMirrored st))
|
||||||
preparedDraggers
|
preparedDraggers
|
||||||
return (draggerWrs ++ zip wins rects', Just $ state { draggers = newDraggers,
|
return (draggerWrs ++ zip wins rects', Just $ st { draggers = newDraggers,
|
||||||
focusPos = length l,
|
focusPos = length l,
|
||||||
numWindows = length wins })
|
numWindows = length wins })
|
||||||
where
|
where
|
||||||
mirrorAdjust a b = if (isMirrored state)
|
mirrorAdjust a b = if (isMirrored st)
|
||||||
then b
|
then b
|
||||||
else a
|
else a
|
||||||
|
|
||||||
handleMessage state m
|
handleMessage st m
|
||||||
| Just (IncMasterN d) <- fromMessage m =
|
| Just (IncMasterN d) <- fromMessage m =
|
||||||
return $ Just $ state { nmaster = max 0 (nmaster state + d) }
|
return $ Just $ st { nmaster = max 0 (nmaster st + d) }
|
||||||
| Just Shrink <- fromMessage m =
|
| Just Shrink <- fromMessage m =
|
||||||
return $ Just $ state { masterFrac = max 0 (masterFrac state - fracIncrement state) }
|
return $ Just $ st { masterFrac = max 0 (masterFrac st - fracIncrement st) }
|
||||||
| Just Expand <- fromMessage m =
|
| Just Expand <- fromMessage m =
|
||||||
return $ Just $ state { masterFrac = min 1 (masterFrac state + fracIncrement state) }
|
return $ Just $ st { masterFrac = min 1 (masterFrac st + fracIncrement st) }
|
||||||
| Just ShrinkSlave <- fromMessage m =
|
| Just ShrinkSlave <- fromMessage m =
|
||||||
return $ Just $ modifySlave state (- fracIncrement state)
|
return $ Just $ modifySlave st (- fracIncrement st)
|
||||||
| Just ExpandSlave <- fromMessage m =
|
| Just ExpandSlave <- fromMessage m =
|
||||||
return $ Just $ modifySlave state (fracIncrement state)
|
return $ Just $ modifySlave st (fracIncrement st)
|
||||||
| Just (SetMasterFraction f) <- fromMessage m =
|
| Just (SetMasterFraction f) <- fromMessage m =
|
||||||
return $ Just $ state { masterFrac = max 0 (min 1 f) }
|
return $ Just $ st { masterFrac = max 0 (min 1 f) }
|
||||||
| Just (SetLeftSlaveFraction pos f) <- fromMessage m =
|
| Just (SetLeftSlaveFraction pos f) <- fromMessage m =
|
||||||
return $ Just $ state { leftFracs = replaceAtPos (slaveFrac state)
|
return $ Just $ st { leftFracs = replaceAtPos (slaveFrac st)
|
||||||
(leftFracs state) pos (max 0 (min 1 f)) }
|
(leftFracs st) pos (max 0 (min 1 f)) }
|
||||||
| Just (SetRightSlaveFraction pos f) <- fromMessage m =
|
| Just (SetRightSlaveFraction pos f) <- fromMessage m =
|
||||||
return $ Just $ state { rightFracs = replaceAtPos (slaveFrac state)
|
return $ Just $ st { rightFracs = replaceAtPos (slaveFrac st)
|
||||||
(rightFracs state) pos (max 0 (min 1 f)) }
|
(rightFracs st) pos (max 0 (min 1 f)) }
|
||||||
|
|
||||||
| Just e <- fromMessage m :: Maybe Event = handleResize (draggers state) (isMirrored state) e >> return Nothing
|
| Just e <- fromMessage m :: Maybe Event = handleResize (draggers st) (isMirrored st) e >> return Nothing
|
||||||
| Just Hide <- fromMessage m = releaseResources >> return (Just $ state { draggers = [] })
|
| Just Hide <- fromMessage m = releaseResources >> return (Just $ st { draggers = [] })
|
||||||
| Just ReleaseResources <- fromMessage m = releaseResources >> return (Just $ state { draggers = [] })
|
| Just ReleaseResources <- fromMessage m = releaseResources >> return (Just $ st { draggers = [] })
|
||||||
where releaseResources = mapM_ deleteDragger $ draggers state
|
where releaseResources = mapM_ deleteDragger $ draggers st
|
||||||
handleMessage _ _ = return Nothing
|
handleMessage _ _ = return Nothing
|
||||||
|
|
||||||
description state = mirror "MouseResizableTile"
|
description st = mirror "MouseResizableTile"
|
||||||
where mirror = if isMirrored state then ("Mirror " ++) else id
|
where mirror = if isMirrored st then ("Mirror " ++) else id
|
||||||
|
|
||||||
draggerGeometry :: DraggerType -> X DraggerGeometry
|
draggerGeometry :: DraggerType -> X DraggerGeometry
|
||||||
draggerGeometry (FixedDragger g d) =
|
draggerGeometry (FixedDragger g d) =
|
||||||
@ -203,28 +203,28 @@ adjustForMirror True (draggerRect, draggerCursor, draggerInfo) =
|
|||||||
else xC_sb_h_double_arrow
|
else xC_sb_h_double_arrow
|
||||||
|
|
||||||
modifySlave :: MouseResizableTile a -> Rational -> MouseResizableTile a
|
modifySlave :: MouseResizableTile a -> Rational -> MouseResizableTile a
|
||||||
modifySlave state delta =
|
modifySlave st delta =
|
||||||
let pos = focusPos state
|
let pos = focusPos st
|
||||||
num = numWindows state
|
num = numWindows st
|
||||||
nmaster' = nmaster state
|
nmaster' = nmaster st
|
||||||
leftFracs' = leftFracs state
|
leftFracs' = leftFracs st
|
||||||
rightFracs' = rightFracs state
|
rightFracs' = rightFracs st
|
||||||
slFrac = slaveFrac state
|
slFrac = slaveFrac st
|
||||||
draggersLeft = nmaster' - 1
|
draggersLeft = nmaster' - 1
|
||||||
draggersRight = (num - nmaster') - 1
|
draggersRight = (num - nmaster') - 1
|
||||||
in if pos < nmaster'
|
in if pos < nmaster'
|
||||||
then if draggersLeft > 0
|
then if draggersLeft > 0
|
||||||
then let draggerPos = min (draggersLeft - 1) pos
|
then let draggerPos = min (draggersLeft - 1) pos
|
||||||
oldFraction = (leftFracs' ++ repeat slFrac) !! draggerPos
|
oldFraction = (leftFracs' ++ repeat slFrac) !! draggerPos
|
||||||
in state { leftFracs = replaceAtPos slFrac leftFracs' draggerPos
|
in st { leftFracs = replaceAtPos slFrac leftFracs' draggerPos
|
||||||
(max 0 (min 1 (oldFraction + delta))) }
|
(max 0 (min 1 (oldFraction + delta))) }
|
||||||
else state
|
else st
|
||||||
else if draggersRight > 0
|
else if draggersRight > 0
|
||||||
then let draggerPos = min (draggersRight - 1) (pos - nmaster')
|
then let draggerPos = min (draggersRight - 1) (pos - nmaster')
|
||||||
oldFraction = (rightFracs' ++ repeat slFrac) !! draggerPos
|
oldFraction = (rightFracs' ++ repeat slFrac) !! draggerPos
|
||||||
in state { rightFracs = replaceAtPos slFrac rightFracs' draggerPos
|
in st { rightFracs = replaceAtPos slFrac rightFracs' draggerPos
|
||||||
(max 0 (min 1 (oldFraction + delta))) }
|
(max 0 (min 1 (oldFraction + delta))) }
|
||||||
else state
|
else st
|
||||||
|
|
||||||
replaceAtPos :: (Num t, Eq t) => Rational -> [Rational] -> t -> Rational -> [Rational]
|
replaceAtPos :: (Num t, Eq t) => Rational -> [Rational] -> t -> Rational -> [Rational]
|
||||||
replaceAtPos _ [] 0 x' = [x']
|
replaceAtPos _ [] 0 x' = [x']
|
||||||
|
@ -105,7 +105,7 @@ configurableNavigation :: LayoutClass l a => WNConfig -> l a -> ModifiedLayout W
|
|||||||
configurableNavigation conf = ModifiedLayout (WindowNavigation conf (I Nothing))
|
configurableNavigation conf = ModifiedLayout (WindowNavigation conf (I Nothing))
|
||||||
|
|
||||||
instance LayoutModifier WindowNavigation Window where
|
instance LayoutModifier WindowNavigation Window where
|
||||||
redoLayout (WindowNavigation conf (I state)) rscr (Just s) origwrs =
|
redoLayout (WindowNavigation conf (I st)) rscr (Just s) origwrs =
|
||||||
do XConf { normalBorder = nbc, focusedBorder = fbc, display = dpy } <- ask
|
do XConf { normalBorder = nbc, focusedBorder = fbc, display = dpy } <- ask
|
||||||
[uc,dc,lc,rc] <-
|
[uc,dc,lc,rc] <-
|
||||||
case brightness conf of
|
case brightness conf of
|
||||||
@ -120,8 +120,8 @@ instance LayoutModifier WindowNavigation Window where
|
|||||||
let w = W.focus s
|
let w = W.focus s
|
||||||
r = case filter ((==w).fst) origwrs of ((_,x):_) -> x
|
r = case filter ((==w).fst) origwrs of ((_,x):_) -> x
|
||||||
[] -> rscr
|
[] -> rscr
|
||||||
pt = case state of Just (NS ptold _) | ptold `inrect` r -> ptold
|
pt = case st of Just (NS ptold _) | ptold `inrect` r -> ptold
|
||||||
_ -> center r
|
_ -> center r
|
||||||
existing_wins = W.integrate s
|
existing_wins = W.integrate s
|
||||||
wrs = filter ((`elem` existing_wins) . fst) $ filter ((/=r) . snd) $
|
wrs = filter ((`elem` existing_wins) . fst) $ filter ((/=r) . snd) $
|
||||||
filter ((/=w) . fst) origwrs
|
filter ((/=w) . fst) origwrs
|
||||||
@ -130,8 +130,8 @@ instance LayoutModifier WindowNavigation Window where
|
|||||||
wnavigablec = nub $ concatMap
|
wnavigablec = nub $ concatMap
|
||||||
(\d -> map (\(win,_) -> (win,dirc d)) $
|
(\d -> map (\(win,_) -> (win,dirc d)) $
|
||||||
take 1 $ navigable d pt wrs) [U,D,R,L]
|
take 1 $ navigable d pt wrs) [U,D,R,L]
|
||||||
wothers = case state of Just (NS _ wo) -> map fst wo
|
wothers = case st of Just (NS _ wo) -> map fst wo
|
||||||
_ -> []
|
_ -> []
|
||||||
mapM_ (sc nbc) (wothers \\ map fst wnavigable)
|
mapM_ (sc nbc) (wothers \\ map fst wnavigable)
|
||||||
mapM_ (\(win,c) -> sc c win) wnavigablec
|
mapM_ (\(win,c) -> sc c win) wnavigablec
|
||||||
return (origwrs, Just $ WindowNavigation conf $ I $ Just $ NS pt wnavigable)
|
return (origwrs, Just $ WindowNavigation conf $ I $ Just $ NS pt wnavigable)
|
||||||
|
Loading…
x
Reference in New Issue
Block a user