mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-01 12:41:53 -07:00
changed type of getScreenInfo in Graphics.X11.Xinerama
This commit is contained in:
10
Main.hs
10
Main.hs
@@ -77,7 +77,7 @@ main = do
|
|||||||
{ display = dpy
|
{ display = dpy
|
||||||
, screen = dflt
|
, screen = dflt
|
||||||
, xineScreens = xinesc
|
, xineScreens = xinesc
|
||||||
, wsOnScreen = M.fromList $ map ((\n -> (n,n)) . fromIntegral . xsi_screen_number) xinesc
|
, wsOnScreen = M.fromList $ map (\n -> (n,n)) [0..((length xinesc)-1)]
|
||||||
, theRoot = rootw
|
, theRoot = rootw
|
||||||
, wmdelete = wmdelt
|
, wmdelete = wmdelt
|
||||||
, wmprotocols = wmprot
|
, wmprotocols = wmprot
|
||||||
@@ -227,10 +227,10 @@ refresh = do
|
|||||||
forM_ (M.assocs ws2sc) $ \(n, scn) ->
|
forM_ (M.assocs ws2sc) $ \(n, scn) ->
|
||||||
whenJust (W.peekStack n ws) $ \w -> withDisplay $ \d -> do
|
whenJust (W.peekStack n ws) $ \w -> withDisplay $ \d -> do
|
||||||
let sc = xinesc !! scn
|
let sc = xinesc !! scn
|
||||||
io $ do moveResizeWindow d w (fromIntegral $ xsi_x_org sc)
|
io $ do moveResizeWindow d w (rect_x sc)
|
||||||
(fromIntegral $ xsi_y_org sc)
|
(rect_y sc)
|
||||||
(fromIntegral $ xsi_width sc)
|
(rect_width sc)
|
||||||
(fromIntegral $ xsi_height sc) -- fullscreen
|
(rect_height sc)
|
||||||
raiseWindow d w
|
raiseWindow d w
|
||||||
whenJust (W.peek ws) setFocus
|
whenJust (W.peek ws) setFocus
|
||||||
|
|
||||||
|
@@ -28,8 +28,6 @@ import System.Posix.Process (executeFile, forkProcess, getProcessStatus)
|
|||||||
import System.Exit
|
import System.Exit
|
||||||
import Graphics.X11.Xlib
|
import Graphics.X11.Xlib
|
||||||
|
|
||||||
import Graphics.X11.Xinerama
|
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
|
||||||
-- | XState, the window manager state.
|
-- | XState, the window manager state.
|
||||||
@@ -37,7 +35,7 @@ import qualified Data.Map as M
|
|||||||
data XState = XState
|
data XState = XState
|
||||||
{ display :: Display
|
{ display :: Display
|
||||||
, screen :: {-# UNPACK #-} !ScreenNumber
|
, screen :: {-# UNPACK #-} !ScreenNumber
|
||||||
, xineScreens :: {-# UNPACK #-} ![XineramaScreenInfo]
|
, xineScreens :: {-# UNPACK #-} ![Rectangle]
|
||||||
-- a mapping of workspaces to xinerama screen numbers
|
-- a mapping of workspaces to xinerama screen numbers
|
||||||
, wsOnScreen :: {-# UNPACK #-} !(M.Map Int Int)
|
, wsOnScreen :: {-# UNPACK #-} !(M.Map Int Int)
|
||||||
, theRoot :: {-# UNPACK #-} !Window
|
, theRoot :: {-# UNPACK #-} !Window
|
||||||
|
Reference in New Issue
Block a user