summaryrefslogtreecommitdiffstats
path: root/XMonad/Core.hs
diff options
context:
space:
mode:
authorDon Stewart <dons@galois.com>2007-11-20 19:17:43 +0100
committerDon Stewart <dons@galois.com>2007-11-20 19:17:43 +0100
commit65caed7239277c77351406ed823c154710c7c954 (patch)
tree0f48d48343428a3bb1121c5d209ca77af950c240 /XMonad/Core.hs
parent5f536f2182f06d73d123b3b6b0504ee37ef5ae4c (diff)
downloadmetatile-65caed7239277c77351406ed823c154710c7c954.tar
metatile-65caed7239277c77351406ed823c154710c7c954.zip
clean up fmap overuse with applicatives. more opportunities remain
darcs-hash:20071120181743-cba2c-15c56f06646e990bea3b41e31e98ef6db1975dff
Diffstat (limited to 'XMonad/Core.hs')
-rw-r--r--XMonad/Core.hs9
1 files changed, 5 insertions, 4 deletions
diff --git a/XMonad/Core.hs b/XMonad/Core.hs
index 5eaa991..cb63333 100644
--- a/XMonad/Core.hs
+++ b/XMonad/Core.hs
@@ -34,6 +34,7 @@ import XMonad.StackSet
import Prelude hiding ( catch )
import Control.Exception (catch, bracket, throw, Exception(ExitException))
+import Control.Applicative
import Control.Monad.State
import Control.Monad.Reader
import System.IO
@@ -125,7 +126,7 @@ type ManageHook = Query (Endo WindowSet)
newtype Query a = Query (ReaderT Window X a) deriving (Functor, Monad, MonadReader Window)
runManageHook :: ManageHook -> Window -> X (WindowSet -> WindowSet)
-runManageHook (Query m) w = fmap appEndo $ runReaderT m w
+runManageHook (Query m) w = appEndo <$> runReaderT m w
instance Monoid a => Monoid (Query a) where
mempty = return mempty
@@ -166,7 +167,7 @@ withWindowSet f = gets windowset >>= f
-- | True if the given window is the root window
isRoot :: Window -> X Bool
-isRoot w = fmap (w==) (asks theRoot)
+isRoot w = (w==) <$> asks theRoot
-- | Wrapper for the common case of atom internment
getAtom :: String -> X Atom
@@ -325,7 +326,7 @@ restart mprog resume = do
--
recompile :: MonadIO m => m ()
recompile = liftIO $ do
- dir <- fmap (++ "/.xmonad") getHomeDirectory
+ dir <- (++ "/.xmonad") <$> getHomeDirectory
let bin = dir ++ "/" ++ "xmonad"
err = bin ++ ".errors"
src = bin ++ ".hs"
@@ -343,7 +344,7 @@ recompile = liftIO $ do
["Error detected while loading xmonad configuration file: " ++ src]
++ lines ghcErr ++ ["","Please check the file for errors."]
doubleFork $ executeFile "xmessage" True [msg] Nothing
- where getModTime f = catch (fmap Just $ getModificationTime f) (const $ return Nothing)
+ where getModTime f = catch (Just <$> getModificationTime f) (const $ return Nothing)
-- | Run a side effecting action with the current workspace. Like 'when' but
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()