summaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-11-19 04:31:20 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-11-19 04:31:20 +0100
commit204ed1bb5fd09ff921b20c7cfe3e3616bf483f52 (patch)
treebba169ce8f080cfa86fd3c7ea2278943f00172e4 /XMonad
parentda0fe17954c46860c020e5eccb9a1a49cd473412 (diff)
downloadmetatile-204ed1bb5fd09ff921b20c7cfe3e3616bf483f52.tar
metatile-204ed1bb5fd09ff921b20c7cfe3e3616bf483f52.zip
No more liftM
darcs-hash:20071119033120-a5988-a45cb35f2b919d5e57980fb9eea9c6d4361bc61b
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Core.hs6
-rw-r--r--XMonad/Operations.hs6
2 files changed, 6 insertions, 6 deletions
diff --git a/XMonad/Core.hs b/XMonad/Core.hs
index 8e89ac1..dd8de32 100644
--- a/XMonad/Core.hs
+++ b/XMonad/Core.hs
@@ -151,7 +151,7 @@ withWindowSet f = gets windowset >>= f
-- | True if the given window is the root window
isRoot :: Window -> X Bool
-isRoot w = liftM (w==) (asks theRoot)
+isRoot w = fmap (w==) (asks theRoot)
-- | Wrapper for the common case of atom internment
getAtom :: String -> X Atom
@@ -216,7 +216,7 @@ class Show (layout a) => LayoutClass layout a where
description = show
instance LayoutClass Layout Window where
- doLayout (Layout l) r s = fmap (fmap Layout) `liftM` doLayout l r s
+ doLayout (Layout l) r s = fmap (fmap Layout) `fmap` doLayout l r s
handleMessage (Layout l) = fmap (fmap Layout) . handleMessage l
description (Layout l) = description l
@@ -310,7 +310,7 @@ restart mprog resume = do
--
recompile :: MonadIO m => m ()
recompile = liftIO $ do
- dir <- liftM (++ "/.xmonad") getHomeDirectory
+ dir <- fmap (++ "/.xmonad") getHomeDirectory
let bin = dir ++ "/" ++ "xmonad"
err = bin ++ ".errors"
src = bin ++ ".hs"
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index fa5d3cc..1c18690 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -51,7 +51,7 @@ manage w = whenX (fmap not $ isClient w) $ withDisplay $ \d -> do
sh <- io $ getWMNormalHints d w
let isFixedSize = sh_min_size sh /= Nothing && sh_min_size sh == sh_max_size sh
- isTransient <- isJust `liftM` io (getTransientForHint d w)
+ isTransient <- isJust `fmap` io (getTransientForHint d w)
(sc, rr) <- floatLocation w
-- ensure that float windows don't go over the edge of the screen
@@ -296,7 +296,7 @@ setFocusX w = withWindowSet $ \ws -> do
setButtonGrab True otherw
-- If we ungrab buttons on the root window, we lose our mouse bindings.
- whenX (not `liftM` isRoot w) $ setButtonGrab False w
+ whenX (not `fmap` isRoot w) $ setButtonGrab False w
io $ do setInputFocus dpy w revertToPointerRoot 0
-- raiseWindow dpy w
@@ -376,7 +376,7 @@ cleanMask km = do
-- | Get the Pixel value for a named color
initColor :: Display -> String -> IO Pixel
-initColor dpy c = (color_pixel . fst) `liftM` allocNamedColor dpy colormap c
+initColor dpy c = (color_pixel . fst) `fmap` allocNamedColor dpy colormap c
where colormap = defaultColormap dpy (defaultScreen dpy)
------------------------------------------------------------------------