diff options
author | Spencer Janssen <sjanssen@cse.unl.edu> | 2008-01-18 04:22:28 +0100 |
---|---|---|
committer | Spencer Janssen <sjanssen@cse.unl.edu> | 2008-01-18 04:22:28 +0100 |
commit | 33f724f49a802d979d420ef8dc9bde8e063ceea9 (patch) | |
tree | 935fc658cecbfc89bdb0fc9860de8b2a14cf588f | |
parent | f0b743e3ad16a47efe4768294aad95e7b8e71092 (diff) | |
download | xmonad-33f724f49a802d979d420ef8dc9bde8e063ceea9.tar.gz xmonad-33f724f49a802d979d420ef8dc9bde8e063ceea9.tar.xz xmonad-33f724f49a802d979d420ef8dc9bde8e063ceea9.zip |
Simplify duplicate/cloned screen logic
darcs-hash:20080118032228-a5988-04035889f9b0a1230b09a9334ea6341783e16052.gz
-rw-r--r-- | XMonad/Main.hs | 3 | ||||
-rw-r--r-- | XMonad/Operations.hs | 41 |
2 files changed, 22 insertions, 22 deletions
diff --git a/XMonad/Main.hs b/XMonad/Main.hs index 94a8a22..2c22792 100644 --- a/XMonad/Main.hs +++ b/XMonad/Main.hs @@ -26,7 +26,6 @@ import System.Environment (getArgs) import Graphics.X11.Xlib hiding (refreshKeyboardMapping) import Graphics.X11.Xlib.Extras -import Graphics.X11.Xinerama (getScreenInfo) import XMonad.Core import XMonad.StackSet (new, floating, member) @@ -46,7 +45,7 @@ xmonad initxmc = do let dflt = defaultScreen dpy rootw <- rootWindow dpy dflt - xinesc <- getScreenInfo dpy + xinesc <- getCleanedScreenInfo dpy nbc <- initColor dpy $ normalBorderColor xmc fbc <- initColor dpy $ focusedBorderColor xmc hSetBuffering stdout NoBuffering diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs index db537d6..faa5ad2 100644 --- a/XMonad/Operations.hs +++ b/XMonad/Operations.hs @@ -246,34 +246,35 @@ tileWindow w r = withDisplay $ \d -> do -- --------------------------------------------------------------------- --- | 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) = - x1 >= x2 && - y1 >= y2 && - fromIntegral x1 + w1 <= fromIntegral x2 + w2 && - fromIntegral y1 + h1 <= fromIntegral y2 + h2 - -- remove all screens completely contained in another. - 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 - +-- | Returns True if the first rectangle is contained within, but not equal +-- to the second. +containedIn :: Rectangle -> Rectangle -> Bool +containedIn r1@(Rectangle x1 y1 w1 h1) r2@(Rectangle x2 y2 w2 h2) + = and [ r1 /= r2 + , x1 >= x2 + , y1 >= y2 + , fromIntegral x1 + w1 <= fromIntegral x2 + w2 + , fromIntegral y1 + h1 <= fromIntegral y2 + h2 ] + +-- | Given a list of screens, remove all duplicated screens and screens that +-- are entirely contained within another. +nubScreens :: [Rectangle] -> [Rectangle] +nubScreens xs = nub . filter (\x -> not $ any (x `containedIn`) xs) $ xs + +-- | Cleans the list of screens according to the rules documented for +-- nubScreens. +getCleanedScreenInfo :: MonadIO m => Display -> m [Rectangle] +getCleanedScreenInfo = io . fmap nubScreens . getScreenInfo -- | 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) + xinesc <- withDisplay 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 - (a:as) = zipWith3 (\x (n,s) g -> W.Screen x n (SD s g)) xs xinesc gs + (a:as) = zipWith3 W.Screen xs [0..] $ zipWith SD xinesc gs sgs = map (statusGap . W.screenDetail) (v:vs) gs = take (length xinesc) (sgs ++ repeat (0,0,0,0)) in ws { W.current = a |