xmonad-0.8: A tiling window managerContentsIndex
XMonad.Core
Portabilitynot portable, uses cunning newtype deriving
Stabilityunstable
Maintainerspencerjanssen@gmail.com
Description
The X monad, a state monad transformer over IO, for the window manager state, and support routines.
Synopsis
data X a
type WindowSet = StackSet WorkspaceId (Layout Window) Window ScreenId ScreenDetail
type WindowSpace = Workspace WorkspaceId (Layout Window) Window
type WorkspaceId = String
newtype ScreenId = S Int
data ScreenDetail = SD {
screenRect :: !Rectangle
}
data XState = XState {
windowset :: !WindowSet
mapped :: !Set Window
waitingUnmap :: !Map Window Int
dragging :: !Maybe (Position -> Position -> X (), X ())
}
data XConf = XConf {
display :: Display
config :: !XConfig Layout
theRoot :: !Window
normalBorder :: !Pixel
focusedBorder :: !Pixel
keyActions :: !Map (KeyMask, KeySym) (X ())
buttonActions :: !Map (KeyMask, Button) (Window -> X ())
mouseFocused :: !Bool
}
data XConfig l = XConfig {
normalBorderColor :: !String
focusedBorderColor :: !String
terminal :: !String
layoutHook :: !l Window
manageHook :: !ManageHook
workspaces :: ![String]
numlockMask :: !KeyMask
modMask :: !KeyMask
keys :: !XConfig Layout -> Map (ButtonMask, KeySym) (X ())
mouseBindings :: !XConfig Layout -> Map (ButtonMask, Button) (Window -> X ())
borderWidth :: !Dimension
logHook :: !X ()
startupHook :: !X ()
focusFollowsMouse :: !Bool
}
class Show (layout a) => LayoutClass layout a where
runLayout :: Workspace WorkspaceId (layout a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
doLayout :: layout a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a))
pureLayout :: layout a -> Rectangle -> Stack a -> [(a, Rectangle)]
emptyLayout :: layout a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
handleMessage :: layout a -> SomeMessage -> X (Maybe (layout a))
pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
description :: layout a -> String
data Layout a = forall l . (LayoutClass l a, Read (l a)) => Layout (l a)
readsLayout :: Layout a -> String -> [(Layout a, String)]
class Typeable a => Message a
data SomeMessage = forall a . Message a => SomeMessage a
fromMessage :: Message m => SomeMessage -> Maybe m
data LayoutMessages
= Hide
| ReleaseResources
runX :: XConf -> XState -> X a -> IO (a, XState)
catchX :: X a -> X a -> X a
userCode :: X () -> X ()
io :: MonadIO m => IO a -> m a
catchIO :: MonadIO m => IO () -> m ()
doubleFork :: MonadIO m => IO () -> m ()
withDisplay :: (Display -> X a) -> X a
withWindowSet :: (WindowSet -> X a) -> X a
isRoot :: Window -> X Bool
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
getAtom :: String -> X Atom
spawn :: MonadIO m => String -> m ()
getXMonadDir :: MonadIO m => m String
recompile :: MonadIO m => Bool -> m Bool
trace :: MonadIO m => String -> m ()
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
whenX :: X Bool -> X () -> X ()
atom_WM_STATE :: X Atom
atom_WM_PROTOCOLS :: X Atom
atom_WM_DELETE_WINDOW :: X Atom
type ManageHook = Query (Endo WindowSet)
newtype Query a = Query (ReaderT Window X a)
runQuery :: Query a -> Window -> X a
Documentation
data X a

The X monad, ReaderT and StateT transformers over IO encapsulating the window manager configuration and state, respectively.

Dynamic components may be retrieved with get, static components with ask. With newtype deriving we get readers and state monads instantiated on XConf and XState automatically.

