mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-06 07:01:52 -07:00
Add preliminary randr support
This commit is contained in:
9
Main.hs
9
Main.hs
@@ -26,7 +26,7 @@ import Graphics.X11.Xinerama (getScreenInfo)
|
|||||||
import XMonad
|
import XMonad
|
||||||
import Config
|
import Config
|
||||||
import StackSet (new)
|
import StackSet (new)
|
||||||
import Operations (manage, unmanage, focus, setFocusX, full, isClient)
|
import Operations (manage, unmanage, focus, setFocusX, full, isClient, rescreen)
|
||||||
|
|
||||||
--
|
--
|
||||||
-- The main entry point
|
-- The main entry point
|
||||||
@@ -70,7 +70,7 @@ main = do
|
|||||||
-- setup initial X environment
|
-- setup initial X environment
|
||||||
sync dpy False
|
sync dpy False
|
||||||
selectInput dpy rootw $ substructureRedirectMask .|. substructureNotifyMask
|
selectInput dpy rootw $ substructureRedirectMask .|. substructureNotifyMask
|
||||||
.|. enterWindowMask .|. leaveWindowMask
|
.|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask
|
||||||
grabKeys dpy rootw
|
grabKeys dpy rootw
|
||||||
sync dpy False
|
sync dpy False
|
||||||
|
|
||||||
@@ -171,4 +171,9 @@ handle e@(ConfigureRequestEvent {}) = withDisplay $ \dpy -> do
|
|||||||
, wc_stack_mode = fromIntegral $ ev_detail e }
|
, wc_stack_mode = fromIntegral $ ev_detail e }
|
||||||
io $ sync dpy False
|
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
|
handle _ = return () -- trace (eventName e) -- ignoring
|
||||||
|
@@ -28,6 +28,7 @@ import Control.Monad.Reader
|
|||||||
import Control.Arrow
|
import Control.Arrow
|
||||||
|
|
||||||
import Graphics.X11.Xlib
|
import Graphics.X11.Xlib
|
||||||
|
import Graphics.X11.Xinerama (getScreenInfo)
|
||||||
import Graphics.X11.Xlib.Extras
|
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 :: [Button]
|
||||||
buttonsToGrab = [button1, button2, button3]
|
buttonsToGrab = [button1, button2, button3]
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user