summaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorJoachim Breitner <mail@joachim-breitner.de>2007-12-31 19:15:56 +0100
committerJoachim Breitner <mail@joachim-breitner.de>2007-12-31 19:15:56 +0100
commit60fca32854a646dfbce8156a1789bce773fccfa4 (patch)
tree37146f5fef798fe64249812112debcc5e8980104 /XMonad
parenteb3c9dbaccd0dd3a0a11e1b9a7590a3992590910 (diff)
downloadmetatile-60fca32854a646dfbce8156a1789bce773fccfa4.tar
metatile-60fca32854a646dfbce8156a1789bce773fccfa4.zip
Put the screen removing stuff in getCleanedScreenInfo
darcs-hash:20071231181556-23c07-0ff6a10eb151e7ea06e57f2c6317fe21f87309c8
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Operations.hs18
1 files changed, 13 insertions, 5 deletions
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index 71b9c31..db537d6 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -246,11 +246,11 @@ tileWindow w r = withDisplay $ \d -> do
-- ---------------------------------------------------------------------
--- | rescreen. The screen configuration may have changed (due to
--- xrandr), update the state and refresh the screen, and reset the gap.
-rescreen :: X ()
-rescreen = do
- xinesc' <- withDisplay (io . getScreenInfo)
+-- | getCleanedScreenInfo. reads the list of screens and removes
+-- duplicated or contained screens.
+getCleanedScreenInfo :: Display -> IO ([(ScreenId, Rectangle)])
+getCleanedScreenInfo dpy = do
+ xinesc' <- getScreenInfo dpy
let xinescN' = zip [0..] xinesc'
containedIn :: Rectangle -> Rectangle -> Bool
containedIn (Rectangle x1 y1 w1 h1) (Rectangle x2 y2 w2 h2) =
@@ -262,6 +262,14 @@ rescreen = do
xinescS' = filter (\(_,r1) -> not (any (\r2 -> r1 `containedIn` r2 && r1 /= r2) xinesc')) xinescN'
-- removes all duplicate screens but the first
xinesc = foldr (\r l -> if snd r `elem` map snd l then l else r:l) [] xinescS'
+ return xinesc
+
+
+-- | rescreen. The screen configuration may have changed (due to
+-- xrandr), update the state and refresh the screen, and reset the gap.
+rescreen :: X ()
+rescreen = do
+ xinesc <- withDisplay (io . getCleanedScreenInfo)
windows $ \ws@(W.StackSet { W.current = v, W.visible = vs, W.hidden = hs }) ->
let (xs, ys) = splitAt (length xinesc) $ map W.workspace (v:vs) ++ hs