mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
clean up Layout.hs, not entirely happy about the impure layouts.
This commit is contained in:
parent
04ee55c3ca
commit
f7686746c6
194
XMonad/Layout.hs
194
XMonad/Layout.hs
@ -32,9 +32,110 @@ import Control.Arrow ((***), second)
|
||||
import Control.Monad
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- | Builtin basic layout algorithms:
|
||||
--
|
||||
-- > fullscreen mode
|
||||
-- > tall mode
|
||||
--
|
||||
-- The latter algorithms support the following operations:
|
||||
--
|
||||
-- > Shrink
|
||||
-- > Expand
|
||||
--
|
||||
data Resize = Shrink | Expand deriving Typeable
|
||||
|
||||
-- | You can also increase the number of clients in the master pane
|
||||
data IncMasterN = IncMasterN Int deriving Typeable
|
||||
|
||||
instance Message Resize
|
||||
instance Message IncMasterN
|
||||
|
||||
-- | Simple fullscreen mode, just render all windows fullscreen.
|
||||
data Full a = Full deriving (Show, Read)
|
||||
|
||||
instance LayoutClass Full a
|
||||
|
||||
-- | The builtin tiling mode of xmonad, and its operations.
|
||||
data Tall a = Tall Int Rational Rational deriving (Show, Read)
|
||||
-- TODO should be capped [0..1] ..
|
||||
|
||||
-- a nice pure layout, lots of properties for the layout, and its messages, in Properties.hs
|
||||
instance LayoutClass Tall a where
|
||||
pureLayout (Tall nmaster _ frac) r s = zip ws rs
|
||||
where ws = W.integrate s
|
||||
rs = tile frac r nmaster (length ws)
|
||||
|
||||
pureMessage (Tall nmaster delta frac) m =
|
||||
msum [fmap resize (fromMessage m)
|
||||
,fmap incmastern (fromMessage m)]
|
||||
|
||||
where resize Shrink = Tall nmaster delta (max 0 $ frac-delta)
|
||||
resize Expand = Tall nmaster delta (min 1 $ frac+delta)
|
||||
incmastern (IncMasterN d) = Tall (max 0 (nmaster+d)) delta frac
|
||||
|
||||
description _ = "Tall"
|
||||
|
||||
-- | tile. Compute the positions for windows using the default 2 pane tiling algorithm.
|
||||
--
|
||||
-- The screen is divided (currently) into two panes. all clients are
|
||||
-- then partioned between these two panes. one pane, the `master', by
|
||||
-- convention has the least number of windows in it (by default, 1).
|
||||
-- the variable `nmaster' controls how many windows are rendered in the
|
||||
-- master pane.
|
||||
--
|
||||
-- `delta' specifies the ratio of the screen to resize by.
|
||||
--
|
||||
-- 'frac' specifies what proportion of the screen to devote to the
|
||||
-- master area.
|
||||
--
|
||||
tile :: Rational -> Rectangle -> Int -> Int -> [Rectangle]
|
||||
tile f r nmaster n = if n <= nmaster || nmaster == 0
|
||||
then splitVertically n r
|
||||
else splitVertically nmaster r1 ++ splitVertically (n-nmaster) r2 -- two columns
|
||||
where (r1,r2) = splitHorizontallyBy f r
|
||||
|
||||
--
|
||||
-- Divide the screen vertically into n subrectangles
|
||||
--
|
||||
splitVertically, splitHorizontally :: Int -> Rectangle -> [Rectangle]
|
||||
splitVertically n r | n < 2 = [r]
|
||||
splitVertically n (Rectangle sx sy sw sh) = Rectangle sx sy sw smallh :
|
||||
splitVertically (n-1) (Rectangle sx (sy+fromIntegral smallh) sw (sh-smallh))
|
||||
where smallh = sh `div` fromIntegral n --hmm, this is a fold or map.
|
||||
|
||||
-- Not used in the core, but exported
|
||||
splitHorizontally n = map mirrorRect . splitVertically n . mirrorRect
|
||||
|
||||
-- Divide the screen into two rectangles, using a rational to specify the ratio
|
||||
splitHorizontallyBy, splitVerticallyBy :: RealFrac r => r -> Rectangle -> (Rectangle, Rectangle)
|
||||
splitHorizontallyBy f (Rectangle sx sy sw sh) =
|
||||
( Rectangle sx sy leftw sh
|
||||
, Rectangle (sx + fromIntegral leftw) sy (sw-fromIntegral leftw) sh)
|
||||
where leftw = floor $ fromIntegral sw * f
|
||||
|
||||
-- Not used in the core, but exported
|
||||
splitVerticallyBy f = (mirrorRect *** mirrorRect) . splitHorizontallyBy f . mirrorRect
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- | Mirror a layout, compute its 90 degree rotated form.
|
||||
|
||||
-- | Mirror a layout, compute its 90 degree rotated form.
|
||||
data Mirror l a = Mirror (l a) deriving (Show, Read)
|
||||
|
||||
instance LayoutClass l a => LayoutClass (Mirror l) a where
|
||||
runLayout (W.Workspace i (Mirror l) ms) r = (map (second mirrorRect) *** fmap Mirror)
|
||||
`fmap` runLayout (W.Workspace i l ms) (mirrorRect r)
|
||||
handleMessage (Mirror l) = fmap (fmap Mirror) . handleMessage l
|
||||
description (Mirror l) = "Mirror "++ description l
|
||||
|
||||
-- | Mirror a rectangle
|
||||
mirrorRect :: Rectangle -> Rectangle
|
||||
mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- LayoutClass selection manager
|
||||
-- Layouts that transition between other layouts
|
||||
|
||||
-- | A layout that allows users to switch between various layout options.
|
||||
|
||||
@ -87,96 +188,3 @@ instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
|
||||
-- The default cases for left and right:
|
||||
handleMessage (SLeft r l) m = fmap (fmap $ SLeft r) $ handleMessage l m
|
||||
handleMessage (SRight l r) m = fmap (fmap $ SRight l) $ handleMessage r m
|
||||
|
||||
--
|
||||
-- | Builtin layout algorithms:
|
||||
--
|
||||
-- > fullscreen mode
|
||||
-- > tall mode
|
||||
--
|
||||
-- The latter algorithms support the following operations:
|
||||
--
|
||||
-- > Shrink
|
||||
-- > Expand
|
||||
--
|
||||
data Resize = Shrink | Expand deriving Typeable
|
||||
|
||||
-- | You can also increase the number of clients in the master pane
|
||||
data IncMasterN = IncMasterN Int deriving Typeable
|
||||
|
||||
instance Message Resize
|
||||
instance Message IncMasterN
|
||||
|
||||
-- | Simple fullscreen mode, just render all windows fullscreen.
|
||||
data Full a = Full deriving (Show, Read)
|
||||
|
||||
instance LayoutClass Full a
|
||||
|
||||
-- | The inbuilt tiling mode of xmonad, and its operations.
|
||||
data Tall a = Tall Int Rational Rational deriving (Show, Read)
|
||||
|
||||
instance LayoutClass Tall a where
|
||||
pureLayout (Tall nmaster _ frac) r s = zip ws rs
|
||||
where ws = W.integrate s
|
||||
rs = tile frac r nmaster (length ws)
|
||||
|
||||
pureMessage (Tall nmaster delta frac) m = msum [fmap resize (fromMessage m)
|
||||
,fmap incmastern (fromMessage m)]
|
||||
where resize Shrink = Tall nmaster delta (max 0 $ frac-delta)
|
||||
resize Expand = Tall nmaster delta (min 1 $ frac+delta)
|
||||
incmastern (IncMasterN d) = Tall (max 0 (nmaster+d)) delta frac
|
||||
description _ = "Tall"
|
||||
|
||||
-- | Mirror a rectangle
|
||||
mirrorRect :: Rectangle -> Rectangle
|
||||
mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
||||
|
||||
-- | Mirror a layout, compute its 90 degree rotated form.
|
||||
data Mirror l a = Mirror (l a) deriving (Show, Read)
|
||||
|
||||
instance LayoutClass l a => LayoutClass (Mirror l) a where
|
||||
runLayout (W.Workspace i (Mirror l) ms) r = (map (second mirrorRect) *** fmap Mirror)
|
||||
`fmap` runLayout (W.Workspace i l ms) (mirrorRect r)
|
||||
handleMessage (Mirror l) = fmap (fmap Mirror) . handleMessage l
|
||||
description (Mirror l) = "Mirror "++ description l
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
||||
-- | tile. Compute the positions for windows using the default 2 pane tiling algorithm.
|
||||
--
|
||||
-- The screen is divided (currently) into two panes. all clients are
|
||||
-- then partioned between these two panes. one pane, the `master', by
|
||||
-- convention has the least number of windows in it (by default, 1).
|
||||
-- the variable `nmaster' controls how many windows are rendered in the
|
||||
-- master pane.
|
||||
--
|
||||
-- `delta' specifies the ratio of the screen to resize by.
|
||||
--
|
||||
-- 'frac' specifies what proportion of the screen to devote to the
|
||||
-- master area.
|
||||
--
|
||||
tile :: Rational -> Rectangle -> Int -> Int -> [Rectangle]
|
||||
tile f r nmaster n = if n <= nmaster || nmaster == 0
|
||||
then splitVertically n r
|
||||
else splitVertically nmaster r1 ++ splitVertically (n-nmaster) r2 -- two columns
|
||||
where (r1,r2) = splitHorizontallyBy f r
|
||||
|
||||
--
|
||||
-- Divide the screen vertically into n subrectangles
|
||||
--
|
||||
splitVertically, splitHorizontally :: Int -> Rectangle -> [Rectangle]
|
||||
splitVertically n r | n < 2 = [r]
|
||||
splitVertically n (Rectangle sx sy sw sh) = Rectangle sx sy sw smallh :
|
||||
splitVertically (n-1) (Rectangle sx (sy+fromIntegral smallh) sw (sh-smallh))
|
||||
where smallh = sh `div` fromIntegral n --hmm, this is a fold or map.
|
||||
|
||||
splitHorizontally n = map mirrorRect . splitVertically n . mirrorRect
|
||||
|
||||
-- Divide the screen into two rectangles, using a rational to specify the ratio
|
||||
splitHorizontallyBy, splitVerticallyBy :: RealFrac r => r -> Rectangle -> (Rectangle, Rectangle)
|
||||
splitHorizontallyBy f (Rectangle sx sy sw sh) =
|
||||
( Rectangle sx sy leftw sh
|
||||
, Rectangle (sx + fromIntegral leftw) sy (sw-fromIntegral leftw) sh)
|
||||
where leftw = floor $ fromIntegral sw * f
|
||||
|
||||
splitVerticallyBy f = (mirrorRect *** mirrorRect) . splitHorizontallyBy f . mirrorRect
|
||||
|
Loading…
x
Reference in New Issue
Block a user