aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util/WorkspaceCompare.hs
diff options
context:
space:
mode:
authorJuraj Hercek <juhe_xmonad@hck.sk>2008-01-09 16:49:23 +0100
committerJuraj Hercek <juhe_xmonad@hck.sk>2008-01-09 16:49:23 +0100
commit1539f68a9a5297dff073cc062a1baf14458153f5 (patch)
treea89dd2e5e0b024528fca41a6cad306f62f22728d /XMonad/Util/WorkspaceCompare.hs
parent91e67ec7f78a2859e32a8400326114bc5db69a60 (diff)
downloadXMonadContrib-1539f68a9a5297dff073cc062a1baf14458153f5.tar.gz
XMonadContrib-1539f68a9a5297dff073cc062a1baf14458153f5.tar.xz
XMonadContrib-1539f68a9a5297dff073cc062a1baf14458153f5.zip
Extended PP with sorting algorithm specification and added xinerama sorting
algorithm - idea is to specify sorting algorithm from user's xmonad.hs - xinerama sorting algorithm produces same ordering as pprWindowSetXinerama - default ppSort is set to getSortByTag, so the default functionality is the same as it was before darcs-hash:20080109154923-69f16-2b9674eab322c2cac47698a66402cecae6abe253.gz
Diffstat (limited to 'XMonad/Util/WorkspaceCompare.hs')
-rw-r--r--XMonad/Util/WorkspaceCompare.hs40
1 files changed, 34 insertions, 6 deletions
diff --git a/XMonad/Util/WorkspaceCompare.hs b/XMonad/Util/WorkspaceCompare.hs
index bba9ebe..3517100 100644
--- a/XMonad/Util/WorkspaceCompare.hs
+++ b/XMonad/Util/WorkspaceCompare.hs
@@ -9,12 +9,17 @@
-- Portability : unportable
--
-module XMonad.Util.WorkspaceCompare ( getWsIndex, getWsCompare, getSortByTag ) where
+module XMonad.Util.WorkspaceCompare ( getWsIndex
+ , getWsCompare
+ , getSortByTag
+ , getSortByXineramaRule ) where
import XMonad
import qualified XMonad.StackSet as S
import Data.List
import Data.Monoid
+import Data.Ord
+import Data.Maybe
-- | Lookup the index of a workspace id in the user's config, return Nothing
-- if that workspace does not exist in the config.
@@ -28,14 +33,37 @@ getWsCompare :: X (WorkspaceId -> WorkspaceId -> Ordering)
getWsCompare = do
wsIndex <- getWsIndex
return $ \a b -> f (wsIndex a) (wsIndex b) `mappend` compare a b
- where
- f Nothing Nothing = EQ
- f (Just _) Nothing = LT
- f Nothing (Just _) = GT
- f (Just x) (Just y) = compare x y
+ where
+ f Nothing Nothing = EQ
+ f (Just _) Nothing = LT
+ f Nothing (Just _) = GT
+ f (Just x) (Just y) = compare x y
+
+-- | A comparison function for Xinerama based on visibility, workspace and
+-- screen id. It produces same ordering as pprWindowSetXinerama does.
+getXineramaWsCompare :: X(WorkspaceId -> WorkspaceId -> Ordering)
+getXineramaWsCompare = do
+ w <- gets windowset
+ return $ \ a b -> case (isOnScreen a w, isOnScreen b w) of
+ (True, True) -> comparing (tagToSid (onScreen w)) a b
+ (False, False) -> compare a b
+ (True, False) -> LT
+ (False, True) -> GT
+ where
+ onScreen w = S.current w : S.visible w
+ isOnScreen a w = a `elem` map (S.tag . S.workspace) (onScreen w)
+ tagToSid s x = S.screen $ fromJust $ find ((== x) . S.tag . S.workspace) s
+ --S.screen $ head $ filter ((== x) . S.tag . S.workspace) s
-- | Sort several workspaces according to the order in getWsCompare
getSortByTag :: X ([WindowSpace] -> [WindowSpace])
getSortByTag = do
cmp <- getWsCompare
return $ sortBy (\a b -> cmp (S.tag a) (S.tag b))
+
+-- | Sort serveral workspaces for xinerama displays
+getSortByXineramaRule :: X ([WindowSpace] -> [WindowSpace])
+getSortByXineramaRule = do
+ cmp <- getXineramaWsCompare
+ return $ sortBy (\a b -> cmp (S.tag a) (S.tag b))
+