diff options
-rw-r--r-- | XMonad/Layout/IM.hs | 23 | ||||
-rw-r--r-- | XMonad/Util/WindowProperties.hs | 49 | ||||
-rw-r--r-- | xmonad-contrib.cabal | 1 |
3 files changed, 51 insertions, 22 deletions
diff --git a/XMonad/Layout/IM.hs b/XMonad/Layout/IM.hs index dae15d1..08ddea9 100644 --- a/XMonad/Layout/IM.hs +++ b/XMonad/Layout/IM.hs @@ -32,6 +32,7 @@ import qualified XMonad.StackSet as S import Data.List import XMonad.Layout (splitHorizontallyBy) import XMonad.Layout.Grid (arrange) +import XMonad.Util.WindowProperties -- $usage -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: @@ -68,28 +69,6 @@ import XMonad.Layout.Grid (arrange) data IM a = IM Rational Property deriving (Read, Show) --- It's hard to reuse code from ManageHook because Query Bool is not in Show/Read. -data Property = Title String - | ClassName String - | Resource String - | And Property Property - | Or Property Property - | Not Property - | Const Bool - deriving (Read, Show) -infixr 9 `And` -infixr 8 `Or` - --- | Does given window have this property? -hasProperty :: Property -> Window -> X Bool -hasProperty (Title s) w = withDisplay $ \d -> fmap (Just s ==) $ io $ fetchName d w -hasProperty (Resource s) w = withDisplay $ \d -> fmap ((==) s . resName ) $ io $ getClassHint d w -hasProperty (ClassName s) w = withDisplay $ \d -> fmap ((==) s . resClass) $ io $ getClassHint d w -hasProperty (And p1 p2) w = do { r1 <- hasProperty p1 w; r2 <- hasProperty p2 w; return $ r1 && r2 } -hasProperty (Or p1 p2) w = do { r1 <- hasProperty p1 w; r2 <- hasProperty p2 w; return $ r1 || r2 } -hasProperty (Not p1) w = do { r1 <- hasProperty p1 w; return $ not r1 } -hasProperty (Const b) _ = return b - instance LayoutClass IM Window where description _ = "IM" doLayout (IM r prop) rect stack = do diff --git a/XMonad/Util/WindowProperties.hs b/XMonad/Util/WindowProperties.hs new file mode 100644 index 0000000..a8a9c23 --- /dev/null +++ b/XMonad/Util/WindowProperties.hs @@ -0,0 +1,49 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Layout.WindowProperties +-- Copyright : (c) Roman Cheplyaka +-- License : BSD-style (see LICENSE) +-- +-- Maintainer : Roman Cheplyaka <roma@ro-che.info> +-- Stability : unstable +-- Portability : unportable +-- +-- EDSL for specifying window properties, such as title, classname or resource. +-- +----------------------------------------------------------------------------- +module XMonad.Util.WindowProperties ( + -- * Usage + -- $usage + Property(..), hasProperty) +where +import XMonad + +-- $usage +-- This module allows to specify window properties, such as title, classname or +-- resource, and to check them. +-- +-- In contrast to ManageHook properties, these are instances of Show and Read, +-- so they can be used in layout definitions etc. For example usage see "XMonad.Layout.IM" + +-- | Property constructors are quite self-explaining. +data Property = Title String + | ClassName String + | Resource String + | And Property Property + | Or Property Property + | Not Property + | Const Bool + deriving (Read, Show) +infixr 9 `And` +infixr 8 `Or` + +-- | Does given window have this property? +hasProperty :: Property -> Window -> X Bool +hasProperty (Title s) w = withDisplay $ \d -> fmap (Just s ==) $ io $ fetchName d w +hasProperty (Resource s) w = withDisplay $ \d -> fmap ((==) s . resName ) $ io $ getClassHint d w +hasProperty (ClassName s) w = withDisplay $ \d -> fmap ((==) s . resClass) $ io $ getClassHint d w +hasProperty (And p1 p2) w = do { r1 <- hasProperty p1 w; r2 <- hasProperty p2 w; return $ r1 && r2 } +hasProperty (Or p1 p2) w = do { r1 <- hasProperty p1 w; r2 <- hasProperty p2 w; return $ r1 || r2 } +hasProperty (Not p1) w = do { r1 <- hasProperty p1 w; return $ not r1 } +hasProperty (Const b) _ = return b + diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal index 250eb07..d9299f0 100644 --- a/xmonad-contrib.cabal +++ b/xmonad-contrib.cabal @@ -177,6 +177,7 @@ library XMonad.Util.Scratchpad XMonad.Util.Themes XMonad.Util.Timer + XMonad.Util.WindowProperties XMonad.Util.WorkspaceCompare XMonad.Util.XSelection XMonad.Util.XUtils |