{-# LANGUAGE DeriveDataTypeable, PatternGuards, FlexibleInstances, MultiParamTypeClasses, CPP #-}
module XMonad.Hooks.ManageDocks (
docks, manageDocks, checkDock, AvoidStruts, avoidStruts, avoidStrutsOn,
docksEventHook, docksStartupHook,
ToggleStruts(..),
SetStruts(..),
module XMonad.Util.Types,
#ifdef TESTING
r2c,
c2r,
RectC(..),
#endif
calcGap
) where
import XMonad
import Foreign.C.Types (CLong)
import XMonad.Layout.LayoutModifier
import XMonad.Util.Types
import XMonad.Util.WindowProperties (getProp32s)
import XMonad.Util.XUtils (fi)
import qualified XMonad.Util.ExtensibleState as XS
import Data.Monoid (All(..), mempty)
import Data.Functor((<$>))
import qualified Data.Set as S
import qualified Data.Map as M
import Control.Monad (when, forM_, filterM)
docks :: XConfig a -> XConfig a
docks c = c { startupHook = docksStartupHook <+> startupHook c
, handleEventHook = docksEventHook <+> handleEventHook c
, manageHook = manageDocks <+> manageHook c }
newtype StrutCache = StrutCache { fromStrutCache :: M.Map Window [Strut] }
deriving (Eq, Typeable)
data UpdateDocks = UpdateDocks deriving Typeable
instance Message UpdateDocks
refreshDocks :: X ()
refreshDocks = sendMessage UpdateDocks
instance ExtensionClass StrutCache where
initialValue = StrutCache M.empty
updateStrutCache :: Window -> [Strut] -> X Bool
updateStrutCache w strut = do
XS.modified $ StrutCache . M.insert w strut . fromStrutCache
deleteFromStructCache :: Window -> X Bool
deleteFromStructCache w = do
XS.modified $ StrutCache . M.delete w . fromStrutCache
manageDocks :: ManageHook
manageDocks = checkDock --> (doIgnore <+> setDocksMask)
where setDocksMask = do
ask >>= \win -> liftX $ withDisplay $ \dpy -> do
io $ selectInput dpy win (propertyChangeMask .|. structureNotifyMask)
mempty
checkDock :: Query Bool
checkDock = ask >>= \w -> liftX $ do
dock <- getAtom "_NET_WM_WINDOW_TYPE_DOCK"
desk <- getAtom "_NET_WM_WINDOW_TYPE_DESKTOP"
mbr <- getProp32s "_NET_WM_WINDOW_TYPE" w
case mbr of
Just rs -> return $ any (`elem` [dock,desk]) (map fromIntegral rs)
_ -> return False
docksEventHook :: Event -> X All
docksEventHook (MapNotifyEvent { ev_window = w }) = do
whenX (runQuery checkDock w <&&> (not <$> isClient w)) $ do
strut <- getStrut w
whenX (updateStrutCache w strut) refreshDocks
return (All True)
docksEventHook (PropertyEvent { ev_window = w
, ev_atom = a }) = do
nws <- getAtom "_NET_WM_STRUT"
nwsp <- getAtom "_NET_WM_STRUT_PARTIAL"
when (a == nws || a == nwsp) $ do
strut <- getStrut w
whenX (updateStrutCache w strut) refreshDocks
return (All True)
docksEventHook (DestroyWindowEvent {ev_window = w}) = do
whenX (deleteFromStructCache w) refreshDocks
return (All True)
docksEventHook _ = return (All True)
docksStartupHook :: X ()
docksStartupHook = withDisplay $ \dpy -> do
rootw <- asks theRoot
(_,_,wins) <- io $ queryTree dpy rootw
docks <- filterM (runQuery checkDock) wins
forM_ docks $ \win -> do
strut <- getStrut win
updateStrutCache win strut
refreshDocks
getStrut :: Window -> X [Strut]
getStrut w = do
msp <- getProp32s "_NET_WM_STRUT_PARTIAL" w
case msp of
Just sp -> return $ parseStrutPartial sp
Nothing -> fmap (maybe [] parseStrut) $ getProp32s "_NET_WM_STRUT" w
where
parseStrut xs@[_, _, _, _] = parseStrutPartial . take 12 $ xs ++ cycle [minBound, maxBound]
parseStrut _ = []
parseStrutPartial [l, r, t, b, ly1, ly2, ry1, ry2, tx1, tx2, bx1, bx2]
= filter (\(_, n, _, _) -> n /= 0)
[(L, l, ly1, ly2), (R, r, ry1, ry2), (U, t, tx1, tx2), (D, b, bx1, bx2)]
parseStrutPartial _ = []
calcGap :: S.Set Direction2D -> X (Rectangle -> Rectangle)
calcGap ss = withDisplay $ \dpy -> do
rootw <- asks theRoot
struts <- (filter careAbout . concat) `fmap` XS.gets (M.elems . fromStrutCache)
wa <- io $ getWindowAttributes dpy rootw
let screen = r2c $ Rectangle (fi $ wa_x wa) (fi $ wa_y wa) (fi $ wa_width wa) (fi $ wa_height wa)
return $ \r -> c2r $ foldr (reduce screen) (r2c r) struts
where careAbout (s,_,_,_) = s `S.member` ss
avoidStruts :: LayoutClass l a => l a -> ModifiedLayout AvoidStruts l a
avoidStruts = avoidStrutsOn [U,D,L,R]
avoidStrutsOn :: LayoutClass l a =>
[Direction2D]
-> l a
-> ModifiedLayout AvoidStruts l a
avoidStrutsOn ss = ModifiedLayout $ AvoidStruts (S.fromList ss)
data AvoidStruts a = AvoidStruts (S.Set Direction2D) deriving ( Read, Show )
data ToggleStruts = ToggleStruts
| ToggleStrut Direction2D
deriving (Read,Show,Typeable)
instance Message ToggleStruts
data SetStruts = SetStruts { addedStruts :: [Direction2D]
, removedStruts :: [Direction2D]
}
deriving (Read,Show,Typeable)
instance Message SetStruts
instance LayoutModifier AvoidStruts a where
modifyLayout (AvoidStruts ss) w r = do
srect <- fmap ($ r) (calcGap ss)
rmWorkarea
runLayout w srect
pureMess as@(AvoidStruts ss) m
| Just ToggleStruts <- fromMessage m = Just $ AvoidStruts (toggleAll ss)
| Just (ToggleStrut s) <- fromMessage m = Just $ AvoidStruts (toggleOne s ss)
| Just (SetStruts n k) <- fromMessage m
, let newSS = S.fromList n `S.union` (ss S.\\ S.fromList k)
, newSS /= ss = Just $ AvoidStruts newSS
| Just UpdateDocks <- fromMessage m = Just as
| otherwise = Nothing
where toggleAll x | S.null x = S.fromList [minBound .. maxBound]
| otherwise = S.empty
toggleOne x xs | x `S.member` xs = S.delete x xs
| otherwise = x `S.insert` xs
rmWorkarea :: X ()
rmWorkarea = withDisplay $ \dpy -> do
a <- getAtom "_NET_WORKAREA"
r <- asks theRoot
io (deleteProperty dpy r a)
type Strut = (Direction2D, CLong, CLong, CLong)
newtype RectC = RectC (CLong, CLong, CLong, CLong) deriving (Eq,Show)
r2c :: Rectangle -> RectC
r2c (Rectangle x y w h) = RectC (fi x, fi y, fi x + fi w - 1, fi y + fi h - 1)
c2r :: RectC -> Rectangle
c2r (RectC (x1, y1, x2, y2)) = Rectangle (fi x1) (fi y1) (fi $ x2 - x1 + 1) (fi $ y2 - y1 + 1)
reduce :: RectC -> Strut -> RectC -> RectC
reduce (RectC (sx0, sy0, sx1, sy1)) (s, n, l, h) (RectC (x0, y0, x1, y1)) =
RectC $ case s of
L | p (y0, y1) && qh x1 -> (mx x0 sx0, y0 , x1 , y1 )
R | p (y0, y1) && qv sx1 x0 -> (x0 , y0 , mn x1 sx1, y1 )
U | p (x0, x1) && qh y1 -> (x0 , mx y0 sy0, x1 , y1 )
D | p (x0, x1) && qv sy1 y0 -> (x0 , y0 , x1 , mn y1 sy1)
_ -> (x0 , y0 , x1 , y1 )
where
mx a b = max a (b + n)
mn a b = min a (b - n)
p r = r `overlaps` (l, h)
qh d1 = n <= d1
qv sd1 d0 = sd1 - n >= d0
overlaps :: Ord a => (a, a) -> (a, a) -> Bool
(a, b) `overlaps` (x, y) =
inRange (a, b) x || inRange (a, b) y || inRange (x, y) a
where
inRange (i, j) k = i <= k && k <= j