Add preliminary randr support

This commit is contained in:
Spencer Janssen
2007-05-22 04:02:28 +00:00
parent c4dd126200
commit 07a354e5a3
2 changed files with 27 additions and 2 deletions

View File

@@ -26,7 +26,7 @@ import Graphics.X11.Xinerama (getScreenInfo)
import XMonad
import Config
import StackSet (new)
import Operations (manage, unmanage, focus, setFocusX, full, isClient)
import Operations (manage, unmanage, focus, setFocusX, full, isClient, rescreen)
--
-- The main entry point
@@ -70,7 +70,7 @@ main = do
-- setup initial X environment
sync dpy False
selectInput dpy rootw $ substructureRedirectMask .|. substructureNotifyMask
.|. enterWindowMask .|. leaveWindowMask
.|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask
grabKeys dpy rootw
sync dpy False
@@ -171,4 +171,9 @@ handle e@(ConfigureRequestEvent {}) = withDisplay $ \dpy -> do
, wc_stack_mode = fromIntegral $ ev_detail e }
io $ sync dpy False
-- the root may have configured
handle e@(ConfigureEvent {ev_window = w}) = do
r <- asks theRoot
when (r == w) rescreen
handle _ = return () -- trace (eventName e) -- ignoring

View File

@@ -28,6 +28,7 @@ import Control.Monad.Reader
import Control.Arrow
import Graphics.X11.Xlib
import Graphics.X11.Xinerama (getScreenInfo)
import Graphics.X11.Xlib.Extras
-- ---------------------------------------------------------------------
@@ -155,6 +156,25 @@ tileWindow d w r = do
-- ---------------------------------------------------------------------
-- | rescreen. The screen configuration may have changed, update the state and
-- refresh the screen.
rescreen :: X ()
rescreen = do
dpy <- asks display
xinesc <- io $ getScreenInfo dpy
-- TODO: This stuff is necessary because Xlib apparently caches screen
-- width/height. Find a better solution later. I hate Xlib.
let sx = maximum $ map (\r -> rect_x r + fromIntegral (rect_width r)) xinesc
sy = maximum $ map (\r -> rect_y r + fromIntegral (rect_height r)) xinesc
modify (\s -> s { xineScreens = xinesc, dimensions = (sx, sy) })
windows $ \ws@(W.StackSet { W.current = v, W.visible = vs, W.hidden = hs }) ->
let (x:xs, ys) = splitAt (length xinesc) $ map W.workspace (v:vs) ++ hs
in ws { W.current = W.Screen x 0
, W.visible = zipWith W.Screen xs [1 ..]
, W.hidden = ys }
-- ---------------------------------------------------------------------
buttonsToGrab :: [Button]
buttonsToGrab = [button1, button2, button3]