aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util/NamedWindows.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
commit4866f2e367dfcf22a9591231ba40948826a1b438 (patch)
tree7a245caee3f146826b267d773b7eaa80386a818e /XMonad/Util/NamedWindows.hs
parent47589e1913fb9530481caedb543978a30d4323ea (diff)
downloadXMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.gz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.xz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.zip
Hierarchify
darcs-hash:20071101201059-a5988-fc1f1262bec1b69e13ba18ae7cefeafc8c4471d4.gz
Diffstat (limited to 'XMonad/Util/NamedWindows.hs')
-rw-r--r--XMonad/Util/NamedWindows.hs57
1 files changed, 57 insertions, 0 deletions
diff --git a/XMonad/Util/NamedWindows.hs b/XMonad/Util/NamedWindows.hs
new file mode 100644
index 0000000..05613b2
--- /dev/null
+++ b/XMonad/Util/NamedWindows.hs
@@ -0,0 +1,57 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Util.NamedWindows
+-- Copyright : (c) David Roundy <droundy@darcs.net>
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : David Roundy <droundy@darcs.net>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- This module allows you to associate the X titles of windows with
+-- them.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Util.NamedWindows (
+ -- * Usage
+ -- $usage
+ NamedWindow,
+ getName,
+ withNamedWindow,
+ unName
+ ) where
+
+import Control.Monad.Reader ( asks )
+import Control.Monad.State ( gets )
+
+import qualified XMonad.StackSet as W ( peek )
+
+import Graphics.X11.Xlib
+import Graphics.X11.Xlib.Extras
+
+import XMonad
+
+-- $usage
+-- See "XMonadContrib.Mosaic" for an example of its use.
+
+
+data NamedWindow = NW !String !Window
+instance Eq NamedWindow where
+ (NW s _) == (NW s' _) = s == s'
+instance Ord NamedWindow where
+ compare (NW s _) (NW s' _) = compare s s'
+instance Show NamedWindow where
+ show (NW n _) = n
+
+getName :: Window -> X NamedWindow
+getName w = asks display >>= \d -> do s <- io $ getClassHint d w
+ n <- maybe (resName s) id `fmap` io (fetchName d w)
+ return $ NW n w
+
+unName :: NamedWindow -> Window
+unName (NW _ w) = w
+
+withNamedWindow :: (NamedWindow -> X ()) -> X ()
+withNamedWindow f = do ws <- gets windowset
+ whenJust (W.peek ws) $ \w -> getName w >>= f