From 1539f68a9a5297dff073cc062a1baf14458153f5 Mon Sep 17 00:00:00 2001 From: Juraj Hercek Date: Wed, 9 Jan 2008 16:49:23 +0100 Subject: 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 --- XMonad/Hooks/DynamicLog.hs | 4 +++- XMonad/Util/WorkspaceCompare.hs | 40 ++++++++++++++++++++++++++++++++++------ 2 files changed, 37 insertions(+), 7 deletions(-) diff --git a/XMonad/Hooks/DynamicLog.hs b/XMonad/Hooks/DynamicLog.hs index d6ab9eb..d949a85 100644 --- a/XMonad/Hooks/DynamicLog.hs +++ b/XMonad/Hooks/DynamicLog.hs @@ -108,7 +108,7 @@ dynamicLogWithPP :: PP -> X () dynamicLogWithPP pp = do winset <- gets windowset urgents <- readUrgents - sort' <- getSortByTag + sort' <- ppSort pp -- layout description let ld = description . S.layout . S.workspace . S.current $ winset -- workspace list @@ -200,6 +200,7 @@ data PP = PP { ppCurrent, ppVisible , ppLayout :: String -> String , ppOrder :: [String] -> [String] , ppOutput :: String -> IO () + , ppSort :: X ([WindowSpace] -> [WindowSpace]) } -- | The default pretty printing options, as seen in dynamicLog @@ -215,6 +216,7 @@ defaultPP = PP { ppCurrent = wrap "[" "]" , ppLayout = id , ppOrder = id , ppOutput = putStrLn + , ppSort = getSortByTag } -- | Settings to emulate dwm's statusbar, dzen only 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)) + -- cgit v1.2.3