show/hide Instances
Monad X
Functor X
Applicative X
MonadIO X
MonadState XState X
MonadReader XConf X
Monoid a => Monoid (X a)
type WindowSet = StackSet WorkspaceId (Layout Window) Window ScreenId ScreenDetail
type WindowSpace = Workspace WorkspaceId (Layout Window) Window
type WorkspaceId = String
Virtual workspace indices
newtype ScreenId
Physical screen indices
Constructors
S Int
show/hide Instances
data ScreenDetail
The Rectangle with screen dimensions
Constructors
SD
screenRect :: !Rectangle
show/hide Instances
data XState
XState, the (mutable) window manager state.
Constructors
XState
windowset :: !WindowSetworkspace list
mapped :: !Set Windowthe Set of mapped windows
waitingUnmap :: !Map Window Intthe number of expected UnmapEvents
dragging :: !Maybe (Position -> Position -> X (), X ())
show/hide Instances
MonadState XState X
data XConf
XConf, the (read-only) window manager configuration.
Constructors
XConf
display :: Displaythe X11 display
config :: !XConfig Layoutinitial user configuration
theRoot :: !Windowthe root window
normalBorder :: !Pixelborder color of unfocused windows
focusedBorder :: !Pixelborder color of the focused window
keyActions :: !Map (KeyMask, KeySym) (X ())a mapping of key presses to actions
buttonActions :: !Map (KeyMask, Button) (Window -> X ())a mapping of button presses to actions
mouseFocused :: !Boolwas refocus caused by mouse action?
show/hide Instances
MonadReader XConf X
data XConfig l
Constructors
XConfig
normalBorderColor :: !StringNon focused windows border color. Default: "#dddddd"
focusedBorderColor :: !StringFocused windows border color. Default: "#ff0000"
terminal :: !StringThe preferred terminal application. Default: "xterm"
layoutHook :: !l WindowThe available layouts
manageHook :: !ManageHookThe action to run when a new window is opened
workspaces :: ![String]The list of workspaces' names
numlockMask :: !KeyMaskThe numlock modifier
modMask :: !KeyMaskthe mod modifier
keys :: !XConfig Layout -> Map (ButtonMask, KeySym) (X ())The key binding: a map from key presses and actions
mouseBindings :: !XConfig Layout -> Map (ButtonMask, Button) (Window -> X ())The mouse bindings
borderWidth :: !DimensionThe border width
logHook :: !X ()The action to perform when the windows set is changed
startupHook :: !X ()The action to perform on startup
focusFollowsMouse :: !BoolWhether window entry events can change focus
class Show (layout a) => LayoutClass layout a where

Every layout must be an instance of LayoutClass, which defines the basic layout operations along with a sensible default for each.

Minimal complete definition:

You should also strongly consider implementing description, although it is not required.

Note that any code which uses LayoutClass methods should only ever call runLayout, handleMessage, and description! In other words, the only calls to doLayout, pureMessage, and other such methods should be from the default implementations of runLayout, handleMessage, and so on. This ensures that the proper methods will be used, regardless of the particular methods that any LayoutClass instance chooses to define.

Methods
runLayout :: Workspace WorkspaceId (layout a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
By default, runLayout calls doLayout if there are any windows to be laid out, and emptyLayout otherwise. Most instances of LayoutClass probably do not need to implement runLayout; it is only useful for layouts which wish to make use of more of the Workspace information (for example, XMonad.Layout.PerWorkspace).
doLayout :: layout a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a))

Given a Rectangle in which to place the windows, and a Stack of windows, return a list of windows and their corresponding Rectangles. If an element is not given a Rectangle by doLayout, then it is not shown on screen. The order of windows in this list should be the desired stacking order.

Also possibly return a modified layout (by returning Just newLayout), if this layout needs to be modified (e.g. if it keeps track of some sort of state). Return Nothing if the layout does not need to be modified.

Layouts which do not need access to the X monad (IO, window manager state, or configuration) and do not keep track of their own state should implement pureLayout instead of doLayout.

pureLayout :: layout a -> Rectangle -> Stack a -> [(a, Rectangle)]
This is a pure version of doLayout, for cases where we don't need access to the X monad to determine how to lay out the windows, and we don't need to modify the layout itself.
emptyLayout :: layout a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
emptyLayout is called when there are no windows.
handleMessage :: layout a -> SomeMessage -> X (Maybe (layout a))

handleMessage performs message handling. If handleMessage returns Nothing, then the layout did not respond to the message and the screen is not refreshed. Otherwise, handleMessage returns an updated layout and the screen is refreshed.

