{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
module XMonad.Layout.FixedColumn (
FixedColumn(..)
) where
import Control.Monad (msum)
import Data.Maybe (fromMaybe)
import Graphics.X11.Xlib (Window, rect_width)
import Graphics.X11.Xlib.Extras ( getWMNormalHints
, getWindowAttributes
, sh_base_size
, sh_resize_inc
, wa_border_width)
import XMonad.Core (X, LayoutClass(..), fromMessage, io, withDisplay)
import XMonad.Layout (Resize(..), IncMasterN(..), tile)
import XMonad.StackSet as W
data FixedColumn a = FixedColumn !Int
!Int
!Int
!Int
deriving (Read, Show)
instance LayoutClass FixedColumn Window where
doLayout (FixedColumn nmaster _ ncol fallback) r s = do
fws <- mapM (widthCols fallback ncol) ws
let frac = maximum (take nmaster fws) // rect_width r
rs = tile frac r nmaster (length ws)
return $ (zip ws rs, Nothing)
where ws = W.integrate s
x // y = fromIntegral x / fromIntegral y
pureMessage (FixedColumn nmaster delta ncol fallback) m =
msum [fmap resize (fromMessage m)
,fmap incmastern (fromMessage m)]
where resize Shrink
= FixedColumn nmaster delta (max 0 $ ncol - delta) fallback
resize Expand
= FixedColumn nmaster delta (ncol + delta) fallback
incmastern (IncMasterN d)
= FixedColumn (max 0 (nmaster+d)) delta ncol fallback
description _ = "FixedColumn"
widthCols :: Int -> Int -> Window -> X Int
widthCols inc n w = withDisplay $ \d -> io $ do
sh <- getWMNormalHints d w
bw <- fmap (fromIntegral . wa_border_width) $ getWindowAttributes d w
let widthHint f = f sh >>= return . fromIntegral . fst
oneCol = fromMaybe inc $ widthHint sh_resize_inc
base = fromMaybe 0 $ widthHint sh_base_size
return $ 2 * bw + base + n * oneCol