aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions
diff options
context:
space:
mode:
authorDevin Mullins <me@twifkak.com>2008-09-21 03:11:59 +0200
committerDevin Mullins <me@twifkak.com>2008-09-21 03:11:59 +0200
commit508debd233d9bddf5f5f8c8ad071fcbe52da4f0e (patch)
treeacf8b9e46e295dbb61db0b137456d4e32505da2d /XMonad/Actions
parent4f7c0734e3736dce79dda5656f6bd88540d9e9d1 (diff)
downloadXMonadContrib-508debd233d9bddf5f5f8c8ad071fcbe52da4f0e.tar.gz
XMonadContrib-508debd233d9bddf5f5f8c8ad071fcbe52da4f0e.tar.xz
XMonadContrib-508debd233d9bddf5f5f8c8ad071fcbe52da4f0e.zip
cleanup - use currentTag
darcs-hash:20080921011159-78224-b0ac172560719cba3a1c41171d91e222a6fa1304.gz
Diffstat (limited to 'XMonad/Actions')
-rw-r--r--XMonad/Actions/CopyWindow.hs4
-rw-r--r--XMonad/Actions/CycleWS.hs2
-rw-r--r--XMonad/Actions/PerWorkspaceKeys.hs2
-rw-r--r--XMonad/Actions/SwapWorkspaces.hs2
-rw-r--r--XMonad/Actions/TagWindows.hs7
-rw-r--r--XMonad/Actions/WindowBringer.hs2
-rw-r--r--XMonad/Actions/WindowNavigation.hs4
7 files changed, 11 insertions, 12 deletions
diff --git a/XMonad/Actions/CopyWindow.hs b/XMonad/Actions/CopyWindow.hs
index 68835e8..68d6e38 100644
--- a/XMonad/Actions/CopyWindow.hs
+++ b/XMonad/Actions/CopyWindow.hs
@@ -77,7 +77,7 @@ copyToAll s = foldr copy s $ map tag (workspaces s)
copyWindow :: (Eq a, Eq i, Eq s) => a -> i -> StackSet i l a s sd -> StackSet i l a s sd
copyWindow w n = copy'
where copy' s = if n `tagMember` s
- then view (tag (workspace (current s))) $ insertUp' w $ view n s
+ then view (currentTag s) $ insertUp' w $ view n s
else s
insertUp' a s = modify (Just $ Stack a [] [])
(\(Stack t l r) -> if a `elem` t:l++r
@@ -107,7 +107,7 @@ kill1 = do ss <- gets windowset
killAllOtherCopies :: X ()
killAllOtherCopies = do ss <- gets windowset
whenJust (peek ss) $ \w -> windows $
- view (tag (workspace (current ss))) .
+ view (currentTag ss) .
delFromAllButCurrent w
where
delFromAllButCurrent w ss = foldr ($) ss $
diff --git a/XMonad/Actions/CycleWS.hs b/XMonad/Actions/CycleWS.hs
index ac0fddb..f7a59bb 100644
--- a/XMonad/Actions/CycleWS.hs
+++ b/XMonad/Actions/CycleWS.hs
@@ -217,7 +217,7 @@ findWorkspace s dir t n = findWorkspaceGen s (wsTypeToPred t) (maybeNegate dir n
maybeNegate Prev d = (-d)
findWorkspaceGen :: X WorkspaceSort -> X (WindowSpace -> Bool) -> Int -> X WorkspaceId
-findWorkspaceGen _ _ 0 = (tag . workspace . current) `fmap` gets windowset
+findWorkspaceGen _ _ 0 = gets (currentTag . windowset)
findWorkspaceGen sortX wsPredX d = do
wsPred <- wsPredX
sort <- sortX
diff --git a/XMonad/Actions/PerWorkspaceKeys.hs b/XMonad/Actions/PerWorkspaceKeys.hs
index 9dd6a5d..dcf1a9b 100644
--- a/XMonad/Actions/PerWorkspaceKeys.hs
+++ b/XMonad/Actions/PerWorkspaceKeys.hs
@@ -36,7 +36,7 @@ import Data.List (find)
-- | Uses supplied function to decide which action to run depending on current workspace name.
chooseAction :: (String->X()) -> X()
-chooseAction f = withWindowSet (f . S.tag . S.workspace . S.current)
+chooseAction f = withWindowSet (f . S.currentTag)
-- | If current workspace is listed, run appropriate action (only the first match counts!)
-- If it isn't listed, then run default action (marked with empty string, \"\"), or do nothing if default isn't supplied.
diff --git a/XMonad/Actions/SwapWorkspaces.hs b/XMonad/Actions/SwapWorkspaces.hs
index c9b1143..9890ef2 100644
--- a/XMonad/Actions/SwapWorkspaces.hs
+++ b/XMonad/Actions/SwapWorkspaces.hs
@@ -48,7 +48,7 @@ import XMonad.Util.WorkspaceCompare
-- | Swaps the currently focused workspace with the given workspace tag, via
-- @swapWorkspaces@.
swapWithCurrent :: Eq i => i -> StackSet i l a s sd -> StackSet i l a s sd
-swapWithCurrent t s = swapWorkspaces t (tag $ workspace $ current s) s
+swapWithCurrent t s = swapWorkspaces t (currentTag s) s
-- | Say @swapTo Next@ or @swapTo Prev@ to move your current workspace.
-- This is an @X ()@ so can be hooked up to your keybindings directly.
diff --git a/XMonad/Actions/TagWindows.hs b/XMonad/Actions/TagWindows.hs
index 4501e7d..01ea1d8 100644
--- a/XMonad/Actions/TagWindows.hs
+++ b/XMonad/Actions/TagWindows.hs
@@ -120,7 +120,7 @@ wsToList ws = crs ++ cls
wsToListGlobal :: (Ord i) => StackSet i l a s sd -> [a]
wsToListGlobal ws = concat ([crs] ++ rws ++ lws ++ [cls])
where
- curtag = tag . workspace . current $ ws
+ curtag = currentTag ws
(crs, cls) = (cms down, cms (reverse . up))
cms f = maybe [] f (stack . workspace . current $ ws)
(lws, rws) = (mws (<), mws (>))
@@ -149,8 +149,7 @@ withTagged t f = withTagged' t (mapM_ f)
withTaggedGlobal t f = withTaggedGlobal' t (mapM_ f)
withTagged' :: String -> ([Window] -> X ()) -> X ()
-withTagged' t m = gets windowset >>=
- filterM (hasTag t) . integrate' . stack . workspace . current >>= m
+withTagged' t m = gets windowset >>= filterM (hasTag t) . index >>= m
withTaggedGlobal' :: String -> ([Window] -> X ()) -> X ()
withTaggedGlobal' t m = gets windowset >>=
@@ -160,7 +159,7 @@ withFocusedP :: (Window -> WindowSet -> WindowSet) -> X ()
withFocusedP f = withFocused $ windows . f
shiftHere :: (Ord a, Eq s, Eq i) => a -> StackSet i l a s sd -> StackSet i l a s sd
-shiftHere w s = shiftWin (tag . workspace . current $ s) w s
+shiftHere w s = shiftWin (currentTag s) w s
shiftToScreen :: (Ord a, Eq s, Eq i) => s -> a -> StackSet i l a s sd -> StackSet i l a s sd
shiftToScreen sid w s = case filter (\m -> sid /= screen m) ((current s):(visible s)) of
diff --git a/XMonad/Actions/WindowBringer.hs b/XMonad/Actions/WindowBringer.hs
index 83ba481..102c15b 100644
--- a/XMonad/Actions/WindowBringer.hs
+++ b/XMonad/Actions/WindowBringer.hs
@@ -57,7 +57,7 @@ bringMenu = actionMenu bringWindow
-- | Brings the specified window into the current workspace.
bringWindow :: Window -> X.WindowSet -> X.WindowSet
-bringWindow w ws = W.shiftWin (W.tag . W.workspace . W.current $ ws) w ws
+bringWindow w ws = W.shiftWin (W.currentTag ws) w ws
-- | Calls dmenuMap to grab the appropriate Window, and hands it off to action
-- if found.
diff --git a/XMonad/Actions/WindowNavigation.hs b/XMonad/Actions/WindowNavigation.hs
index 88c4db1..99b61b6 100644
--- a/XMonad/Actions/WindowNavigation.hs
+++ b/XMonad/Actions/WindowNavigation.hs
@@ -153,7 +153,7 @@ currentPosition posRef = do
currentWindow <- gets (W.peek . windowset)
currentRect <- maybe (Rectangle 0 0 0 0) snd <$> windowRect (fromMaybe root currentWindow)
- wsid <- gets (W.tag . W.workspace . W.current . windowset)
+ wsid <- gets (W.currentTag . windowset)
mp <- M.lookup wsid <$> io (readIORef posRef)
return $ maybe (middleOf currentRect) (`inside` currentRect) mp
@@ -162,7 +162,7 @@ currentPosition posRef = do
setPosition :: IORef WNState -> Point -> Rectangle -> X ()
setPosition posRef oldPos newRect = do
- wsid <- gets (W.tag . W.workspace . W.current . windowset)
+ wsid <- gets (W.currentTag . windowset)
io $ modifyIORef posRef $ M.insert wsid (oldPos `inside` newRect)
inside :: Point -> Rectangle -> Point