Layouts which do not need access to the X monad to decide how to handle messages should implement pureMessage instead of handleMessage (this restricts the risk of error, and makes testing much easier).

pureMessage :: layout a -> SomeMessage -> Maybe (layout a)
Respond to a message by (possibly) changing our layout, but taking no other action. If the layout changes, the screen will be refreshed.
description :: layout a -> String
This should be a human-readable string that is used when selecting layouts by name. The default implementation is show, which is in some cases a poor default.
show/hide Instances
data Layout a
An existential type that can hold any object that is in Read and LayoutClass.
Constructors
forall l . (LayoutClass l a, Read (l a)) => Layout (l a)
show/hide Instances
LayoutClass Layout Window
Show (Layout a)
readsLayout :: Layout a -> String -> [(Layout a, String)]
Using the Layout as a witness, parse existentially wrapped windows from a String.
class Typeable a => Message a

Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/, Simon Marlow, 2006. Use extensible messages to the handleMessage handler.

User-extensible messages must be a member of this class.

show/hide Instances
data SomeMessage
A wrapped value of some type in the Message class.
Constructors
forall a . Message a => SomeMessage a
fromMessage :: Message m => SomeMessage -> Maybe m
And now, unwrap a given, unknown Message type, performing a (dynamic) type check on the result.
data LayoutMessages
LayoutMessages are core messages that all layouts (especially stateful layouts) should consider handling.
Constructors
Hidesent when a layout becomes non-visible
ReleaseResourcessent when xmonad is exiting or restarting
show/hide Instances
runX :: XConf -> XState -> X a -> IO (a, XState)
Run the X monad, given a chunk of X monad code, and an initial state Return the result, and final state
catchX :: X a -> X a -> X a
Run in the X monad, and in case of exception, and catch it and log it to stderr, and run the error case.
userCode :: X () -> X ()
Execute the argument, catching all exceptions. Either this function or catchX should be used at all callsites of user customized code.
io :: MonadIO m => IO a -> m a

General utilities

Lift an IO action into the X monad

catchIO :: MonadIO m => IO () -> m ()
Lift an IO action into the X monad. If the action results in an IO exception, log the exception to stderr and continue normal execution.
doubleFork :: MonadIO m => IO () -> m ()
Double fork and execute an IO action (usually one of the exec family of functions)
withDisplay :: (Display -> X a) -> X a
Run a monad action with the current display settings
withWindowSet :: (WindowSet -> X a) -> X a
Run a monadic action with the current stack set
isRoot :: Window -> X Bool
True if the given window is the root window
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
This is basically a map function, running a function in the X monad on each workspace with the output of that function being the modified workspace.
getAtom :: String -> X Atom
Wrapper for the common case of atom internment
spawn :: MonadIO m => String -> m ()
spawn. Launch an external application
getXMonadDir :: MonadIO m => m String
Return the path to ~/.xmonad.
recompile :: MonadIO m => Bool -> m Bool

'recompile force', recompile ~/.xmonad/xmonad.hs when any of the following apply:

  • force is True
  • the xmonad executable does not exist
  • the xmonad executable is older than xmonad.hs

The -i flag is used to restrict recompilation to the xmonad.hs file only.

Compilation errors (if any) are logged to ~/.xmonad/xmonad.errors. If GHC indicates failure with a non-zero exit code, an xmessage displaying that file is spawned.

False is returned if there are compilation errors.

trace :: MonadIO m => String -> m ()
A trace for the X monad. Logs a string to stderr. The result may be found in your .xsession-errors file
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
Conditionally run an action, using a Maybe a to decide.
whenX :: X Bool -> X () -> X ()
Conditionally run an action, using a X event to decide
atom_WM_STATE :: X Atom
atom_WM_PROTOCOLS :: X Atom
atom_WM_DELETE_WINDOW :: X Atom
Common non-predefined atoms
type ManageHook = Query (Endo WindowSet)
newtype Query a
Constructors
Query (ReaderT Window X a)
show/hide Instances
Monad Query
Functor Query
MonadIO Query
MonadReader Window Query
Monoid a => Monoid (Query a)
runQuery :: Query a -> Window -> X a
Produced by Haddock version 2.1.0