xmonad-0.12: A tiling window manager

Copyright(c) Spencer Janssen 2007
LicenseBSD3-style (see LICENSE)
Maintainerspencerjanssen@gmail.com
Stabilityunstable
Portabilitynot portable, uses cunning newtype deriving
Safe HaskellNone
LanguageHaskell98

XMonad.Core

Description

The X monad, a state monad transformer over IO, for the window manager state, and support routines.

Synopsis

Documentation

data X a Source

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.

type WorkspaceId = String Source

Virtual workspace indices

data ScreenDetail Source

The Rectangle with screen dimensions

Constructors

SD 

Fields

screenRect :: !Rectangle
 

data XState Source

XState, the (mutable) window manager state.

Constructors

XState 

Fields

windowset :: !WindowSet

workspace list

mapped :: !(Set Window)

the Set of mapped windows

waitingUnmap :: !(Map Window Int)

the number of expected UnmapEvents

dragging :: !(Maybe (Position -> Position -> X (), X ()))
 
numberlockMask :: !KeyMask

The numlock modifier

extensibleState :: !(Map String (Either String StateExtension))

stores custom state information.

The module XMonad.Utils.ExtensibleState in xmonad-contrib provides additional information and a simple interface for using this.

data XConf Source

XConf, the (read-only) window manager configuration.

Constructors

XConf 

Fields

display :: Display

the X11 display

config :: !(XConfig Layout)

initial user configuration

theRoot :: !Window

the root window

normalBorder :: !Pixel

border color of unfocused windows

focusedBorder :: !Pixel

border 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 :: !Bool

was refocus caused by mouse action?

mousePosition :: !(Maybe (Position, Position))

position of the mouse according to the event currently being processed

currentEvent :: !(Maybe Event)

event currently being processed

data XConfig l Source

Constructors

XConfig 

Fields

normalBorderColor :: !String

Non focused windows border color. Default: "#dddddd"

focusedBorderColor :: !String

Focused windows border color. Default: "#ff0000"

terminal :: !String

The preferred terminal application. Default: "xterm"

layoutHook :: !(l Window)

The available layouts

manageHook :: !ManageHook

The action to run when a new window is opened

handleEventHook :: !(Event -> X All)

Handle an X event, returns (All True) if the default handler should also be run afterwards. mappend should be used for combining event hooks in most cases.

workspaces :: ![String]

The list of workspaces' names

modMask :: !KeyMask

the 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 :: !Dimension

The border width

logHook :: !(X ())

The action to perform when the windows set is changed

startupHook :: !(X ())

The action to perform on startup

focusFollowsMouse :: !Bool

Whether window entry events can change focus

clickJustFocuses :: !Bool

False to make a click which changes focus to be additionally passed to the window

clientMask :: !EventMask

The client events that xmonad is interested in

rootMask :: !EventMask

The root events that xmonad is interested in

handleExtraArgs :: !([String] -> XConfig Layout -> IO (XConfig Layout))

Modify the configuration, complain about extra arguments etc. with arguments that are not handled by default

class Show (layout a) => LayoutClass layout a where Source

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.

Minimal complete definition

Nothing

Methods

runLayout :: Workspace WorkspaceId (layout a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a)) Source

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)) Source

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)] Source

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)) Source

emptyLayout is called when there are no windows.

handleMessage :: layout a -> SomeMessage -> X (Maybe (layout a)) Source

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) Source

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 Source

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.

data Layout a Source

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) 

readsLayout :: Layout a -> String -> [(Layout a, String)] Source

Using the Layout as a witness, parse existentially wrapped windows from a String.

class Typeable a

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

class Typeable a => Message a Source

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.

data SomeMessage Source

A wrapped value of some type in the Message class.

Constructors

forall a . Message a => SomeMessage a 

fromMessage :: Message m => SomeMessage -> Maybe m Source

And now, unwrap a given, unknown Message type, performing a (dynamic) type check on the result.

data LayoutMessages Source

LayoutMessages are core messages that all layouts (especially stateful layouts) should consider handling.

Constructors

Hide

sent when a layout becomes non-visible

ReleaseResources

sent when xmonad is exiting or restarting

data StateExtension Source

Existential type to store a state extension.

Constructors

forall a . ExtensionClass a => StateExtension a

Non-persistent state extension

forall a . (Read a, Show a, ExtensionClass a) => PersistentExtension a

Persistent extension

class Typeable a => ExtensionClass a where Source

Every module must make the data it wants to store an instance of this class.

Minimal complete definition: initialValue

Minimal complete definition

initialValue

Methods

initialValue :: a Source

Defines an initial value for the state extension

extensionType :: a -> StateExtension Source

Specifies whether the state extension should be persistent. Setting this method to PersistentExtension will make the stored data survive restarts, but requires a to be an instance of Read and Show.

It defaults to StateExtension, i.e. no persistence.

runX :: XConf -> XState -> X a -> IO (a, XState) Source

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 Source

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 a -> X (Maybe a) Source

Execute the argument, catching all exceptions. Either this function or catchX should be used at all callsites of user customized code.

userCodeDef :: a -> X a -> X a Source

Same as userCode but with a default argument to return instead of using Maybe, provided for convenience.

io :: MonadIO m => IO a -> m a Source

General utilities

Lift an IO action into the X monad

catchIO :: MonadIO m => IO () -> m () Source

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.

installSignalHandlers :: MonadIO m => m () Source

Ignore SIGPIPE to avoid termination when a pipe is full, and SIGCHLD to avoid zombie processes, and clean up any extant zombie processes.

withDisplay :: (Display -> X a) -> X a Source

Run a monad action with the current display settings

withWindowSet :: (WindowSet -> X a) -> X a Source

Run a monadic action with the current stack set

isRoot :: Window -> X Bool Source

True if the given window is the root window

runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X () Source

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 Source

Wrapper for the common case of atom internment

spawn :: MonadIO m => String -> m () Source

spawn. Launch an external application. Specifically, it double-forks and runs the String you pass as a command to /bin/sh.

Note this function assumes your locale uses utf8.

spawnPID :: MonadIO m => String -> m ProcessID Source

Like spawn, but returns the ProcessID of the launched application

xfork :: MonadIO m => IO () -> m ProcessID Source

A replacement for forkProcess which resets default signal handlers.

getXMonadDir :: MonadIO m => m String Source

Return the path to ~/.xmonad.

recompile :: MonadIO m => Bool -> m Bool Source

'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 or any file in ~/.xmonad/lib

The -i flag is used to restrict recompilation to the xmonad.hs file only, and any files in the ~/.xmonad/lib directory.

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 () Source

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 () Source

Conditionally run an action, using a Maybe a to decide.

whenX :: X Bool -> X () -> X () Source

Conditionally run an action, using a X event to decide

atom_WM_STATE :: X Atom Source

Common non-predefined atoms

atom_WM_PROTOCOLS :: X Atom Source

Common non-predefined atoms

atom_WM_DELETE_WINDOW :: X Atom Source

Common non-predefined atoms

atom_WM_TAKE_FOCUS :: X Atom Source

Common non-predefined atoms