Initial tiling support.

This commit is contained in:
Spencer Janssen 2007-03-20 07:18:12 +00:00
parent 893ea985fa
commit e0584a008d
3 changed files with 50 additions and 23 deletions

44
Main.hs
View File

@ -55,12 +55,16 @@ keys = M.fromList $
, ((modMask, xK_k ), raise LT) , ((modMask, xK_k ), raise LT)
, ((modMask .|. shiftMask, xK_c ), kill) , ((modMask .|. shiftMask, xK_c ), kill)
, ((modMask .|. shiftMask, xK_q ), io $ exitWith ExitSuccess) , ((modMask .|. shiftMask, xK_q ), io $ exitWith ExitSuccess)
, ((modMask, xK_space ), switchLayout)
] ++ ] ++
-- generate keybindings to each workspace: -- generate keybindings to each workspace:
[((m .|. modMask, xK_0 + fromIntegral i), f i) [((m .|. modMask, xK_0 + fromIntegral i), f i)
| i <- [1 .. workspaces] | i <- [1 .. workspaces]
, (f, m) <- [(view, 0), (tag, shiftMask)]] , (f, m) <- [(view, 0), (tag, shiftMask)]]
ratio :: Rational
ratio = 0.5
-- --
-- The main entry point -- The main entry point
-- --
@ -83,6 +87,7 @@ main = do
, wmprotocols = wmprot , wmprotocols = wmprot
, dimensions = (displayWidth dpy dflt, displayHeight dpy dflt) , dimensions = (displayWidth dpy dflt, displayHeight dpy dflt)
, workspace = W.empty workspaces , workspace = W.empty workspaces
, layout = Full
} }
xSetErrorHandler -- in C, I'm too lazy to write the binding xSetErrorHandler -- in C, I'm too lazy to write the binding
@ -224,16 +229,39 @@ refresh = do
ws <- gets workspace ws <- gets workspace
ws2sc <- gets wsOnScreen ws2sc <- gets wsOnScreen
xinesc <- gets xineScreens xinesc <- gets xineScreens
forM_ (M.assocs ws2sc) $ \(n, scn) -> d <- gets display
whenJust (W.peekStack n ws) $ \w -> withDisplay $ \d -> do l <- gets layout
let sc = xinesc !! scn let move w a b c e = io $ moveResizeWindow d w a b c e
io $ do moveResizeWindow d w (rect_x sc) forM_ (M.assocs ws2sc) $ \(n, scn) -> do
(rect_y sc) let sc = xinesc !! scn
(rect_width sc) sx = rect_x sc
(rect_height sc) sy = rect_y sc
raiseWindow d w sw = rect_width sc
sh = rect_height sc
case l of
Full -> whenJust (W.peekStack n ws) $ \w -> do
move w sx sy sw sh
io $ raiseWindow d w
Tile -> case W.index n ws of
[] -> return ()
[w] -> do move w sx sy sw sh; io $ raiseWindow d w
(w:s) -> do
let lw = floor $ fromIntegral sw * ratio
rw = sw - fromIntegral lw
rh = fromIntegral sh `div` fromIntegral (length s)
move w sx sy (fromIntegral lw) sh
zipWithM_ (\i a -> move a (sx + lw) (sy + i * rh) rw (fromIntegral rh)) [0..] s
whenJust (W.peek ws) (io . raiseWindow d) -- this is always Just
whenJust (W.peek ws) setFocus whenJust (W.peek ws) setFocus
-- | switchLayout. Switch to another layout scheme.
switchLayout :: X ()
switchLayout = do
modify (\s -> s {layout = case layout s of
Full -> Tile
Tile -> Full })
refresh
-- | windows. Modify the current window list with a pure function, and refresh -- | windows. Modify the current window list with a pure function, and refresh
windows :: (WorkSpace -> WorkSpace) -> X () windows :: (WorkSpace -> WorkSpace) -> X ()
windows f = do windows f = do

21
TODO
View File

@ -2,6 +2,8 @@
- tiling - tiling
- Refactor to make user configuration reasonable. There should be one - Refactor to make user configuration reasonable. There should be one
file (Config.hs) with all the knobs a user can twist. file (Config.hs) with all the knobs a user can twist.
- Code clean up after tiling and StackSet changes
- Make sure the quickchecks make sense with the new StackSet
- think about the statusbar/multithreading. - think about the statusbar/multithreading.
Three shared TVars: Three shared TVars:
@ -21,16 +23,9 @@
redraws whenever it finds a change. redraws whenever it finds a change.
- tiling: - tiling:
- StackSet currently holds one stack, it needs to hold two. One stack - Layout calculation: the current algorithm is crude, windows overlap
contains focus info, the top of that stack is always the window that - make focus remain between workspace switches
is in the foreground and has focus. - change focus in the StackSet structure on EnterNotify
- operations to change window order (like dwm's mod+enter)
The other stack keeps track of window layout order. In tiling mode, - add 'ratio' to XState, add bindings to change it on the fly
the first window in the stack is in the master area. In both tiling - borders (low priority, maybe wait until 0.2)
and full screen mode, window cycling follows the order in this stack.
- Layout calculation: a simple function from number of windows to list
of coordinates.
- state components, key combos, etc. for changing the current layout
scheme

View File

@ -15,8 +15,8 @@
-- --
module XMonad ( module XMonad (
X, WorkSpace, XState(..), runX, X, WorkSpace, XState(..), Layout(..),
io, withDisplay, isRoot, runX, io, withDisplay, isRoot,
spawn, trace, whenJust spawn, trace, whenJust
) where ) where
@ -43,10 +43,14 @@ data XState = XState
, wmprotocols :: {-# UNPACK #-} !Atom , wmprotocols :: {-# UNPACK #-} !Atom
, dimensions :: {-# UNPACK #-} !(Int,Int) , dimensions :: {-# UNPACK #-} !(Int,Int)
, workspace :: {-# UNPACK #-} !WorkSpace -- ^ workspace list , workspace :: {-# UNPACK #-} !WorkSpace -- ^ workspace list
, layout :: {-# UNPACK #-} !Layout
} }
type WorkSpace = StackSet Window type WorkSpace = StackSet Window
-- | The different layout modes
data Layout = Full | Tile
-- | The X monad, a StateT transformer over IO encapuslating the window -- | The X monad, a StateT transformer over IO encapuslating the window
-- manager state -- manager state
newtype X a = X (StateT XState IO a) newtype X a = X (StateT XState IO a)