xmonad-0.16.9999: 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.

Instances

Instances details
Monad X Source # 
Instance details

Defined in XMonad.Core

Methods

(>>=) :: X a -> (a -> X b) -> X b #

(>>) :: X a -> X b -> X b #

return :: a -> X a #

Functor X Source # 
Instance details

Defined in XMonad.Core

Methods

fmap :: (a -> b) -> X a -> X b #

(<$) :: a -> X b -> X a #

MonadFail X Source # 
Instance details

Defined in XMonad.Core

Methods

fail :: String -> X a #

Applicative X Source # 
Instance details

Defined in XMonad.Core

Methods

pure :: a -> X a #

(<*>) :: X (a -> b) -> X a -> X b #

liftA2 :: (a -> b -> c) -> X a -> X b -> X c #

(*>) :: X a -> X b -> X b #

(<*) :: X a -> X b -> X a #

MonadIO X Source # 
Instance details

Defined in XMonad.Core

Methods

liftIO :: IO a -> X a #

MonadState XState X Source # 
Instance details

Defined in XMonad.Core

Methods

get :: X XState #

put :: XState -> X () #

state :: (XState -> (a, XState)) -> X a #

MonadReader XConf X Source # 
Instance details

Defined in XMonad.Core

Methods

ask :: X XConf #

local :: (XConf -> XConf) -> X a -> X a #

reader :: (XConf -> a) -> X a #

Semigroup a => Semigroup (X a) Source # 
Instance details

Defined in XMonad.Core

Methods

(<>) :: X a -> X a -> X a #

sconcat :: NonEmpty (X a) -> X a #

stimes :: Integral b => b -> X a -> X a #

Monoid a => Monoid (X a) Source # 
Instance details

Defined in XMonad.Core

Methods

mempty :: X a #

mappend :: X a -> X a -> X a #

mconcat :: [X a] -> X a #

Default a => Default (X a) Source # 
Instance details

Defined in XMonad.Core

Methods

def :: X a #

type WorkspaceId = String Source #

Virtual workspace indices

newtype ScreenId Source #

Physical screen indices

Constructors

S Int 

Instances

Instances details
Enum ScreenId Source # 
Instance details

Defined in XMonad.Core

Eq ScreenId Source # 
Instance details

Defined in XMonad.Core

Integral ScreenId Source # 
Instance details

Defined in XMonad.Core

Num ScreenId Source # 
Instance details

Defined in XMonad.Core

Ord ScreenId Source # 
Instance details

Defined in XMonad.Core

Read ScreenId Source # 
Instance details

Defined in XMonad.Core

Real ScreenId Source # 
Instance details

Defined in XMonad.Core

Show ScreenId Source # 
Instance details

Defined in XMonad.Core

newtype ScreenDetail Source #

The Rectangle with screen dimensions

Constructors

SD 

data XState Source #

XState, the (mutable) window manager state.

Constructors

XState 

Fields

Instances

Instances details
MonadState XState X Source # 
Instance details

Defined in XMonad.Core

Methods

get :: X XState #

put :: XState -> X () #

state :: (XState -> (a, XState)) -> X a #

data XConf Source #

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

Constructors

XConf 

Fields

Instances

Instances details
MonadReader XConf X Source # 
Instance details

Defined in XMonad.Core

Methods

ask :: X XConf #

local :: (XConf -> XConf) -> X a -> X a #

reader :: (XConf -> a) -> X a #

data XConfig l Source #

Constructors

XConfig 

Fields

Instances

Instances details
a ~ Choose Tall (Choose (Mirror Tall) Full) => Default (XConfig a) Source # 
Instance details

Defined in XMonad.Config

Methods

def :: XConfig a #

class (Show (layout a), Typeable layout) => 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.

All of the methods have default implementations, so there is no minimal complete definition. They do, however, have a dependency structure by default; this is something to be aware of should you choose to implement one of these methods. Here is how a minimal complete definition would look like if we did not provide any default implementations:

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.

