mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-01 12:41:53 -07:00
Make screen info dynamic: first step to supporting randr
This commit is contained in:
8
Main.hs
8
Main.hs
@@ -45,19 +45,19 @@ main = do
|
|||||||
let safeLayouts = case defaultLayouts of [] -> (full, []); (x:xs) -> (x, xs)
|
let safeLayouts = case defaultLayouts of [] -> (full, []); (x:xs) -> (x, xs)
|
||||||
cf = XConf
|
cf = XConf
|
||||||
{ display = dpy
|
{ display = dpy
|
||||||
, xineScreens = xinesc
|
|
||||||
, theRoot = rootw
|
, theRoot = rootw
|
||||||
, wmdelete = wmdelt
|
, wmdelete = wmdelt
|
||||||
, wmprotocols = wmprot
|
, wmprotocols = wmprot
|
||||||
-- fromIntegral needed for X11 versions that use Int instead of CInt.
|
-- fromIntegral needed for X11 versions that use Int instead of CInt.
|
||||||
, dimensions = (fromIntegral (displayWidth dpy dflt),
|
|
||||||
fromIntegral (displayHeight dpy dflt))
|
|
||||||
, normalBorder = nbc
|
, normalBorder = nbc
|
||||||
, focusedBorder = fbc
|
, focusedBorder = fbc
|
||||||
}
|
}
|
||||||
st = XState
|
st = XState
|
||||||
{ windowset = new (fromIntegral workspaces) (fromIntegral $ length xinesc)
|
{ 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
|
xSetErrorHandler -- in C, I'm too lazy to write the binding: dons
|
||||||
|
|
||||||
|
@@ -100,7 +100,7 @@ windows f = modify (\s -> s { windowset = f (windowset s) }) >> refresh
|
|||||||
-- | hide. Hide a window by moving it off screen.
|
-- | hide. Hide a window by moving it off screen.
|
||||||
hide :: Window -> X ()
|
hide :: Window -> X ()
|
||||||
hide w = withDisplay $ \d -> do
|
hide w = withDisplay $ \d -> do
|
||||||
(sw,sh) <- asks dimensions
|
(sw,sh) <- gets dimensions
|
||||||
io $ moveWindow d w (2*fromIntegral sw) (2*fromIntegral sh)
|
io $ moveWindow d w (2*fromIntegral sw) (2*fromIntegral sh)
|
||||||
|
|
||||||
-- | refresh. Render the currently visible workspaces, as determined by
|
-- | refresh. Render the currently visible workspaces, as determined by
|
||||||
@@ -111,8 +111,8 @@ hide w = withDisplay $ \d -> do
|
|||||||
--
|
--
|
||||||
refresh :: X ()
|
refresh :: X ()
|
||||||
refresh = do
|
refresh = do
|
||||||
XState { windowset = ws, layouts = fls } <- get
|
XState { windowset = ws, layouts = fls, xineScreens = xinesc } <- get
|
||||||
XConf { xineScreens = xinesc, display = d } <- ask
|
d <- asks display
|
||||||
|
|
||||||
-- for each workspace, layout the currently visible workspaces
|
-- for each workspace, layout the currently visible workspaces
|
||||||
(`mapM_` (W.current ws : W.visible ws)) $ \w -> do
|
(`mapM_` (W.current ws : W.visible ws)) $ \w -> do
|
||||||
|
@@ -39,6 +39,9 @@ import qualified Data.Map as M
|
|||||||
-- Just the display, width, height and a window list
|
-- Just the display, width, height and a window list
|
||||||
data XState = XState
|
data XState = XState
|
||||||
{ windowset :: !WindowSet -- ^ workspace list
|
{ 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])) }
|
, layouts :: !(M.Map WorkspaceId (Layout, [Layout])) }
|
||||||
-- ^ mapping of workspaces to descriptions of their layouts
|
-- ^ mapping of workspaces to descriptions of their layouts
|
||||||
|
|
||||||
@@ -48,10 +51,7 @@ data XConf = XConf
|
|||||||
, theRoot :: !Window -- ^ the root window
|
, theRoot :: !Window -- ^ the root window
|
||||||
, wmdelete :: !Atom -- ^ window deletion atom
|
, wmdelete :: !Atom -- ^ window deletion atom
|
||||||
, wmprotocols :: !Atom -- ^ wm protocols 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
|
, normalBorder :: !Color -- ^ border color of unfocused windows
|
||||||
, focusedBorder :: !Color } -- ^ border color of the focused window
|
, focusedBorder :: !Color } -- ^ border color of the focused window
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user