Simplify duplicate/cloned screen logic

This commit is contained in:
Spencer Janssen 2008-01-18 03:22:28 +00:00
parent be5e27038f
commit f9799422f9
2 changed files with 21 additions and 21 deletions

View File

@ -26,7 +26,6 @@ import System.Environment (getArgs)
import Graphics.X11.Xlib hiding (refreshKeyboardMapping) import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
import Graphics.X11.Xlib.Extras import Graphics.X11.Xlib.Extras
import Graphics.X11.Xinerama (getScreenInfo)
import XMonad.Core import XMonad.Core
import XMonad.StackSet (new, floating, member) import XMonad.StackSet (new, floating, member)
@ -46,7 +45,7 @@ xmonad initxmc = do
let dflt = defaultScreen dpy let dflt = defaultScreen dpy
rootw <- rootWindow dpy dflt rootw <- rootWindow dpy dflt
xinesc <- getScreenInfo dpy xinesc <- getCleanedScreenInfo dpy
nbc <- initColor dpy $ normalBorderColor xmc nbc <- initColor dpy $ normalBorderColor xmc
fbc <- initColor dpy $ focusedBorderColor xmc fbc <- initColor dpy $ focusedBorderColor xmc
hSetBuffering stdout NoBuffering hSetBuffering stdout NoBuffering

View File

@ -246,34 +246,35 @@ tileWindow w r = withDisplay $ \d -> do
-- --------------------------------------------------------------------- -- ---------------------------------------------------------------------
-- | getCleanedScreenInfo. reads the list of screens and removes -- | Returns True if the first rectangle is contained within, but not equal
-- duplicated or contained screens. -- to the second.
getCleanedScreenInfo :: Display -> IO ([(ScreenId, Rectangle)]) containedIn :: Rectangle -> Rectangle -> Bool
getCleanedScreenInfo dpy = do containedIn r1@(Rectangle x1 y1 w1 h1) r2@(Rectangle x2 y2 w2 h2)
xinesc' <- getScreenInfo dpy = and [ r1 /= r2
let xinescN' = zip [0..] xinesc' , x1 >= x2
containedIn :: Rectangle -> Rectangle -> Bool , y1 >= y2
containedIn (Rectangle x1 y1 w1 h1) (Rectangle x2 y2 w2 h2) = , fromIntegral x1 + w1 <= fromIntegral x2 + w2
x1 >= x2 && , fromIntegral y1 + h1 <= fromIntegral y2 + h2 ]
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
-- | 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 -- | rescreen. The screen configuration may have changed (due to
-- xrandr), update the state and refresh the screen, and reset the gap. -- xrandr), update the state and refresh the screen, and reset the gap.
rescreen :: X () rescreen :: X ()
rescreen = do rescreen = do
xinesc <- withDisplay (io . getCleanedScreenInfo) xinesc <- withDisplay getCleanedScreenInfo
windows $ \ws@(W.StackSet { W.current = v, W.visible = vs, W.hidden = hs }) -> 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 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) sgs = map (statusGap . W.screenDetail) (v:vs)
gs = take (length xinesc) (sgs ++ repeat (0,0,0,0)) gs = take (length xinesc) (sgs ++ repeat (0,0,0,0))
in ws { W.current = a in ws { W.current = a