{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module XMonad.ManageHook where
import XMonad.Core
import Graphics.X11.Xlib.Extras
import Graphics.X11.Xlib (Display, Window, internAtom, wM_NAME)
import Control.Exception.Extensible (bracket, SomeException(..))
import qualified Control.Exception.Extensible as E
import Control.Monad.Reader
import Data.Maybe
import Data.Monoid
import qualified XMonad.StackSet as W
import XMonad.Operations (floatLocation, reveal)
liftX :: X a -> Query a
liftX = Query . lift
idHook :: Monoid m => m
idHook = mempty
(<+>) :: Monoid m => m -> m -> m
(<+>) = mappend
composeAll :: Monoid m => [m] -> m
composeAll = mconcat
infix 0 -->
(-->) :: (Monad m, Monoid a) => m Bool -> m a -> m a
p --> f = p >>= \b -> if b then f else return mempty
(=?) :: Eq a => Query a -> a -> Query Bool
q =? x = fmap (== x) q
infixr 3 <&&>, <||>
(<&&>) :: Monad m => m Bool -> m Bool -> m Bool
(<&&>) = liftM2 (&&)
(<||>) :: Monad m => m Bool -> m Bool -> m Bool
(<||>) = liftM2 (||)
title :: Query String
title = ask >>= \w -> liftX $ do
d <- asks display
let
getProp =
(internAtom d "_NET_WM_NAME" False >>= getTextProperty d w)
`E.catch` \(SomeException _) -> getTextProperty d w wM_NAME
extract prop = do l <- wcTextPropertyToTextList d prop
return $ if null l then "" else head l
io $ bracket getProp (xFree . tp_value) extract `E.catch` \(SomeException _) -> return ""
appName :: Query String
appName = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap resName $ io $ getClassHint d w)
resource :: Query String
resource = appName
className :: Query String
className = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap resClass $ io $ getClassHint d w)
stringProperty :: String -> Query String
stringProperty p = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap (fromMaybe "") $ getStringProperty d w p)
getStringProperty :: Display -> Window -> String -> X (Maybe String)
getStringProperty d w p = do
a <- getAtom p
md <- io $ getWindowProperty8 d a w
return $ fmap (map (toEnum . fromIntegral)) md
doF :: (s -> s) -> Query (Endo s)
doF = return . Endo
doFloat :: ManageHook
doFloat = ask >>= \w -> doF . W.float w . snd =<< liftX (floatLocation w)
doIgnore :: ManageHook
doIgnore = ask >>= \w -> liftX (reveal w) >> doF (W.delete w)
doShift :: WorkspaceId -> ManageHook
doShift i = doF . W.shiftWin i =<< ask