From a40b80d0d810733be0cd7553d11339217e5528ed Mon Sep 17 00:00:00 2001 From: Anders Engstrom Date: Mon, 8 Mar 2010 12:37:04 +0100 Subject: X.A.PhysicalScreens cleaning and allow cycling Ignore-this: 3a9a3554cda29f976df646b38b56e8e7 Remove redundant import to supress warning, did some refactoring to use xmonad internal things to find screens instead of using X11-stuff. Also added ability to cycle between screens in physical order. darcs-hash:20100308113704-8978f-d312f0f413ff2d6fc1b1fe64dfac098e298d59f5.gz --- XMonad/Actions/PhysicalScreens.hs | 48 +++++++++++++++++++++++++++++++-------- 1 file changed, 38 insertions(+), 10 deletions(-) (limited to 'XMonad') diff --git a/XMonad/Actions/PhysicalScreens.hs b/XMonad/Actions/PhysicalScreens.hs index 84b4e32..7ba3ce5 100644 --- a/XMonad/Actions/PhysicalScreens.hs +++ b/XMonad/Actions/PhysicalScreens.hs @@ -19,14 +19,14 @@ module XMonad.Actions.PhysicalScreens ( , getScreen , viewScreen , sendToScreen + , onNextNeighbour + , onPrevNeighbour ) where import XMonad import qualified XMonad.StackSet as W -import Graphics.X11.Xinerama - -import Data.List (sortBy) +import Data.List (sortBy,findIndex) import Data.Function (on) {- $usage @@ -43,6 +43,11 @@ Example usage in your @~\/.xmonad\/xmonad.hs@ file: > import XMonad.Actions.PhysicalSCreens +> , ((modMask, xK_a), onPrevNeighbour W.view) +> , ((modMask, xK_o), onNextNeighbour W.view) +> , ((modMask .|. shiftMask, xK_a), onPrevNeighbour W.shift) +> , ((modMask .|. shiftMask, xK_o), onNextNeighbour W.shift) + > -- > -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3 > -- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3 @@ -60,12 +65,12 @@ newtype PhysicalScreen = P Int deriving (Eq,Ord,Show,Read,Enum,Num,Integral,Real -- | Translate a physical screen index to a "ScreenId" getScreen :: PhysicalScreen -> X (Maybe ScreenId) -getScreen (P i) = withDisplay $ \dpy -> do - screens <- io $ getScreenInfo dpy - if i >= length screens - then return Nothing - else let ss = sortBy (cmpScreen `on` fst) $ zip screens [0..] - in return $ Just $ snd $ ss !! i +getScreen (P i) = do w <- gets windowset + let screens = W.current w : W.visible w + if i<0 || i >= length screens + then return Nothing + else let ss = sortBy (cmpScreen `on` (screenRect . W.screenDetail)) screens + in return $ Just $ W.screen $ ss !! i -- | Switch to a given physical screen viewScreen :: PhysicalScreen -> X () @@ -84,4 +89,27 @@ sendToScreen p = do i <- getScreen p -- | Compare two screens by their top-left corners, ordering -- | top-to-bottom and then left-to-right. cmpScreen :: Rectangle -> Rectangle -> Ordering -cmpScreen (Rectangle x1 y1 _ _) (Rectangle x2 y2 _ _) = compare (y1,x1) (y2,x2) +cmpScreen (Rectangle x1 y1 _ _) (Rectangle x2 y2 _ _) = compare (y1,x1) (y2,x2) + + +-- | Get ScreenId for neighbours of the current screen based on position offset. +getNeighbour :: Int -> X ScreenId +getNeighbour d = do w <- gets windowset + let ss = map W.screen $ sortBy (cmpScreen `on` (screenRect . W.screenDetail)) $ W.current w : W.visible w + curPos = maybe 0 id $ findIndex (== W.screen (W.current w)) ss + pos = (curPos + d) `mod` length ss + return $ ss !! pos + +neighbourWindows :: Int -> (WorkspaceId -> WindowSet -> WindowSet) -> X () +neighbourWindows d f = do s <- getNeighbour d + w <- screenWorkspace s + whenJust w $ windows . f + +-- | Apply operation on a WindowSet with the WorkspaceId of the next screen in the physical order as parameter. +onNextNeighbour :: (WorkspaceId -> WindowSet -> WindowSet) -> X () +onNextNeighbour = neighbourWindows 1 + +-- | Apply operation on a WindowSet with the WorkspaceId of the previous screen in the physical order as parameter. +onPrevNeighbour :: (WorkspaceId -> WindowSet -> WindowSet) -> X () +onPrevNeighbour = neighbourWindows (-1) + -- cgit v1.2.3