aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/IM.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/Layout/IM.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/Layout/IM.hs')
-rw-r--r--XMonad/Layout/IM.hs23
1 files changed, 1 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