comments, move isRoot into XMonad

This commit is contained in:
Don Stewart
2007-03-12 01:23:50 +00:00
parent 511559958a
commit 5398895bf4
2 changed files with 12 additions and 6 deletions

View File

@@ -270,10 +270,6 @@ setTopFocus = do
Just new -> setFocus new Just new -> setFocus new
Nothing -> gets theRoot >>= setFocus Nothing -> gets theRoot >>= setFocus
-- | True if the given window is the root window
isRoot :: Window -> X Bool
isRoot w = liftM (w==) (gets theRoot)
-- | raise. focus to window at offset 'n' in list. -- | raise. focus to window at offset 'n' in list.
-- The currently focused window is always the head of the list -- The currently focused window is always the head of the list
raise :: Ordering -> X () raise :: Ordering -> X ()

View File

@@ -15,7 +15,9 @@
-- --
module XMonad ( module XMonad (
X, WorkSpace, XState(..),runX, withDisplay, io, spawn, trace, whenJust X, WorkSpace, XState(..),runX,
io, withDisplay, isRoot,
spawn, trace, whenJust
) where ) where
import StackSet (StackSet) import StackSet (StackSet)
@@ -49,11 +51,19 @@ newtype X a = X (StateT XState IO a)
runX :: XState -> X a -> IO () runX :: XState -> X a -> IO ()
runX st (X a) = runStateT a st >> return () runX st (X a) = runStateT a st >> return ()
-- ---------------------------------------------------------------------
-- Convenient wrappers to state
-- | Run a monad action with the current display settings -- | Run a monad action with the current display settings
withDisplay :: (Display -> X ()) -> X () withDisplay :: (Display -> X ()) -> X ()
withDisplay f = gets display >>= f withDisplay f = gets display >>= f
------------------------------------------------------------------------ -- | True if the given window is the root window
isRoot :: Window -> X Bool
isRoot w = liftM (w==) (gets theRoot)
-- ---------------------------------------------------------------------
-- Utilities
-- | Lift an IO action into the X monad -- | Lift an IO action into the X monad
io :: IO a -> X a io :: IO a -> X a