Instances

Instances details
LayoutClass Layout Window Source # 
Instance details

Defined in XMonad.Core

LayoutClass Tall a Source # 
Instance details

Defined in XMonad.Layout

LayoutClass Full a Source # 
Instance details

Defined in XMonad.Layout

LayoutClass l a => LayoutClass (Mirror l) a Source # 
Instance details

Defined in XMonad.Layout

(LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a Source # 
Instance details

Defined in XMonad.Layout

Methods

runLayout :: Workspace WorkspaceId (Choose l r a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (Choose l r a)) Source #

doLayout :: Choose l r a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (Choose l r a)) Source #

pureLayout :: Choose l r a -> Rectangle -> Stack a -> [(a, Rectangle)] Source #

emptyLayout :: Choose l r a -> Rectangle -> X ([(a, Rectangle)], Maybe (Choose l r a)) Source #

handleMessage :: Choose l r a -> SomeMessage -> X (Maybe (Choose l r a)) Source #

pureMessage :: Choose l r a -> SomeMessage -> Maybe (Choose l r a) Source #

description :: Choose l r a -> String Source #

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 :: k) #

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.

Instances

Instances details
Message Event Source # 
Instance details

Defined in XMonad.Core

Message LayoutMessages Source # 
Instance details

Defined in XMonad.Core

Message JumpToLayout Source # 
Instance details

Defined in XMonad.Layout

Message ChangeLayout Source # 
Instance details

Defined in XMonad.Layout

Message IncMasterN Source # 
Instance details

Defined in XMonad.Layout

Message Resize Source # 
Instance details

Defined in XMonad.Layout

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

Instances

Instances details
Eq LayoutMessages Source # 
Instance details

Defined in XMonad.Core

Message LayoutMessages Source # 
Instance details

Defined in XMonad.Core

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.

data ConfExtension Source #

Existential type to store a config extension.

Constructors

forall a.Typeable a => ConfExtension a 

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.

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

'recompile force', recompile the xmonad configuration file 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 the lib directory (under the configuration directory).

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

Compilation errors (if any) are logged to the xmonad.errors file in the xmonad data directory. 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

getXMonadDir :: X String Source #

Deprecated: Use `asks (cfgDir . directories)' instead.

Return the path to the xmonad configuration directory.

getXMonadCacheDir :: X String Source #

Deprecated: Use `asks (cacheDir . directories)' instead.

Return the path to the xmonad cache directory.

getXMonadDataDir :: X String Source #

