Make screen info dynamic: first step to supporting randr

This commit is contained in:
Spencer Janssen
2007-05-21 15:27:59 +00:00
parent b1345e037c
commit b59d4d1dc0
3 changed files with 10 additions and 10 deletions

View File

@@ -45,19 +45,19 @@ main = do
let safeLayouts = case defaultLayouts of [] -> (full, []); (x:xs) -> (x, xs)
cf = XConf
{ display = dpy
, xineScreens = xinesc
, theRoot = rootw
, wmdelete = wmdelt
, wmprotocols = wmprot
-- fromIntegral needed for X11 versions that use Int instead of CInt.
, dimensions = (fromIntegral (displayWidth dpy dflt),
fromIntegral (displayHeight dpy dflt))
, normalBorder = nbc
, focusedBorder = fbc
}
st = XState
{ windowset = new (fromIntegral workspaces) (fromIntegral $ length xinesc)
, layouts = M.fromList [(w, safeLayouts) | w <- [0 .. W workspaces - 1]] }
, layouts = M.fromList [(w, safeLayouts) | w <- [0 .. W workspaces - 1]]
, xineScreens = xinesc
, dimensions = (fromIntegral (displayWidth dpy dflt),
fromIntegral (displayHeight dpy dflt)) }
xSetErrorHandler -- in C, I'm too lazy to write the binding: dons

View File

@@ -100,7 +100,7 @@ windows f = modify (\s -> s { windowset = f (windowset s) }) >> refresh
-- | hide. Hide a window by moving it off screen.
hide :: Window -> X ()
hide w = withDisplay $ \d -> do
(sw,sh) <- asks dimensions
(sw,sh) <- gets dimensions
io $ moveWindow d w (2*fromIntegral sw) (2*fromIntegral sh)
-- | refresh. Render the currently visible workspaces, as determined by
@@ -111,8 +111,8 @@ hide w = withDisplay $ \d -> do
--
refresh :: X ()
refresh = do
XState { windowset = ws, layouts = fls } <- get
XConf { xineScreens = xinesc, display = d } <- ask
XState { windowset = ws, layouts = fls, xineScreens = xinesc } <- get
d <- asks display
-- for each workspace, layout the currently visible workspaces
(`mapM_` (W.current ws : W.visible ws)) $ \w -> do

View File

@@ -39,6 +39,9 @@ import qualified Data.Map as M
-- Just the display, width, height and a window list
data XState = XState
{ windowset :: !WindowSet -- ^ workspace list
, xineScreens :: ![Rectangle] -- ^ dimensions of each screen
, dimensions :: !(Int,Int) -- ^ dimensions of the screen,
-- used for hiding windows
, layouts :: !(M.Map WorkspaceId (Layout, [Layout])) }
-- ^ mapping of workspaces to descriptions of their layouts
@@ -48,10 +51,7 @@ data XConf = XConf
, theRoot :: !Window -- ^ the root window
, wmdelete :: !Atom -- ^ window deletion atom
, wmprotocols :: !Atom -- ^ wm protocols atom
, dimensions :: !(Int,Int) -- ^ dimensions of the screen,
-- used for hiding windows
, xineScreens :: ![Rectangle] -- ^ dimensions of each screen
, normalBorder :: !Color -- ^ border color of unfocused windows
, focusedBorder :: !Color } -- ^ border color of the focused window