Cleaned up layout a little bit

This commit is contained in:
hughes
2007-04-01 02:36:39 +00:00
parent cf91d8aa53
commit 0bb46e09cb

View File

@@ -41,8 +41,10 @@ refresh = do
-- runRects draws the windows, figuring out their rectangles. -- runRects draws the windows, figuring out their rectangles.
-- The code here is for a horizontal split, and tr is possibly -- The code here is for a horizontal split, and tr is possibly
-- used to convert to the vertical case. -- used to convert to the vertical case. The comments
runRects :: Rectangle -> (Rectangle -> Rectangle) -> (Rational -> Disposition -> Disposition) -- speak in terms of the horizontal case.
runRects :: Rectangle -> (Rectangle -> Rectangle)
-> (Rational -> Disposition -> Disposition)
-> (Disposition -> Rational) -> Rational -> [Window] -> X () -> (Disposition -> Rational) -> Rational -> [Window] -> X ()
runRects _ _ _ _ _ [] = return () -- impossible runRects _ _ _ _ _ [] = return () -- impossible
runRects (Rectangle sx sy sw sh) tr dfix fracFn tf (w:s) = do runRects (Rectangle sx sy sw sh) tr dfix fracFn tf (w:s) = do
@@ -83,12 +85,25 @@ refresh = do
[] -> return () [] -> return ()
[w] -> fullWindow w [w] -> fullWindow w
s -> case l of s -> case l of
Horz -> runRects sc id (\r dp -> dp {horzFrac = r}) horzFrac (horzTileFrac fl) s Horz -> (runRects sc
Vert -> runRects (flipRect sc) flipRect (\r dp -> dp {vertFrac = r}) vertFrac (vertTileFrac fl) s id
_ -> error "Operations.refresh: the absurdly impossible happened. Please complain about this." (\r dp -> dp {horzFrac = r})
horzFrac
(horzTileFrac fl)
s)
Vert -> (runRects (flipRect sc)
flipRect
(\r dp -> dp {vertFrac = r})
vertFrac
(vertTileFrac fl)
s)
_ -> error "Operations.refresh: the absurdly \
\impossible happened. Please \
\complain about this."
whenJust (W.peek ws) setFocus whenJust (W.peek ws) setFocus
-- | switchLayout. Switch to another layout scheme. Switches the current workspace. -- | switchLayout. Switch to another layout scheme. Switches the
-- current workspace.
switchLayout :: X () switchLayout :: X ()
switchLayout = layout $ \fl -> fl { layoutType = rot (layoutType fl) } switchLayout = layout $ \fl -> fl { layoutType = rot (layoutType fl) }
@@ -97,7 +112,9 @@ changeVert :: Rational -> X ()
changeVert delta = do changeVert delta = do
l <- gets (layoutType . currentDesc) l <- gets (layoutType . currentDesc)
case l of case l of
Vert -> layout $ \d -> d {vertTileFrac = min 1 $ max 0 $ vertTileFrac d + delta} Vert -> layout $ \d -> d {vertTileFrac = min 1 $
max 0 $
vertTileFrac d + delta}
_ -> return () _ -> return ()
-- | changeHorz. Changes the horizontal split, if it's visible. -- | changeHorz. Changes the horizontal split, if it's visible.
@@ -105,7 +122,9 @@ changeHorz :: Rational -> X ()
changeHorz delta = do changeHorz delta = do
l <- gets (layoutType . currentDesc) l <- gets (layoutType . currentDesc)
case l of case l of
Horz -> layout $ \d -> d {horzTileFrac = min 1 $ max 0 $ horzTileFrac d + delta} Horz -> layout $ \d -> d {horzTileFrac = min 1 $
max 0 $
horzTileFrac d + delta}
_ -> return () _ -> return ()
-- | changeSize. Changes the size of the window, except in Full mode, with the -- | changeSize. Changes the size of the window, except in Full mode, with the
@@ -114,14 +133,17 @@ changeSize :: Rational -> Rational -> X ()
changeSize delta mini = do changeSize delta mini = do
l <- gets (layoutType . currentDesc) l <- gets (layoutType . currentDesc)
mw <- gets (W.peek . workspace) mw <- gets (W.peek . workspace)
whenJust mw $ \w -> do whenJust mw $ \w -> do -- This is always Just.
case l of -- This is always Just. case l of
Full -> return () Full -> return ()
Horz -> disposeW w $ \d -> d {horzFrac = max mini $ horzFrac d + delta} Horz -> disposeW w $ \d -> d {horzFrac = max mini $
Vert -> disposeW w $ \d -> d {vertFrac = max mini $ vertFrac d + delta} -- hrm... horzFrac d + delta}
Vert -> disposeW w $ \d -> d {vertFrac = max mini $
vertFrac d + delta} -- hrm...
refresh refresh
-- | layout. Modify the current workspace's layout with a pure function and refresh. -- | layout. Modify the current workspace's layout with a pure
-- function and refresh.
layout :: (LayoutDesc -> LayoutDesc) -> X () layout :: (LayoutDesc -> LayoutDesc) -> X ()
layout f = do layout f = do
modify $ \s -> modify $ \s ->