{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances, FlexibleInstances, FlexibleContexts #-}
module XMonad.Layout.Drawer
(
simpleDrawer
, drawer
, onLeft, onTop, onRight, onBottom
, module XMonad.Util.WindowProperties
, Drawer, Reflected
) where
import XMonad
import XMonad.Layout.LayoutModifier
import XMonad.Util.WindowProperties
import XMonad.StackSet as S
import XMonad.Layout.Reflect
data Drawer l a = Drawer Rational Rational Property (l a)
deriving (Read, Show)
partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a], [a])
partitionM _ [] = return ([], [])
partitionM f (x:xs) = do
b <- f x
(ys, zs) <- partitionM f xs
return $ if b
then (x:ys, zs)
else (ys, x:zs)
instance (LayoutClass l Window, Read (l Window)) => LayoutModifier (Drawer l) Window where
modifyLayout (Drawer rs rb p l) ws rect =
case stack ws of
Nothing -> runLayout ws rect
Just stk@(Stack { up=up_, down=down_, S.focus=w }) -> do
(upD, upM) <- partitionM (hasProperty p) up_
(downD, downM) <- partitionM (hasProperty p) down_
b <- hasProperty p w
focusedWindow <- gets (fmap S.focus . stack . workspace . current . windowset)
let rectD = if b && Just w == focusedWindow then rectB else rectS
let (stackD, stackM) = if b
then ( Just $ stk { up=upD, down=downD }
, mkStack upM downM )
else ( mkStack upD downD
, Just $ stk { up=upM, down=downM } )
(winsD, _) <- runLayout (ws { layout=l, stack=stackD }) rectD
(winsM, u') <- runLayout (ws { stack=stackM }) rectM
return (winsD ++ winsM, u')
where
mkStack [] [] = Nothing
mkStack xs (y:ys) = Just (Stack { up=xs, S.focus=y, down=ys })
mkStack (x:xs) ys = Just (Stack { up=xs, S.focus=x, down=ys })
rectB = rect { rect_width=round $ fromIntegral (rect_width rect) * rb }
rectS = rectB { rect_x=rect_x rectB - (round $ (rb - rs) * fromIntegral (rect_width rect)) }
rectM = rect { rect_x=rect_x rect + round (fromIntegral (rect_width rect) * rs)
, rect_width=rect_width rect - round (fromIntegral (rect_width rect) * rs) }
type Reflected l = ModifiedLayout Reflect l
simpleDrawer :: Rational
-> Rational
-> Property
-> Drawer Tall a
simpleDrawer rs rb p = Drawer rs rb p vertical
where
vertical = Tall 0 0 0
drawer :: Rational
-> Rational
-> Property
-> (l a)
-> Drawer l a
drawer = Drawer
onLeft :: Drawer l a -> l' a -> ModifiedLayout (Drawer l) l' a
onLeft = ModifiedLayout
onRight :: Drawer l a -> l' a -> Reflected (ModifiedLayout (Drawer l) (Reflected l')) a
onRight d = reflectHoriz . onLeft d . reflectHoriz
onTop :: Drawer l a -> l' a -> Mirror (ModifiedLayout (Drawer l) (Mirror l')) a
onTop d = Mirror . onLeft d . Mirror
onBottom :: Drawer l a -> l' a -> Reflected (Mirror (ModifiedLayout (Drawer l) (Mirror (Reflected l')))) a
onBottom d = reflectVert . onTop d . reflectVert