Deprecated: Use `asks (dataDir . directories)' instead.

Return the path to the xmonad data directory.

stateFileName :: X FilePath Source #

Get the name of the file used to store the xmonad window state.

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

withWindowAttributes :: Display -> Window -> (WindowAttributes -> X ()) -> X () Source #

Safely access window attributes.

newtype Query a Source #

Constructors

Query (ReaderT Window X a) 

Instances

Instances details
Monad Query Source # 
Instance details

Defined in XMonad.Core

Methods

(>>=) :: Query a -> (a -> Query b) -> Query b #

(>>) :: Query a -> Query b -> Query b #

return :: a -> Query a #

Functor Query Source # 
Instance details

Defined in XMonad.Core

Methods

fmap :: (a -> b) -> Query a -> Query b #

(<$) :: a -> Query b -> Query a #

Applicative Query Source # 
Instance details

Defined in XMonad.Core

Methods

pure :: a -> Query a #

(<*>) :: Query (a -> b) -> Query a -> Query b #

liftA2 :: (a -> b -> c) -> Query a -> Query b -> Query c #

(*>) :: Query a -> Query b -> Query b #

(<*) :: Query a -> Query b -> Query a #

MonadIO Query Source # 
Instance details

Defined in XMonad.Core

Methods

liftIO :: IO a -> Query a #

MonadReader Window Query Source # 
Instance details

Defined in XMonad.Core

Methods

ask :: Query Window #

local :: (Window -> Window) -> Query a -> Query a #

reader :: (Window -> a) -> Query a #

Semigroup a => Semigroup (Query a) Source # 
Instance details

Defined in XMonad.Core

Methods

(<>) :: Query a -> Query a -> Query a #

sconcat :: NonEmpty (Query a) -> Query a #

stimes :: Integral b => b -> Query a -> Query a #

Monoid a => Monoid (Query a) Source # 
Instance details

Defined in XMonad.Core

Methods

mempty :: Query a #

mappend :: Query a -> Query a -> Query a #

mconcat :: [Query a] -> Query a #

Default a => Default (Query a) Source # 
Instance details

Defined in XMonad.Core

Methods

def :: Query a #

runQuery :: Query a -> Window -> X a Source #

data Directories' a Source #

All the directories that xmonad will use. They will be used for the following purposes:

  • dataDir: This directory is used by XMonad to store data files such as the run-time state file and the configuration binary generated by GHC.
  • cfgDir: This directory is where user configuration files are stored (e.g, the xmonad.hs file). You may also create a lib subdirectory in the configuration directory and the default recompile command will add it to the GHC include path.
  • cacheDir: This directory is used to store temporary files that can easily be recreated. For example, the XPrompt history file.

For how these directories are chosen, see getDirectories.

Constructors

Directories 

Fields

Instances

Instances details
Functor Directories' Source # 
Instance details

Defined in XMonad.Core

Methods

fmap :: (a -> b) -> Directories' a -> Directories' b #

(<$) :: a -> Directories' b -> Directories' a #

Foldable Directories' Source # 
Instance details

Defined in XMonad.Core

Methods

fold :: Monoid m => Directories' m -> m #

foldMap :: Monoid m => (a -> m) -> Directories' a -> m #

foldMap' :: Monoid m => (a -> m) -> Directories' a -> m #

foldr :: (a -> b -> b) -> b -> Directories' a -> b #

foldr' :: (a -> b -> b) -> b -> Directories' a -> b #

foldl :: (b -> a -> b) -> b -> Directories' a -> b #

foldl' :: (b -> a -> b) -> b -> Directories' a -> b #

foldr1 :: (a -> a -> a) -> Directories' a -> a #

foldl1 :: (a -> a -> a) -> Directories' a -> a #

toList :: Directories' a -> [a] #

null :: Directories' a -> Bool #

length :: Directories' a -> Int #

elem :: Eq a => a -> Directories' a -> Bool #

maximum :: Ord a => Directories' a -> a #

minimum :: Ord a => Directories' a -> a #

sum :: Num a => Directories' a -> a #

product :: Num a => Directories' a -> a #

Traversable Directories' Source # 
Instance details

Defined in XMonad.Core

Methods

traverse :: Applicative f => (a -> f b) -> Directories' a -> f (Directories' b) #

sequenceA :: Applicative f => Directories' (f a) -> f (Directories' a) #

mapM :: Monad m => (a -> m b) -> Directories' a -> m (Directories' b) #

sequence :: Monad m => Directories' (m a) -> m (Directories' a) #

Show a => Show (Directories' a) Source # 
Instance details

Defined in XMonad.Core

type Directories = Directories' FilePath Source #

Convenient type alias for the most common case in which one might want to use the Directories type.

getDirectories :: IO Directories Source #

Build up the Dirs that xmonad will use. They are chosen as follows:

  1. If all three of xmonad's environment variables (XMONAD_DATA_DIR, XMONAD_CONFIG_DIR, and XMONAD_CACHE_DIR) are set, use them.
  2. If there is a build script called build or configuration xmonad.hs in ~/.xmonad, set all three directories to ~/.xmonad.
  3. Otherwise, use the xmonad directory in XDG_DATA_HOME, XDG_CONFIG_HOME, and XDG_CACHE_HOME (or their respective fallbacks). These directories are created if necessary.

The xmonad configuration file (or the build script, if present) is always assumed to be in cfgDir.