[Xmonad] layout combinators
Joe Thornber
joe.thornber at gmail.com
Wed May 30 16:21:56 EDT 2007
I'm not going to get time to look at this again until the weekend, so
I thought I'd post what I had for people to muse over.
Combining splitters rather than rectangles is a neat idea (I hope).
However I think we do need a combinator that merges rectangles back
together again. Consider a layout consisting of three columns, where
the middle column is twice the width of the out ones. To do this I'd
like to create four columns and then merge together the two middle
columns:
eg, merge [1..2] . hcat . replicate 4 $ unit
I really don't like passing indexes to merge, so if anyone can come up
with a nicer way I'd be very interested.
For now, this approach ignores the whole issue of scaling factors
given by the user to get the window sizes exactly as they want. But I
do wonder if that can be done as a seperate distortion pass over the
resultant rects anyway.
- Joe
--
-- Layout combinators
--
type Splitter = Rect -> [Rect]
unit :: Splitter
unit = (: [])
catDir :: Direction -> [Splitter] -> Splitter
catDir dir splitters = concat .
zipWith ($) splitters .
divideMany (length splitters) dir
hcat, vcat :: [Splitter] -> Splitter
hcat splitters = catDir East splitters
vcat splitters = catDir South splitters
hjoin, vjoin :: Splitter -> Splitter -> Splitter
vjoin left right = vcat [left, right]
hjoin left right = hcat [left, right]
mkLayout :: (Int -> Splitter) -> Layout
mkLayout s = Layout { doLayout = l, modifyLayout = const Nothing}
where
l sc ws = return . zip ws . map fromRect . s (length ws) . toRect $ sc
--
-- Layouts
--
ejtTall :: Layout
ejtTall = mkLayout tall'
where
tall' 1 = unit
tall' n = unit `hjoin` (vcat . replicate (n - 1) $ unit)
ejtWide :: Layout
ejtWide = mkLayout wide'
where
wide' 1 = unit
wide' n = unit `vjoin` (hcat . replicate (n - 1) $ unit)
ejtColumn :: Layout
ejtColumn = mkLayout $ \_ -> hcat . replicate 4 $ (unit 'vjoin' unit)
More information about the Xmonad
mailing list