| Portability | |
|---|---|
| Stability | provisional |
| Maintainer | Don Stewart <dons@galois.com> |
XMonad
Description
- module XMonad.Main
- module XMonad.Core
- module XMonad.Config
- module XMonad.Layout
- module XMonad.ManageHook
- module XMonad.Operations
- module Graphics.X11
- module Graphics.X11.Xlib.Extras
- (.|.) :: Bits a => a -> a -> a
- class Monad m => MonadState s m | m -> s where
- gets :: MonadState s m => (s -> a) -> m a
- modify :: MonadState s m => (s -> s) -> m ()
- class Monad m => MonadReader r m | m -> r where
- asks :: MonadReader r m => (r -> a) -> m a
- class Monad m => MonadIO m where
Documentation
module XMonad.Main
module XMonad.Core
module XMonad.Config
module XMonad.Layout
module XMonad.ManageHook
module XMonad.Operations
module Graphics.X11
module Graphics.X11.Xlib.Extras
class Monad m => MonadState s m | m -> s where
get returns the state from the internals of the monad.
put replaces the state inside the monad.
Instances
| MonadState XState X | |
| MonadState s (State s) | |
| Monad m => MonadState s (StateT s m) | |
| MonadState s m => MonadState s (ReaderT r m) |
gets :: MonadState s m => (s -> a) -> m a
Gets specific component of the state, using a projection function supplied.
modify :: MonadState s m => (s -> s) -> m ()
Monadic state transformer.
Maps an old state to a new state inside a state monad. The old state is thrown away.
Main> :t modify ((+1) :: Int -> Int)
modify (...) :: (MonadState Int a) => a ()
This says that modify (+1) acts over any
Monad that is a member of the MonadState class,
with an Int state.
class Monad m => MonadReader r m | m -> r where
See examples in Control.Monad.Reader.
Note, the partially applied function type (->) r is a simple reader monad.
See the instance declaration below.
Methods
ask :: m r
Retrieves the monad environment.
local :: (r -> r) -> m a -> m a
Executes a computation in a modified environment. Parameters:
- The function to modify the environment.
-
Readerto run. - The resulting
Reader.
Instances
| MonadReader Window Query | |
| MonadReader XConf X | |
| MonadReader r ((->) r) | |
| MonadReader r (Reader r) | |
| MonadReader r m => MonadReader r (StateT s m) | |
| Monad m => MonadReader r (ReaderT r m) |
asks :: MonadReader r m => (r -> a) -> m a
Retrieves a function of the current environment. Parameters:
- The selector function to apply to the environment.
See an example in Control.Monad.Reader.