{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module XMonad.Layout.MultiDishes (
MultiDishes (..)
) where
import XMonad
import XMonad.StackSet (integrate)
import Control.Monad (ap)
data MultiDishes a = MultiDishes Int Int Rational deriving (Show, Read)
instance LayoutClass MultiDishes a where
pureLayout (MultiDishes nmaster dishesPerStack h) r =
ap zip (multiDishes h r nmaster dishesPerStack . length) . integrate
pureMessage (MultiDishes nmaster dishesPerStack h) m = fmap incmastern (fromMessage m)
where incmastern (IncMasterN d) = MultiDishes (max 0 (nmaster+d)) dishesPerStack h
multiDishes :: Rational -> Rectangle -> Int -> Int -> Int -> [Rectangle]
multiDishes h s nmaster dishesPerStack n = if n <= nmaster
then splitHorizontally n s
else ws
where
(filledDishStackCount, remainder) =
(n - nmaster) `quotRem` (max 1 dishesPerStack)
(firstDepth, dishStackCount) =
if remainder == 0 then
(dishesPerStack, filledDishStackCount)
else
(remainder, filledDishStackCount + 1)
(masterRect, dishesRect) =
splitVerticallyBy (1 - (fromIntegral dishStackCount) * h) s
dishStackRects =
splitVertically dishStackCount dishesRect
allDishRects = case dishStackRects of
(firstStack:bottomDishStacks) ->
splitHorizontally firstDepth firstStack ++ (bottomDishStacks >>= splitHorizontally dishesPerStack)
[] -> []
ws =
splitHorizontally nmaster masterRect ++ allDishRects