mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-05 22:51:54 -07:00
Fill in missing workspace code
How do we manage workspaces? thunk keeps a list of window lists, corresponding each window stack on each workspace. When you switch views to a different workspace it moves all windows off the screen (2*w) (2*h), and then moves back those in the current list. There's some screen flicker, we could probably be smarter about this.
This commit is contained in:
37
Main.hs
37
Main.hs
@@ -63,7 +63,7 @@ main = do
|
|||||||
{ display = dpy
|
{ display = dpy
|
||||||
, screenWidth = displayWidth dpy dflt
|
, screenWidth = displayWidth dpy dflt
|
||||||
, screenHeight = displayHeight dpy dflt
|
, screenHeight = displayHeight dpy dflt
|
||||||
, workspace = (0,S.fromList (replicate 5 []))
|
, workspace = (0,S.fromList (replicate 5 [])) -- 5 empty workspaces
|
||||||
}
|
}
|
||||||
|
|
||||||
runW initState $ do
|
runW initState $ do
|
||||||
@@ -135,7 +135,7 @@ refresh = do
|
|||||||
d <- gets display
|
d <- gets display
|
||||||
sw <- liftM fromIntegral (gets screenWidth)
|
sw <- liftM fromIntegral (gets screenWidth)
|
||||||
sh <- liftM fromIntegral (gets screenHeight)
|
sh <- liftM fromIntegral (gets screenHeight)
|
||||||
io $ do moveResizeWindow d w 0 0 sw sh -- size
|
io $ do moveResizeWindow d w 0 0 sw sh -- fullscreen
|
||||||
raiseWindow d w
|
raiseWindow d w
|
||||||
|
|
||||||
-- | Modify the current window list with a pure funtion, and refresh
|
-- | Modify the current window list with a pure funtion, and refresh
|
||||||
@@ -152,7 +152,7 @@ manage w = do
|
|||||||
withWindows (nub . (w :))
|
withWindows (nub . (w :))
|
||||||
|
|
||||||
-- | unmanage. A window no longer exists, remove it from the window
|
-- | unmanage. A window no longer exists, remove it from the window
|
||||||
-- list, on whatever workspace
|
-- list, on whatever workspace it is.
|
||||||
unmanage :: Window -> W ()
|
unmanage :: Window -> W ()
|
||||||
unmanage w = do
|
unmanage w = do
|
||||||
(_,wks) <- gets workspace
|
(_,wks) <- gets workspace
|
||||||
@@ -189,23 +189,24 @@ kill = do
|
|||||||
return ()
|
return ()
|
||||||
|
|
||||||
-- | Change the current workspace to workspce at offset 'n-1'.
|
-- | Change the current workspace to workspce at offset 'n-1'.
|
||||||
|
-- Todo: refactor
|
||||||
view :: Int -> W ()
|
view :: Int -> W ()
|
||||||
view n = return ()
|
view n = do
|
||||||
|
|
||||||
--
|
|
||||||
-- So the problem is that I don't quite understand X here.
|
|
||||||
-- The following code will set the right list of windows to be current,
|
|
||||||
-- according to our view of things.
|
|
||||||
--
|
|
||||||
-- We just need to tell X that it is only those in the current window
|
|
||||||
-- list that are indeed visible, and everything else is hidden.
|
|
||||||
--
|
|
||||||
-- In particular, if we switch to a new empty workspace, nothing should
|
|
||||||
-- be visible but the root. So: how do we hide windows?
|
|
||||||
--
|
|
||||||
{- do
|
|
||||||
let m = n-1
|
let m = n-1
|
||||||
modifyWorkspaces $ \old@(_,wks) ->
|
modifyWorkspaces $ \old@(_,wks) ->
|
||||||
if m < S.length wks && m >= 0 then (m,wks) else old
|
if m < S.length wks && m >= 0 then (m,wks) else old
|
||||||
|
|
||||||
|
dpy <- gets display
|
||||||
|
sw <- liftM fromIntegral (gets screenWidth)
|
||||||
|
sh <- liftM fromIntegral (gets screenHeight)
|
||||||
|
(i,wks) <- gets workspace
|
||||||
|
|
||||||
|
-- clear the screen: remove all window stacks
|
||||||
|
forM_ (concat $ F.toList wks) $ \win -> do
|
||||||
|
io $ moveWindow dpy win (2*sw) (2*sh)
|
||||||
|
|
||||||
|
-- expose just the visible stack
|
||||||
|
forM_ (wks `S.index` i) $ \win -> do
|
||||||
|
io $ moveWindow dpy win 0 0
|
||||||
|
|
||||||
refresh
|
refresh
|
||||||
-}
|
|
||||||
|
Reference in New Issue
Block a user