aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util/WindowProperties.hs
diff options
context:
space:
mode:
authorRoman Cheplyaka <roma@ro-che.info>2008-03-18 17:56:58 +0100
committerRoman Cheplyaka <roma@ro-che.info>2008-03-18 17:56:58 +0100
commitf44ae00454367441950b38fb2dcea9053c93ccfa (patch)
treecf389da4e440a9e5cba4be5f587de99880a3486a /XMonad/Util/WindowProperties.hs
parentd3775426358270b089138cca15b63d215850b130 (diff)
downloadXMonadContrib-f44ae00454367441950b38fb2dcea9053c93ccfa.tar.gz
XMonadContrib-f44ae00454367441950b38fb2dcea9053c93ccfa.tar.xz
XMonadContrib-f44ae00454367441950b38fb2dcea9053c93ccfa.zip
Move window properties to a separate Util module
Add XMonad.Util.WindowProperties Modify XMonad.Layout.IM.hs to use WindowProperties. darcs-hash:20080318165658-3ebed-d440ac2a3eb05438402f2ce5e23dc7586a89ba70.gz
Diffstat (limited to 'XMonad/Util/WindowProperties.hs')
-rw-r--r--XMonad/Util/WindowProperties.hs49
1 files changed, 49 insertions, 0 deletions
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
+