aboutsummaryrefslogtreecommitdiffstats
path: root/Mosaic.hs
diff options
context:
space:
mode:
authorglasser <glasser@mit.edu>2007-05-23 17:58:55 +0200
committerglasser <glasser@mit.edu>2007-05-23 17:58:55 +0200
commitbea0345abfee66e10b0b5444f139ea8ac59690e0 (patch)
tree30909ff487dfe47281434d12c71aee76d6bc0e65 /Mosaic.hs
parentab5d6ed970317c336ab1ac476b6829b53723bcd7 (diff)
downloadXMonadContrib-bea0345abfee66e10b0b5444f139ea8ac59690e0.tar.gz
XMonadContrib-bea0345abfee66e10b0b5444f139ea8ac59690e0.tar.xz
XMonadContrib-bea0345abfee66e10b0b5444f139ea8ac59690e0.zip
Extract NamedWindow support from Mosaic into its own module
darcs-hash:20070523155855-64353-c23049efec2d620ede1e7acfcc5f1f979148c6fe.gz
Diffstat (limited to 'Mosaic.hs')
-rw-r--r--Mosaic.hs23
1 files changed, 2 insertions, 21 deletions
diff --git a/Mosaic.hs b/Mosaic.hs
index f00825e..8b8411c 100644
--- a/Mosaic.hs
+++ b/Mosaic.hs
@@ -26,12 +26,8 @@ module XMonadContrib.Mosaic ( mosaic, expandWindow, shrinkWindow, squareWindow,
-- , ((modMask .|. shiftMask, xK_s ), withNamedWindow (sendMessage . squareWindow))
-- , ((modMask .|. shiftMask, xK_o ), withNamedWindow (sendMessage . clearWindow))
-import Control.Monad.Reader ( asks )
-import Control.Monad.State ( gets )
-import qualified StackSet as W ( peek )
import Data.Ratio
import Graphics.X11.Xlib
-import Graphics.X11.Xlib.Extras ( fetchName )
import XMonad
import Operations ( Resize(Shrink, Expand) )
import qualified Data.Map as M
@@ -39,6 +35,8 @@ import Data.List ( sort )
import Data.Typeable ( Typeable )
import Control.Monad ( mplus )
+import XMonadContrib.NamedWindows
+
import System.IO.Unsafe
data HandleWindow = ExpandWindow NamedWindow | ShrinkWindow NamedWindow
@@ -91,12 +89,6 @@ add_rater r w = M.alter f w where f Nothing= Just r
type WindowRater = NamedWindow -> Rectangle -> Rational
-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'
-
mosaicL :: Rational -> M.Map NamedWindow WindowRater -> M.Map NamedWindow Area
-> Rectangle -> [Window] -> X [(Window, Rectangle)]
mosaicL _ _ _ _ [] = return []
@@ -195,14 +187,3 @@ allsplits (x:xs) = (map ([x]:) splitsrest) ++
maphead :: (a->a) -> [a] -> [a]
maphead f (x:xs) = f x : xs
maphead _ [] = []
-
-getName :: Window -> X NamedWindow
-getName w = asks display >>= \d -> do n <- maybe "" 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