aboutsummaryrefslogtreecommitdiffstats
path: root/W.hs
diff options
context:
space:
mode:
authorDon Stewart <dons@cse.unsw.edu.au>2007-03-07 12:12:47 +0100
committerDon Stewart <dons@cse.unsw.edu.au>2007-03-07 12:12:47 +0100
commita9fb1d440799450401bd0f1fd0f9bf93c6b318b7 (patch)
tree93d73ab682b461b7a9d4801ef53fdb857a3c1d17 /W.hs
parent8efa021a8b3db0f0299adbfcc03d601eb86812fa (diff)
downloadxmonad-a9fb1d440799450401bd0f1fd0f9bf93c6b318b7.tar.gz
xmonad-a9fb1d440799450401bd0f1fd0f9bf93c6b318b7.tar.xz
xmonad-a9fb1d440799450401bd0f1fd0f9bf93c6b318b7.zip
Add support for multiple workspaces
Everything is in place for multiple workspaces, bar one thing: the view function. It updates thunk's idea of the current visible windows, but I don't know how to tell X to hide the current set, and instead treat the new window list as the only ones visible. See notes for 'view' at bottom of Main.hs. If we can, say, switch to a new workspace, which is empty, 'refresh' should spot this only display the root window. darcs-hash:20070307111247-9c5c1-eb211e587bc65d7fbc9dfec1ea38364691ef2a67.gz
Diffstat (limited to 'W.hs')
-rw-r--r--W.hs35
1 files changed, 14 insertions, 21 deletions
diff --git a/W.hs b/W.hs
index d46dc7a..93d8ea6 100644
--- a/W.hs
+++ b/W.hs
@@ -19,6 +19,7 @@ module W where
import Control.Monad.State
import System.IO
import Graphics.X11.Xlib (Display,Window)
+import qualified Data.Sequence as S
-- | WState, the window manager state.
-- Just the display, width, height and a window list
@@ -26,18 +27,11 @@ data WState = WState
{ display :: Display
, screenWidth :: !Int
, screenHeight :: !Int
- , windows :: !Windows
+ , workspace :: !WorkSpaces -- ^ workspace list
}
---
--- Multithreaded issues:
---
--- We'll want a status bar, it will probably read from stdin
--- but will thus need to run in its own thread, and modify its status
--- bar window
---
-
-type Windows = [Window]
+type WorkSpaces = (Int, S.Seq Windows)
+type Windows = [Window]
-- | The W monad, a StateT transformer over IO encapuslating the window
-- manager state
@@ -67,9 +61,13 @@ trace msg = io $ do
-- ---------------------------------------------------------------------
-- Getting at the window manager state
+-- | Modify the workspace list
+modifyWorkspaces :: (WorkSpaces -> WorkSpaces) -> W ()
+modifyWorkspaces f = modify $ \s -> s { workspace = f (workspace s) }
+
-- | Modify the current window list
-modifyWindows :: (Windows -> Windows) -> W ()
-modifyWindows f = modify $ \s -> s {windows = f (windows s)}
+modifyWindows :: (Windows -> Windows) -> W ()
+modifyWindows f = modifyWorkspaces $ \(i,wk) -> (i, S.adjust f i wk)
-- ---------------------------------------------------------------------
-- Generic utilities
@@ -80,16 +78,11 @@ forever a = a >> forever a
-- | Rotate a list by 'n' elements.
--
--- for xs = [5..8] ++ [1..4]
---
--- rotate 0
--- [5,6,7,8,1,2,3,4]
---
--- rotate 1
--- [6,7,8,1,2,3,4,5]
+-- rotate 0 --> [5,6,7,8,1,2,3,4]
+-- rotate 1 --> [6,7,8,1,2,3,4,5]
+-- rotate (-1) --> [4,5,6,7,8,1,2,3]
--
--- rotate (-1)
--- [4,5,6,7,8,1,2,3]
+-- where xs = [5..8] ++ [1..4]
--
rotate :: Int -> [a] -> [a]
rotate n xs = take l . drop offset . cycle $ xs