aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorMiikka Koskinen <arcatan@kapsi.fi>2007-05-21 14:32:39 +0200
committerMiikka Koskinen <arcatan@kapsi.fi>2007-05-21 14:32:39 +0200
commit72fdae2450b73e99ba1f3f204e48de7677870d25 (patch)
tree6045c86e7fb81eb8ccfb21aaf0d0cf5378192692
parent9bb0bc291344fc093f9bba4d5c38ebcc166a8726 (diff)
downloadXMonadContrib-72fdae2450b73e99ba1f3f204e48de7677870d25.tar.gz
XMonadContrib-72fdae2450b73e99ba1f3f204e48de7677870d25.tar.xz
XMonadContrib-72fdae2450b73e99ba1f3f204e48de7677870d25.zip
make FindEmptyWorkspace compile
darcs-hash:20070521123239-0ff8e-810c84edaff2f94ff23e499a7cf53498e3031515.gz
-rw-r--r--FindEmptyWorkspace.hs34
1 files changed, 19 insertions, 15 deletions
diff --git a/FindEmptyWorkspace.hs b/FindEmptyWorkspace.hs
index 860f8b7..44794b1 100644
--- a/FindEmptyWorkspace.hs
+++ b/FindEmptyWorkspace.hs
@@ -28,32 +28,36 @@ module XMonadContrib.FindEmptyWorkspace (
) where
import Control.Monad.State
-import qualified Data.Map as M
+import Data.List
import XMonad
-import Operations
-import qualified StackSet as W
-
--- | Find the first empty workspace in a WindowSet. Returns Nothing if
--- all workspaces are in use.
-findEmptyWorkspace :: WindowSet -> Maybe WorkspaceId
-findEmptyWorkspace = findKey (([],[]) ==) . W.stacks
+import StackSet
+
+import qualified Operations as O
+
+-- | Find the first hidden empty workspace in a StackSet. Returns
+-- Nothing if all workspaces are in use. Function searches currently
+-- focused workspace, other visible workspaces (when in Xinerama) and
+-- hidden workspaces in this order.
+findEmptyWorkspace :: StackSet i a s -> Maybe (Workspace i a)
+findEmptyWorkspace = find (isEmpty . stack) . allWorkspaces
+ where
+ isEmpty Empty = True
+ isEmpty _ = False
+ allWorkspaces ss = (workspace . current) ss :
+ (map workspace . visible) ss ++ hidden ss
withEmptyWorkspace :: (WorkspaceId -> X ()) -> X ()
withEmptyWorkspace f = do
ws <- gets windowset
- whenJust (findEmptyWorkspace ws) f
+ whenJust (findEmptyWorkspace ws) (f . tag)
-- | Find and view an empty workspace. Do nothing if all workspaces are
-- in use.
viewEmptyWorkspace :: X ()
-viewEmptyWorkspace = withEmptyWorkspace view
+viewEmptyWorkspace = withEmptyWorkspace O.view
-- | Tag current window to an empty workspace and view it. Do nothing if
-- all workspaces are in use.
tagToEmptyWorkspace :: X ()
-tagToEmptyWorkspace = withEmptyWorkspace $ \w -> tag w >> view w
-
--- Thanks to mauke on #haskell
-findKey :: (a -> Bool) -> M.Map k a -> Maybe k
-findKey f = M.foldWithKey (\k a -> mplus (if f a then Just k else Nothing)) Nothing
+tagToEmptyWorkspace = withEmptyWorkspace $ \w -> O.shift w >> O.view w