-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | A tiling window manager
--
-- xmonad is a tiling window manager for X. Windows are arranged
-- automatically to tile the screen without gaps or overlap, maximising
-- screen use. All features of the window manager are accessible from the
-- keyboard: a mouse is strictly optional. xmonad is written and
-- extensible in Haskell. Custom layout algorithms, and other extensions,
-- may be written by the user in config files. Layouts are applied
-- dynamically, and different layouts may be used on each workspace.
-- Xinerama is fully supported, allowing windows to be tiled on several
-- screens.
@package xmonad
@version 0.17.2
module XMonad.StackSet
-- | A cursor into a non-empty list of workspaces.
--
-- We puncture the workspace list, producing a hole in the structure used
-- to track the currently focused workspace. The two other lists that are
-- produced are used to track those workspaces visible as Xinerama
-- screens, and those workspaces not visible anywhere.
data StackSet i l a sid sd
StackSet :: !Screen i l a sid sd -> [Screen i l a sid sd] -> [Workspace i l a] -> Map a RationalRect -> StackSet i l a sid sd
-- | currently focused workspace
[current] :: StackSet i l a sid sd -> !Screen i l a sid sd
-- | non-focused workspaces, visible in xinerama
[visible] :: StackSet i l a sid sd -> [Screen i l a sid sd]
-- | workspaces not visible anywhere
[hidden] :: StackSet i l a sid sd -> [Workspace i l a]
-- | floating windows
[floating] :: StackSet i l a sid sd -> Map a RationalRect
-- | A workspace is just a tag, a layout, and a stack.
data Workspace i l a
Workspace :: !i -> l -> Maybe (Stack a) -> Workspace i l a
[tag] :: Workspace i l a -> !i
[layout] :: Workspace i l a -> l
[stack] :: Workspace i l a -> Maybe (Stack a)
-- | Visible workspaces, and their Xinerama screens.
data Screen i l a sid sd
Screen :: !Workspace i l a -> !sid -> !sd -> Screen i l a sid sd
[workspace] :: Screen i l a sid sd -> !Workspace i l a
[screen] :: Screen i l a sid sd -> !sid
[screenDetail] :: Screen i l a sid sd -> !sd
-- | A stack is a cursor onto a window list. The data structure tracks
-- focus by construction, and the master window is by convention the
-- top-most item. Focus operations will not reorder the list that results
-- from flattening the cursor. The structure can be envisaged as:
--
--
-- +-- master: < '7' >
-- up | [ '2' ]
-- +--------- [ '3' ]
-- focus: < '4' >
-- dn +----------- [ '8' ]
--
--
-- A Stack can be viewed as a list with a hole punched in it to
-- make the focused position. Under the zipper/calculus view of such
-- structures, it is the differentiation of a [a], and integrating it
-- back has a natural implementation used in index.
data Stack a
Stack :: !a -> [a] -> [a] -> Stack a
[focus] :: Stack a -> !a
[up] :: Stack a -> [a]
[down] :: Stack a -> [a]
-- | A structure for window geometries
data RationalRect
RationalRect :: !Rational -> !Rational -> !Rational -> !Rational -> RationalRect
-- | O(n). Create a new stackset, of empty stacks, with given tags,
-- with physical screens whose descriptions are given by m. The
-- number of physical screens (length m) should be less
-- than or equal to the number of workspace tags. The first workspace in
-- the list will be current.
--
-- Xinerama: Virtual workspaces are assigned to physical screens,
-- starting at 0.
new :: Integral s => l -> [i] -> [sd] -> StackSet i l a s sd
-- | O(w). Set focus to the workspace with index 'i'. If the index
-- is out of range, return the original StackSet.
--
-- Xinerama: If the workspace is not visible on any Xinerama screen, it
-- becomes the current screen. If it is in the visible list, it becomes
-- current.
view :: (Eq s, Eq i) => i -> StackSet i l a s sd -> StackSet i l a s sd
-- | Set focus to the given workspace. If that workspace does not exist in
-- the stackset, the original workspace is returned. If that workspace is
-- hidden, then display that workspace on the current screen, and
-- move the current workspace to hidden. If that workspace is
-- visible on another screen, the workspaces of the current screen
-- and the other screen are swapped.
greedyView :: (Eq s, Eq i) => i -> StackSet i l a s sd -> StackSet i l a s sd
-- | Find the tag of the workspace visible on Xinerama screen sc.
-- Nothing if screen is out of bounds.
lookupWorkspace :: Eq s => s -> StackSet i l a s sd -> Maybe i
-- | Get a list of all screens in the StackSet.
screens :: StackSet i l a s sd -> [Screen i l a s sd]
-- | Get a list of all workspaces in the StackSet.
workspaces :: StackSet i l a s sd -> [Workspace i l a]
-- | Get a list of all windows in the StackSet in no particular
-- order
allWindows :: Eq a => StackSet i l a s sd -> [a]
-- | Get the tag of the currently focused workspace.
currentTag :: StackSet i l a s sd -> i
-- | O(1). Extract the focused element of the current stack. Return
-- Just that element, or Nothing for an empty stack.
peek :: StackSet i l a s sd -> Maybe a
-- | O(s). Extract the stack on the current workspace, as a list.
-- The order of the stack is determined by the master window -- it will
-- be the head of the list. The implementation is given by the natural
-- integration of a one-hole list cursor, back to a list.
index :: StackSet i l a s sd -> [a]
-- | O(n). Flatten a Stack into a list.
integrate :: Stack a -> [a]
-- | O(n). Flatten a possibly empty stack into a list.
integrate' :: Maybe (Stack a) -> [a]
-- | O(n). Turn a list into a possibly empty stack (i.e., a zipper):
-- the first element of the list is current, and the rest of the list is
-- down.
differentiate :: [a] -> Maybe (Stack a)
-- | O(1), O(w) on the wrapping case. Move the window focus up the
-- stack, wrapping if we reach the end. The wrapping should model a
-- cycle on the current stack. The master window and
-- window order are unaffected by movement of focus.
focusUp :: StackSet i l a s sd -> StackSet i l a s sd
-- | O(1), O(w) on the wrapping case. Like focusUp, but move
-- the window focus down the stack.
focusDown :: StackSet i l a s sd -> StackSet i l a s sd
-- | A variant of focusUp with the same asymptotics that works on a
-- Stack rather than an entire StackSet.
focusUp' :: Stack a -> Stack a
-- | A variant of focusDown with the same asymptotics that works on
-- a Stack rather than an entire StackSet.
focusDown' :: Stack a -> Stack a
-- | O(s). Set focus to the master window.
focusMaster :: StackSet i l a s sd -> StackSet i l a s sd
-- | O(1) on current window, O(n) in general. Focus the window
-- w, and set its workspace as current.
focusWindow :: (Eq s, Eq a, Eq i) => a -> StackSet i l a s sd -> StackSet i l a s sd
-- | Is the given tag present in the StackSet?
tagMember :: Eq i => i -> StackSet i l a s sd -> Bool
-- | Rename a given tag if present in the StackSet.
renameTag :: Eq i => i -> i -> StackSet i l a s sd -> StackSet i l a s sd
-- | Ensure that a given set of workspace tags is present by renaming
-- existing workspaces and/or creating new hidden workspaces as
-- necessary.
ensureTags :: Eq i => l -> [i] -> StackSet i l a s sd -> StackSet i l a s sd
-- | O(n). Is a window in the StackSet?
member :: Eq a => a -> StackSet i l a s sd -> Bool
-- | O(1) on current window, O(n) in general. Return Just the
-- workspace tag of the given window, or Nothing if the window is
-- not in the StackSet.
findTag :: Eq a => a -> StackSet i l a s sd -> Maybe i
-- | Map a function on all the workspaces in the StackSet.
mapWorkspace :: (Workspace i l a -> Workspace i l a) -> StackSet i l a s sd -> StackSet i l a s sd
-- | Map a function on all the layouts in the StackSet.
mapLayout :: (l -> l') -> StackSet i l a s sd -> StackSet i l' a s sd
-- | O(n). (Complexity due to duplicate check). Insert a new element
-- into the stack, above the currently focused element. The new element
-- is given focus; the previously focused element is moved down.
--
-- If the element is already in the stackset, the original stackset is
-- returned unmodified.
--
-- Semantics in Huet's paper is that insert doesn't move the cursor.
-- However, we choose to insert above, and move the focus.
insertUp :: Eq a => a -> StackSet i l a s sd -> StackSet i l a s sd
-- | O(1) on current window, O(n) in general. Delete window
-- w if it exists. There are 4 cases to consider:
--
--
-- - delete on an Nothing workspace leaves it Nothing
-- - otherwise, try to move focus to the down
-- - otherwise, try to move focus to the up
-- - otherwise, you've got an empty workspace, becomes
-- Nothing
--
--
-- Behaviour with respect to the master:
--
--
-- - deleting the master window resets it to the newly focused
-- window
-- - otherwise, delete doesn't affect the master.
--
delete :: Ord a => a -> StackSet i l a s sd -> StackSet i l a s sd
-- | Only temporarily remove the window from the stack, thereby not
-- destroying special information saved in the Stackset
delete' :: Eq a => a -> StackSet i l a s sd -> StackSet i l a s sd
-- | O(n). 'filter p s' returns the elements of s such that
-- p evaluates to True. Order is preserved, and focus
-- moves as described for delete.
filter :: (a -> Bool) -> Stack a -> Maybe (Stack a)
-- | O(1), O(w) on the wrapping case. Swap the upwards (left)
-- neighbour in the stack ordering, wrapping if we reach the end. Much
-- like for focusUp and focusDown, the wrapping model
-- should cycle on the current stack.
swapUp :: StackSet i l a s sd -> StackSet i l a s sd
-- | O(1), O(w) on the wrapping case. Like swapUp, but for
-- swapping the downwards (right) neighbour.
swapDown :: StackSet i l a s sd -> StackSet i l a s sd
-- | O(s). Set the master window to the focused window. The old
-- master window is swapped in the tiling order with the focused window.
-- Focus stays with the item moved.
swapMaster :: StackSet i l a s sd -> StackSet i l a s sd
-- | O(s). Set the master window to the focused window. The other
-- windows are kept in order and shifted down on the stack, as if you
-- just hit mod-shift-k a bunch of times. Focus stays with the item
-- moved.
shiftMaster :: StackSet i l a s sd -> StackSet i l a s sd
-- | Apply a function, and a default value for Nothing, to modify
-- the current stack.
modify :: Maybe (Stack a) -> (Stack a -> Maybe (Stack a)) -> StackSet i l a s sd -> StackSet i l a s sd
-- | Apply a function to modify the current stack if it isn't empty, and we
-- don't want to empty it.
modify' :: (Stack a -> Stack a) -> StackSet i l a s sd -> StackSet i l a s sd
-- | Given a window, and its preferred rectangle, set it as floating A
-- floating window should already be managed by the StackSet.
float :: Ord a => a -> RationalRect -> StackSet i l a s sd -> StackSet i l a s sd
-- | Clear the floating status of a window
sink :: Ord a => a -> StackSet i l a s sd -> StackSet i l a s sd
-- | O(w). shift. Move the focused element of the current stack to
-- stack n, leaving it as the focused element on that stack. The
-- item is inserted above the currently focused element on that
-- workspace. The actual focused workspace doesn't change. If there is no
-- element on the current stack, the original stackSet is returned.
shift :: (Ord a, Eq s, Eq i) => i -> StackSet i l a s sd -> StackSet i l a s sd
-- | O(n). shiftWin. Searches for the specified window w on
-- all workspaces of the stackSet and moves it to stack n,
-- leaving it as the focused element on that stack. The item is inserted
-- above the currently focused element on that workspace. The actual
-- focused workspace doesn't change. If the window is not found in the
-- stackSet, the original stackSet is returned.
shiftWin :: (Ord a, Eq s, Eq i) => i -> a -> StackSet i l a s sd -> StackSet i l a s sd
-- | this function indicates to catch that an error is expected
abort :: String -> a
instance GHC.Classes.Eq XMonad.StackSet.RationalRect
instance GHC.Read.Read XMonad.StackSet.RationalRect
instance GHC.Show.Show XMonad.StackSet.RationalRect
instance GHC.Base.Functor XMonad.StackSet.Stack
instance GHC.Classes.Eq a => GHC.Classes.Eq (XMonad.StackSet.Stack a)
instance GHC.Read.Read a => GHC.Read.Read (XMonad.StackSet.Stack a)
instance GHC.Show.Show a => GHC.Show.Show (XMonad.StackSet.Stack a)
instance (GHC.Classes.Eq i, GHC.Classes.Eq l, GHC.Classes.Eq a) => GHC.Classes.Eq (XMonad.StackSet.Workspace i l a)
instance (GHC.Read.Read i, GHC.Read.Read l, GHC.Read.Read a) => GHC.Read.Read (XMonad.StackSet.Workspace i l a)
instance (GHC.Show.Show i, GHC.Show.Show l, GHC.Show.Show a) => GHC.Show.Show (XMonad.StackSet.Workspace i l a)
instance (GHC.Classes.Eq i, GHC.Classes.Eq l, GHC.Classes.Eq a, GHC.Classes.Eq sid, GHC.Classes.Eq sd) => GHC.Classes.Eq (XMonad.StackSet.Screen i l a sid sd)
instance (GHC.Read.Read i, GHC.Read.Read l, GHC.Read.Read a, GHC.Read.Read sid, GHC.Read.Read sd) => GHC.Read.Read (XMonad.StackSet.Screen i l a sid sd)
instance (GHC.Show.Show i, GHC.Show.Show l, GHC.Show.Show a, GHC.Show.Show sid, GHC.Show.Show sd) => GHC.Show.Show (XMonad.StackSet.Screen i l a sid sd)
instance (GHC.Classes.Eq i, GHC.Classes.Eq l, GHC.Classes.Eq sid, GHC.Classes.Eq sd, GHC.Classes.Eq a) => GHC.Classes.Eq (XMonad.StackSet.StackSet i l a sid sd)
instance (GHC.Read.Read i, GHC.Read.Read l, GHC.Read.Read sid, GHC.Read.Read sd, GHC.Read.Read a, GHC.Classes.Ord a) => GHC.Read.Read (XMonad.StackSet.StackSet i l a sid sd)
instance (GHC.Show.Show i, GHC.Show.Show l, GHC.Show.Show sid, GHC.Show.Show sd, GHC.Show.Show a) => GHC.Show.Show (XMonad.StackSet.StackSet i l a sid sd)
instance Data.Foldable.Foldable XMonad.StackSet.Stack
instance Data.Traversable.Traversable XMonad.StackSet.Stack
-- | The X monad, a state monad transformer over IO, for the
-- window manager state, and support routines.
module XMonad.Core
-- | 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.
data X a
type WindowSet = StackSet WorkspaceId (Layout Window) Window ScreenId ScreenDetail
type WindowSpace = Workspace WorkspaceId (Layout Window) Window
-- | Virtual workspace indices
type WorkspaceId = String
-- | Physical screen indices
newtype ScreenId
S :: Int -> ScreenId
-- | The Rectangle with screen dimensions
newtype ScreenDetail
SD :: Rectangle -> ScreenDetail
[screenRect] :: ScreenDetail -> Rectangle
-- | XState, the (mutable) window manager state.
data XState
XState :: !WindowSet -> !Set Window -> !Map Window Int -> !Maybe (Position -> Position -> X (), X ()) -> !KeyMask -> !Map String (Either String StateExtension) -> XState
-- | workspace list
[windowset] :: XState -> !WindowSet
-- | the Set of mapped windows
[mapped] :: XState -> !Set Window
-- | the number of expected UnmapEvents
[waitingUnmap] :: XState -> !Map Window Int
[dragging] :: XState -> !Maybe (Position -> Position -> X (), X ())
-- | The numlock modifier
[numberlockMask] :: XState -> !KeyMask
-- | stores custom state information.
--
-- The module XMonad.Util.ExtensibleState in xmonad-contrib
-- provides additional information and a simple interface for using this.
[extensibleState] :: XState -> !Map String (Either String StateExtension)
-- | XConf, the (read-only) window manager configuration.
data XConf
XConf :: Display -> !XConfig Layout -> !Window -> !Pixel -> !Pixel -> !Map (KeyMask, KeySym) (X ()) -> !Map (KeyMask, Button) (Window -> X ()) -> !Bool -> !Maybe (Position, Position) -> !Maybe Event -> !Directories -> XConf
-- | the X11 display
[display] :: XConf -> Display
-- | initial user configuration
[config] :: XConf -> !XConfig Layout
-- | the root window
[theRoot] :: XConf -> !Window
-- | border color of unfocused windows
[normalBorder] :: XConf -> !Pixel
-- | border color of the focused window
[focusedBorder] :: XConf -> !Pixel
-- | a mapping of key presses to actions
[keyActions] :: XConf -> !Map (KeyMask, KeySym) (X ())
-- | a mapping of button presses to actions
[buttonActions] :: XConf -> !Map (KeyMask, Button) (Window -> X ())
-- | was refocus caused by mouse action?
[mouseFocused] :: XConf -> !Bool
-- | position of the mouse according to the event currently being processed
[mousePosition] :: XConf -> !Maybe (Position, Position)
-- | event currently being processed
[currentEvent] :: XConf -> !Maybe Event
-- | directories to use
[directories] :: XConf -> !Directories
data XConfig l
XConfig :: !String -> !String -> !String -> !l Window -> !ManageHook -> !Event -> X All -> ![String] -> !KeyMask -> !XConfig Layout -> Map (ButtonMask, KeySym) (X ()) -> !XConfig Layout -> Map (ButtonMask, Button) (Window -> X ()) -> !Dimension -> !X () -> !X () -> !Bool -> !Bool -> !EventMask -> !EventMask -> ![String] -> XConfig Layout -> IO (XConfig Layout) -> !Map TypeRep ConfExtension -> XConfig l
-- | Non focused windows border color. Default: "#dddddd"
[normalBorderColor] :: XConfig l -> !String
-- | Focused windows border color. Default: "#ff0000"
[focusedBorderColor] :: XConfig l -> !String
-- | The preferred terminal application. Default: "xterm"
[terminal] :: XConfig l -> !String
-- | The available layouts
[layoutHook] :: XConfig l -> !l Window
-- | The action to run when a new window is opened
[manageHook] :: XConfig l -> !ManageHook
-- | 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.
[handleEventHook] :: XConfig l -> !Event -> X All
-- | The list of workspaces' names
[workspaces] :: XConfig l -> ![String]
-- | the mod modifier
[modMask] :: XConfig l -> !KeyMask
-- | The key binding: a map from key presses and actions
[keys] :: XConfig l -> !XConfig Layout -> Map (ButtonMask, KeySym) (X ())
-- | The mouse bindings
[mouseBindings] :: XConfig l -> !XConfig Layout -> Map (ButtonMask, Button) (Window -> X ())
-- | The border width
[borderWidth] :: XConfig l -> !Dimension
-- | The action to perform when the windows set is changed
[logHook] :: XConfig l -> !X ()
-- | The action to perform on startup
[startupHook] :: XConfig l -> !X ()
-- | Whether window entry events can change focus
[focusFollowsMouse] :: XConfig l -> !Bool
-- | False to make a click which changes focus to be additionally passed to
-- the window
[clickJustFocuses] :: XConfig l -> !Bool
-- | The client events that xmonad is interested in
[clientMask] :: XConfig l -> !EventMask
-- | The root events that xmonad is interested in
[rootMask] :: XConfig l -> !EventMask
-- | Modify the configuration, complain about extra arguments etc. with
-- arguments that are not handled by default
[handleExtraArgs] :: XConfig l -> ![String] -> XConfig Layout -> IO (XConfig Layout)
-- | Stores custom config information.
--
-- The module XMonad.Util.ExtensibleConf in xmonad-contrib
-- provides additional information and a simple interface for using this.
[extensibleConf] :: XConfig l -> !Map TypeRep ConfExtension
-- | 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.
class (Show (layout a), Typeable layout) => LayoutClass 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).
runLayout :: LayoutClass layout a => Workspace WorkspaceId (layout a) a -> Rectangle -> 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.
doLayout :: LayoutClass layout a => layout a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a))
-- | 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.
pureLayout :: LayoutClass layout a => layout a -> Rectangle -> Stack a -> [(a, Rectangle)]
-- | emptyLayout is called when there are no windows.
emptyLayout :: LayoutClass layout a => layout a -> Rectangle -> X ([(a, Rectangle)], 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).
handleMessage :: LayoutClass layout a => layout a -> SomeMessage -> X (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.
pureMessage :: LayoutClass layout a => layout a -> SomeMessage -> Maybe (layout a)
-- | 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.
description :: LayoutClass layout a => layout a -> String
-- | An existential type that can hold any object that is in Read
-- and LayoutClass.
data Layout a
Layout :: l a -> Layout a
-- | Using the Layout as a witness, parse existentially wrapped
-- windows from a String.
readsLayout :: Layout a -> String -> [(Layout a, String)]
-- | The class Typeable allows a concrete representation of a type
-- to be calculated.
class Typeable (a :: k)
-- | 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.
class Typeable a => Message a
-- | A wrapped value of some type in the Message class.
data SomeMessage
SomeMessage :: a -> SomeMessage
-- | And now, unwrap a given, unknown Message type, performing a
-- (dynamic) type check on the result.
fromMessage :: Message m => SomeMessage -> Maybe m
-- | LayoutMessages are core messages that all layouts (especially
-- stateful layouts) should consider handling.
data LayoutMessages
-- | sent when a layout becomes non-visible
Hide :: LayoutMessages
-- | sent when xmonad is exiting or restarting
ReleaseResources :: LayoutMessages
-- | Existential type to store a state extension.
data StateExtension
-- | Non-persistent state extension
StateExtension :: a -> StateExtension
-- | Persistent extension
PersistentExtension :: a -> StateExtension
-- | Every module must make the data it wants to store an instance of this
-- class.
--
-- Minimal complete definition: initialValue
class Typeable a => ExtensionClass a
-- | Defines an initial value for the state extension
initialValue :: ExtensionClass a => a
-- | 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.
extensionType :: ExtensionClass a => a -> StateExtension
-- | Existential type to store a config extension.
data ConfExtension
ConfExtension :: a -> ConfExtension
-- | Run the X monad, given a chunk of X monad code, and an
-- initial state Return the result, and final state
runX :: XConf -> XState -> X a -> IO (a, XState)
-- | Run in the X monad, and in case of exception, and catch it and
-- log it to stderr, and run the error case.
catchX :: X a -> X a -> X a
-- | Execute the argument, catching all exceptions. Either this function or
-- catchX should be used at all callsites of user customized code.
userCode :: X a -> X (Maybe a)
-- | Same as userCode but with a default argument to return instead of
-- using Maybe, provided for convenience.
userCodeDef :: a -> X a -> X a
-- | General utilities
--
-- Lift an IO action into the X monad
io :: MonadIO m => IO a -> m a
-- | 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.
catchIO :: MonadIO m => IO () -> m ()
-- | Ignore SIGPIPE to avoid termination when a pipe is full, and SIGCHLD
-- to avoid zombie processes, and clean up any extant zombie processes.
installSignalHandlers :: MonadIO m => m ()
uninstallSignalHandlers :: MonadIO m => m ()
-- | Run a monad action with the current display settings
withDisplay :: (Display -> X a) -> X a
-- | Run a monadic action with the current stack set
withWindowSet :: (WindowSet -> X a) -> X a
-- | True if the given window is the root window
isRoot :: Window -> X Bool
-- | 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.
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
-- | Wrapper for the common case of atom internment
getAtom :: String -> X Atom
-- | 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.
spawn :: MonadIO m => String -> m ()
-- | Like spawn, but returns the ProcessID of the launched
-- application
spawnPID :: MonadIO m => String -> m ProcessID
-- | A replacement for forkProcess which resets default signal
-- handlers.
xfork :: MonadIO m => IO () -> m ProcessID
-- | Use xmessage to show information to the user.
xmessage :: MonadIO m => String -> m ()
-- | 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)
-- - custom build script is being used
--
--
-- 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.
recompile :: MonadIO m => Directories -> Bool -> m Bool
-- | A trace for the X monad. Logs a string to stderr. The
-- result may be found in your .xsession-errors file
trace :: MonadIO m => String -> m ()
-- | Conditionally run an action, using a Maybe a to decide.
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
-- | Conditionally run an action, using a X event to decide
whenX :: X Bool -> X () -> X ()
-- | Return the path to the xmonad configuration directory.
-- | Deprecated: Use `asks (cfgDir . directories)' instead.
getXMonadDir :: X String
-- | Return the path to the xmonad cache directory.
-- | Deprecated: Use `asks (cacheDir . directories)' instead.
getXMonadCacheDir :: X String
-- | Return the path to the xmonad data directory.
-- | Deprecated: Use `asks (dataDir . directories)' instead.
getXMonadDataDir :: X String
stateFileName :: Directories -> FilePath
binFileName :: Directories -> FilePath
-- | Common non-predefined atoms
atom_WM_STATE :: X Atom
-- | Common non-predefined atoms
atom_WM_PROTOCOLS :: X Atom
-- | Common non-predefined atoms
atom_WM_DELETE_WINDOW :: X Atom
-- | Common non-predefined atoms
atom_WM_TAKE_FOCUS :: X Atom
-- | Safely access window attributes.
withWindowAttributes :: Display -> Window -> (WindowAttributes -> X ()) -> X ()
type ManageHook = Query (Endo WindowSet)
newtype Query a
Query :: ReaderT Window X a -> Query a
runQuery :: Query a -> Window -> X a
-- | 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.
-- - 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 such as the configuration binary and any
-- intermediate object files generated by GHC. Also, the XPrompt history
-- file goes here.
--
--
-- For how these directories are chosen, see getDirectories.
data Directories' a
Directories :: !a -> !a -> !a -> Directories' a
[dataDir] :: Directories' a -> !a
[cfgDir] :: Directories' a -> !a
[cacheDir] :: Directories' a -> !a
-- | Convenient type alias for the most common case in which one might want
-- to use the Directories type.
type Directories = Directories' FilePath
-- | Build up the Dirs that xmonad will use. They are chosen as
-- follows:
--
--
-- - If all three of xmonad's environment variables
-- (XMONAD_DATA_DIR, XMONAD_CONFIG_DIR, and
-- XMONAD_CACHE_DIR) are set, use them.
-- - If there is a build script called build or configuration
-- xmonad.hs in ~/.xmonad, set all three directories to
-- ~/.xmonad.
-- - 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.
getDirectories :: IO Directories
instance GHC.Real.Real XMonad.Core.ScreenId
instance GHC.Real.Integral XMonad.Core.ScreenId
instance GHC.Num.Num XMonad.Core.ScreenId
instance GHC.Enum.Enum XMonad.Core.ScreenId
instance GHC.Read.Read XMonad.Core.ScreenId
instance GHC.Show.Show XMonad.Core.ScreenId
instance GHC.Classes.Ord XMonad.Core.ScreenId
instance GHC.Classes.Eq XMonad.Core.ScreenId
instance GHC.Read.Read XMonad.Core.ScreenDetail
instance GHC.Show.Show XMonad.Core.ScreenDetail
instance GHC.Classes.Eq XMonad.Core.ScreenDetail
instance GHC.Classes.Eq XMonad.Core.LayoutMessages
instance Data.Traversable.Traversable XMonad.Core.Directories'
instance Data.Foldable.Foldable XMonad.Core.Directories'
instance GHC.Base.Functor XMonad.Core.Directories'
instance GHC.Show.Show a => GHC.Show.Show (XMonad.Core.Directories' a)
instance Control.Monad.IO.Class.MonadIO XMonad.Core.Query
instance Control.Monad.Reader.Class.MonadReader Graphics.X11.Types.Window XMonad.Core.Query
instance GHC.Base.Monad XMonad.Core.Query
instance GHC.Base.Applicative XMonad.Core.Query
instance GHC.Base.Functor XMonad.Core.Query
instance Control.Monad.Reader.Class.MonadReader XMonad.Core.XConf XMonad.Core.X
instance Control.Monad.State.Class.MonadState XMonad.Core.XState XMonad.Core.X
instance Control.Monad.IO.Class.MonadIO XMonad.Core.X
instance Control.Monad.Fail.MonadFail XMonad.Core.X
instance GHC.Base.Monad XMonad.Core.X
instance GHC.Base.Applicative XMonad.Core.X
instance GHC.Base.Functor XMonad.Core.X
instance GHC.Show.Show XMonad.Core.Compile
instance GHC.Base.Semigroup a => GHC.Base.Semigroup (XMonad.Core.X a)
instance GHC.Base.Monoid a => GHC.Base.Monoid (XMonad.Core.X a)
instance Data.Default.Class.Default a => Data.Default.Class.Default (XMonad.Core.X a)
instance GHC.Base.Semigroup a => GHC.Base.Semigroup (XMonad.Core.Query a)
instance GHC.Base.Monoid a => GHC.Base.Monoid (XMonad.Core.Query a)
instance Data.Default.Class.Default a => Data.Default.Class.Default (XMonad.Core.Query a)
instance XMonad.Core.LayoutClass XMonad.Core.Layout Graphics.X11.Types.Window
instance GHC.Show.Show (XMonad.Core.Layout a)
instance XMonad.Core.Message XMonad.Core.LayoutMessages
instance XMonad.Core.Message Graphics.X11.Xlib.Extras.Event
-- | The collection of core layouts.
module XMonad.Layout
-- | Simple fullscreen mode. Renders the focused window fullscreen.
data Full a
Full :: Full a
-- | The builtin tiling mode of xmonad. Supports Shrink,
-- Expand and IncMasterN.
data Tall a
Tall :: !Int -> !Rational -> !Rational -> Tall a
-- | The default number of windows in the master pane (default: 1)
[tallNMaster] :: Tall a -> !Int
-- | Percent of screen to increment by when resizing panes (default: 3/100)
[tallRatioIncrement] :: Tall a -> !Rational
-- | Default proportion of screen occupied by master pane (default: 1/2)
[tallRatio] :: Tall a -> !Rational
-- | Mirror a layout, compute its 90 degree rotated form.
newtype Mirror l a
Mirror :: l a -> Mirror l a
-- | Change the size of the master pane.
data Resize
Shrink :: Resize
Expand :: Resize
-- | Increase the number of clients in the master pane.
newtype IncMasterN
IncMasterN :: Int -> IncMasterN
-- | A layout that allows users to switch between various layout options.
data Choose l r a
Choose :: CLR -> l a -> r a -> Choose l r a
-- | The layout choice combinator
(|||) :: l a -> r a -> Choose l r a
infixr 5 |||
-- | Choose the current sub-layout (left or right) in Choose.
data CLR
CL :: CLR
CR :: CLR
-- | Messages to change the current layout. Also see JumpToLayout.
data ChangeLayout
FirstLayout :: ChangeLayout
NextLayout :: ChangeLayout
-- | A message to jump to a particular layout, specified by its description
-- string.
--
-- The argument given to a JumpToLayout message should be the
-- description of the layout to be selected. If you use
-- XMonad.Hooks.DynamicLog from xmonad-contrib, this is
-- the name of the layout displayed in your status bar. Alternatively,
-- you can use GHCi to determine the proper name to use. For example:
--
--
-- $ ghci
-- GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help
-- Loading package base ... linking ... done.
-- :set prompt "> " -- don't show loaded module names
-- > :m +XMonad.Core -- load the xmonad core
-- > :m +XMonad.Layout.Grid -- load whatever module you want to use
-- > description Grid -- find out what it's called
-- "Grid"
--
--
-- As yet another (possibly easier) alternative, you can use the
-- XMonad.Layout.Renamed module (also in xmonad-contrib)
-- to give custom names to your layouts, and use those.
--
-- For example, if you want to jump directly to the Full layout
-- you can do
--
--
-- , ((modm .|. controlMask, xK_f), sendMessage $ JumpToLayout "Full")
--
newtype JumpToLayout
JumpToLayout :: String -> JumpToLayout
-- | Mirror a rectangle.
mirrorRect :: Rectangle -> Rectangle
splitVertically :: Int -> Rectangle -> [Rectangle]
splitHorizontally :: Int -> Rectangle -> [Rectangle]
splitHorizontallyBy :: RealFrac r => r -> Rectangle -> (Rectangle, Rectangle)
splitVerticallyBy :: RealFrac r => r -> Rectangle -> (Rectangle, Rectangle)
-- | Compute the positions for windows using the default two-pane tiling
-- algorithm.
--
-- The screen is divided into two panes. All clients are then partitioned
-- between these two panes. One pane, the master, by convention has the
-- least number of windows in it.
tile :: Rational -> Rectangle -> Int -> Int -> [Rectangle]
instance GHC.Read.Read (XMonad.Layout.Full a)
instance GHC.Show.Show (XMonad.Layout.Full a)
instance GHC.Read.Read (XMonad.Layout.Tall a)
instance GHC.Show.Show (XMonad.Layout.Tall a)
instance GHC.Read.Read (l a) => GHC.Read.Read (XMonad.Layout.Mirror l a)
instance GHC.Show.Show (l a) => GHC.Show.Show (XMonad.Layout.Mirror l a)
instance GHC.Show.Show XMonad.Layout.ChangeLayout
instance GHC.Classes.Eq XMonad.Layout.ChangeLayout
instance GHC.Classes.Eq XMonad.Layout.CLR
instance GHC.Show.Show XMonad.Layout.CLR
instance GHC.Read.Read XMonad.Layout.CLR
instance (GHC.Show.Show (l a), GHC.Show.Show (r a)) => GHC.Show.Show (XMonad.Layout.Choose l r a)
instance (GHC.Read.Read (l a), GHC.Read.Read (r a)) => GHC.Read.Read (XMonad.Layout.Choose l r a)
instance GHC.Show.Show XMonad.Layout.NextNoWrap
instance GHC.Classes.Eq XMonad.Layout.NextNoWrap
instance XMonad.Core.Message XMonad.Layout.NextNoWrap
instance (XMonad.Core.LayoutClass l a, XMonad.Core.LayoutClass r a) => XMonad.Core.LayoutClass (XMonad.Layout.Choose l r) a
instance XMonad.Core.Message XMonad.Layout.JumpToLayout
instance XMonad.Core.Message XMonad.Layout.ChangeLayout
instance XMonad.Core.LayoutClass l a => XMonad.Core.LayoutClass (XMonad.Layout.Mirror l) a
instance XMonad.Core.LayoutClass XMonad.Layout.Tall a
instance XMonad.Core.LayoutClass XMonad.Layout.Full a
instance XMonad.Core.Message XMonad.Layout.IncMasterN
instance XMonad.Core.Message XMonad.Layout.Resize
-- | Operations. A module for functions that don't cleanly fit anywhere
-- else.
module XMonad.Operations
-- | Add a new window to be managed in the current workspace. Bring it into
-- focus.
--
-- Whether the window is already managed, or not, it is mapped, has its
-- border set, and its event mask set.
manage :: Window -> X ()
-- | A window no longer exists; remove it from the window list, on whatever
-- workspace it is.
unmanage :: Window -> X ()
-- | Kill the specified window. If we do kill it, we'll get a delete notify
-- back from X.
--
-- There are two ways to delete a window. Either just kill it, or if it
-- supports the delete protocol, send a delete event (e.g. firefox)
killWindow :: Window -> X ()
-- | Kill the currently focused client.
kill :: X ()
-- | Is the window is under management by xmonad?
isClient :: Window -> X Bool
-- | Set some properties when we initially gain control of a window.
setInitialProperties :: Window -> X ()
-- | Set a window's WM_STATE property.
setWMState :: Window -> Int -> X ()
-- | Set the border color using the window's color map, if possible;
-- otherwise fall back to the color in Pixel.
setWindowBorderWithFallback :: Display -> Window -> String -> Pixel -> X ()
-- | Hide a window by unmapping it and setting Iconified.
hide :: Window -> X ()
-- | Show a window by mapping it and setting Normal. This is harmless if
-- the window was already visible.
reveal :: Window -> X ()
-- | Move and resize w such that it fits inside the given
-- rectangle, including its border.
tileWindow :: Window -> Rectangle -> X ()
-- | Set the focus to the window on top of the stack, or root
setTopFocus :: X ()
-- | Set focus explicitly to window w if it is managed by us, or
-- root. This happens if X notices we've moved the mouse (and perhaps
-- moved the mouse to a new screen).
focus :: Window -> X ()
-- | Detect whether a window has fixed size or is transient. This check can
-- be used to determine whether the window should be floating or not
isFixedSizeOrTransient :: Display -> Window -> X Bool
-- | Modify the current window list with a pure function, and refresh
windows :: (WindowSet -> WindowSet) -> X ()
-- | Render the currently visible workspaces, as determined by the
-- StackSet. Also, set focus to the focused window.
--
-- This is our view operation (MVC), in that it pretty prints
-- our model with X calls.
refresh :: X ()
-- | The screen configuration may have changed (due to -- xrandr), update
-- the state and refresh the screen, and reset the gap.
rescreen :: X ()
-- | Modify the WindowSet in state with no special handling.
modifyWindowSet :: (WindowSet -> WindowSet) -> X ()
-- | Perform an X action and check its return value against a
-- predicate p. If p holds, unwind changes to the WindowSet and
-- replay them using windows.
windowBracket :: (a -> Bool) -> X a -> X a
-- | Perform an X action. If it returns Any True, unwind
-- the changes to the WindowSet and replay them using
-- windows. This is a version of windowBracket that
-- discards the return value and handles an X action that
-- reports its need for refresh via Any.
windowBracket_ :: X Any -> X ()
-- | Remove all events of a given type from the event queue.
clearEvents :: EventMask -> X ()
-- | Clean the list of screens according to the rules documented for
-- nubScreens.
getCleanedScreenInfo :: MonadIO m => Display -> m [Rectangle]
-- | Apply an X operation to the currently focused window, if there
-- is one.
withFocused :: (Window -> X ()) -> X ()
-- | Apply an X operation to all unfocused windows on the current
-- workspace, if there are any.
withUnfocused :: (Window -> X ()) -> X ()
-- | Strip numlock/capslock from a mask.
cleanMask :: KeyMask -> X KeyMask
-- | Combinations of extra modifier masks we need to grab keys/buttons for.
-- (numlock and capslock)
extraModifiers :: X [KeyMask]
-- | Accumulate mouse motion events
mouseDrag :: (Position -> Position -> X ()) -> X () -> X ()
-- | Drag the window under the cursor with the mouse while it is dragged.
mouseMoveWindow :: Window -> X ()
-- | Resize the window under the cursor with the mouse while it is dragged.
mouseResizeWindow :: Window -> X ()
-- | Tell whether or not to intercept clicks on a given window
setButtonGrab :: Bool -> Window -> X ()
-- | Call X to set the keyboard focus details.
setFocusX :: Window -> X ()
cacheNumlockMask :: X ()
-- | Given a list of keybindings, turn the given KeySyms into actual
-- KeyCodes and prepare them for grabbing.
mkGrabs :: [(KeyMask, KeySym)] -> X [(KeyMask, KeyCode)]
-- | Throw a message to the current LayoutClass possibly modifying
-- how we layout the windows, in which case changes are handled through a
-- refresh.
sendMessage :: Message a => a -> X ()
-- | Send a message to all layouts, without refreshing.
broadcastMessage :: Message a => a -> X ()
-- | Send a message to a layout, without refreshing.
sendMessageWithNoRefresh :: Message a => a -> WindowSpace -> X ()
-- | A type to help serialize xmonad's state to a file.
data StateFile
StateFile :: StackSet WorkspaceId String Window ScreenId ScreenDetail -> [(String, String)] -> StateFile
[sfWins] :: StateFile -> StackSet WorkspaceId String Window ScreenId ScreenDetail
[sfExt] :: StateFile -> [(String, String)]
-- | Write the current window state (and extensible state) to a file so
-- that xmonad can resume with that state intact.
writeStateToFile :: X ()
-- | Read the state of a previous xmonad instance from a file and return
-- that state. The state file is removed after reading it.
readStateFile :: (LayoutClass l Window, Read (l Window)) => XConfig l -> X (Maybe XState)
-- | restart name resume attempts to restart xmonad by executing
-- the program name. If resume is True, restart
-- with the current window state. When executing another window manager,
-- resume should be False.
restart :: String -> Bool -> X ()
-- | Make a tiled window floating, using its suggested rectangle
float :: Window -> X ()
-- | Given a window, find the screen it is located on, and compute the
-- geometry of that window WRT that screen.
floatLocation :: Window -> X (ScreenId, RationalRect)
-- | An alias for a (width, height) pair
type D = (Dimension, Dimension)
-- | Given a window, build an adjuster function that will reduce the given
-- dimensions according to the window's border width and size hints.
mkAdjust :: Window -> X (D -> D)
-- | Reduce the dimensions if needed to comply to the given SizeHints,
-- taking window borders into account.
applySizeHints :: Integral a => Dimension -> SizeHints -> (a, a) -> D
-- | Use X11 size hints to scale a pair of dimensions.
applySizeHints' :: SizeHints -> D -> D
-- | Reduce the dimensions if needed to comply to the given SizeHints.
applySizeHintsContents :: Integral a => SizeHints -> (a, a) -> D
-- | Reduce the dimensions so their aspect ratio falls between the two
-- given aspect ratios.
applyAspectHint :: (D, D) -> D -> D
-- | Reduce the dimensions so they are a multiple of the size increments.
applyResizeIncHint :: D -> D -> D
-- | Reduce the dimensions if they exceed the given maximum dimensions.
applyMaxSizeHint :: D -> D -> D
-- | Returns True if the first rectangle is contained within, but
-- not equal to the second.
containedIn :: Rectangle -> Rectangle -> Bool
-- | Given a list of screens, remove all duplicated screens and screens
-- that are entirely contained within another.
nubScreens :: [Rectangle] -> [Rectangle]
-- | pointWithin x y r returns True if the (x, y)
-- co-ordinate is within r.
pointWithin :: Position -> Position -> Rectangle -> Bool
-- | Produce the actual rectangle from a screen and a ratio on that screen.
scaleRationalRect :: Rectangle -> RationalRect -> Rectangle
-- | Get the Pixel value for a named color.
initColor :: Display -> String -> IO (Maybe Pixel)
-- | Given a point, determine the screen (if any) that contains it.
pointScreen :: Position -> Position -> X (Maybe (Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail))
-- | Return workspace visible on screen sc, or Nothing.
screenWorkspace :: ScreenId -> X (Maybe WorkspaceId)
-- | Set the layout of the currently viewed workspace.
setLayout :: Layout Window -> X ()
-- | Update the layout field of a workspace.
updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X ()
instance GHC.Read.Read XMonad.Operations.StateFile
instance GHC.Show.Show XMonad.Operations.StateFile
-- | An EDSL for ManageHooks
module XMonad.ManageHook
-- | Lift an X action to a Query.
liftX :: X a -> Query a
-- | The identity hook that returns the WindowSet unchanged.
idHook :: Monoid m => m
-- | Infix mappend. Compose two ManageHook from right to
-- left.
(<+>) :: Monoid m => m -> m -> m
-- | Compose the list of ManageHooks.
composeAll :: Monoid m => [m] -> m
-- | p --> x. If p returns True, execute the
-- ManageHook.
--
--
-- (-->) :: Monoid m => Query Bool -> Query m -> Query m -- a simpler type
--
(-->) :: (Monad m, Monoid a) => m Bool -> m a -> m a
infix 0 -->
-- | q =? x. if the result of q equals x, return
-- True.
(=?) :: Eq a => Query a -> a -> Query Bool
-- | && lifted to a Monad.
(<&&>) :: Monad m => m Bool -> m Bool -> m Bool
infixr 3 <&&>
-- | || lifted to a Monad.
(<||>) :: Monad m => m Bool -> m Bool -> m Bool
infixr 3 <||>
-- | If-then-else lifted to a Monad.
ifM :: Monad m => m Bool -> m a -> m a -> m a
-- | Return the window title.
title :: Query String
-- | Return the application name; i.e., the first string returned by
-- WM_CLASS.
appName :: Query String
-- | Backwards compatible alias for appName.
resource :: Query String
-- | Return the resource class; i.e., the second string returned by
-- WM_CLASS.
className :: Query String
-- | A query that can return an arbitrary X property of type String,
-- identified by name.
stringProperty :: String -> Query String
getStringProperty :: Display -> Window -> String -> X (Maybe String)
-- | Return whether the window will be a floating window or not
willFloat :: Query Bool
-- | Modify the WindowSet with a pure function.
doF :: (s -> s) -> Query (Endo s)
-- | Move the window to the floating layer.
doFloat :: ManageHook
-- | Map the window and remove it from the WindowSet.
doIgnore :: ManageHook
-- | Move the window to a given workspace
doShift :: WorkspaceId -> ManageHook
-- | This module specifies the default configuration values for xmonad.
--
-- DO NOT MODIFY THIS FILE! It won't work. You may configure xmonad by
-- providing your own ~/.xmonad/xmonad.hs that overrides
-- specific fields in the default config, def. For a starting
-- point, you can copy the xmonad.hs found in the man
-- directory, or look at examples on the xmonad wiki.
module XMonad.Config
-- | The default set of configuration values itself
-- | Deprecated: Use def (from Data.Default, and re-exported by XMonad
-- and XMonad.Config) instead.
defaultConfig :: XConfig (Choose Tall (Choose (Mirror Tall) Full))
-- | A class for types with a default value.
class Default a
-- | The default value for this type.
def :: Default a => a
instance (a GHC.Types.~ XMonad.Layout.Choose XMonad.Layout.Tall (XMonad.Layout.Choose (XMonad.Layout.Mirror XMonad.Layout.Tall) XMonad.Layout.Full)) => Data.Default.Class.Default (XMonad.Core.XConfig a)
-- | xmonad, a minimalist, tiling window manager for X11
module XMonad.Main
-- | | The entry point into xmonad. Attempts to compile any custom main for
-- xmonad, and if it doesn't find one, just launches the default.
xmonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO ()
-- | Entry point into xmonad for custom builds.
--
-- This function isn't meant to be called by the typical xmonad user
-- because it:
--
--
-- - Does not process any command line arguments.
-- - Therefore doesn't know how to restart a running xmonad.
-- - Does not compile your configuration file since it assumes it's
-- actually running from within your compiled configuration.
--
--
-- Unless you know what you are doing, you should probably be using the
-- xmonad function instead.
--
-- However, if you are using a custom build environment (such as stack,
-- cabal, make, etc.) you will likely want to call this function instead
-- of xmonad. You probably also want to have a key binding to the
-- restart function that restarts your custom binary with the
-- resume flag set to True.
launch :: (LayoutClass l Window, Read (l Window)) => XConfig l -> Directories -> IO ()
module XMonad
-- | interface to the X11 library function XRestackWindows().
restackWindows :: Display -> [Window] -> IO ()
-- | interface to the X11 library function XWithdrawWindow().
withdrawWindow :: Display -> Window -> ScreenNumber -> IO ()
-- | interface to the X11 library function XIconifyWindow().
iconifyWindow :: Display -> Window -> ScreenNumber -> IO ()
-- | interface to the X11 library function
-- XTranslateCoordinates().
translateCoordinates :: Display -> Window -> Window -> Position -> Position -> IO (Bool, Position, Position, Window)
-- | interface to the X11 library function XStoreName().
storeName :: Display -> Window -> String -> IO ()
-- | interface to the X11 library function XCreateSimpleWindow().
createSimpleWindow :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> CInt -> Pixel -> Pixel -> IO Window
-- | interface to the X11 library function XCreateWindow().
createWindow :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> CInt -> CInt -> WindowClass -> Visual -> AttributeMask -> Ptr SetWindowAttributes -> IO Window
-- | interface to the X11 library function XMoveResizeWindow().
moveResizeWindow :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> IO ()
-- | interface to the X11 library function XResizeWindow().
resizeWindow :: Display -> Window -> Dimension -> Dimension -> IO ()
-- | interface to the X11 library function XMoveWindow().
moveWindow :: Display -> Window -> Position -> Position -> IO ()
-- | interface to the X11 library function XReparentWindow().
reparentWindow :: Display -> Window -> Window -> Position -> Position -> IO ()
-- | interface to the X11 library function XMapSubwindows().
mapSubwindows :: Display -> Window -> IO ()
-- | interface to the X11 library function XUnmapSubwindows().
unmapSubwindows :: Display -> Window -> IO ()
-- | interface to the X11 library function XMapWindow().
mapWindow :: Display -> Window -> IO ()
-- | interface to the X11 library function XLowerWindow().
lowerWindow :: Display -> Window -> IO ()
-- | interface to the X11 library function XRaiseWindow().
raiseWindow :: Display -> Window -> IO ()
-- | interface to the X11 library function
-- XCirculateSubwindowsDown().
circulateSubwindowsDown :: Display -> Window -> IO ()
-- | interface to the X11 library function
-- XCirculateSubwindowsUp().
circulateSubwindowsUp :: Display -> Window -> IO ()
-- | interface to the X11 library function XCirculateSubwindows().
circulateSubwindows :: Display -> Window -> CirculationDirection -> IO ()
-- | interface to the X11 library function XDestroyWindow().
destroyWindow :: Display -> Window -> IO ()
-- | interface to the X11 library function XDestroySubwindows().
destroySubwindows :: Display -> Window -> IO ()
-- | interface to the X11 library function XSetWindowBorder().
setWindowBorder :: Display -> Window -> Pixel -> IO ()
-- | interface to the X11 library function
-- XSetWindowBorderPixmap().
setWindowBorderPixmap :: Display -> Window -> Pixmap -> IO ()
-- | interface to the X11 library function
-- XSetWindowBorderWidth().
setWindowBorderWidth :: Display -> Window -> Dimension -> IO ()
-- | interface to the X11 library function XSetWindowBackground().
setWindowBackground :: Display -> Window -> Pixel -> IO ()
-- | interface to the X11 library function
-- XSetWindowBackgroundPixmap().
setWindowBackgroundPixmap :: Display -> Window -> Pixmap -> IO ()
-- | interface to the X11 library function XSetWindowColormap().
setWindowColormap :: Display -> Window -> Colormap -> IO ()
-- | interface to the X11 library function XAddToSaveSet().
addToSaveSet :: Display -> Window -> IO ()
-- | interface to the X11 library function XRemoveFromSaveSet().
removeFromSaveSet :: Display -> Window -> IO ()
-- | interface to the X11 library function XChangeSaveSet().
changeSaveSet :: Display -> Window -> ChangeSaveSetMode -> IO ()
-- | interface to the X11 library function XClearWindow().
clearWindow :: Display -> Window -> IO ()
-- | interface to the X11 library function XClearArea().
clearArea :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> Bool -> IO ()
-- | interface to the X11 library function XSetTextProperty().
setTextProperty :: Display -> Window -> String -> Atom -> IO ()
-- | interface to the X11 library function XRotateBuffers().
rotateBuffers :: Display -> CInt -> IO ()
-- | interface to the X11 library function XFetchBytes().
fetchBytes :: Display -> IO String
-- | interface to the X11 library function XFetchBuffer().
fetchBuffer :: Display -> CInt -> IO String
-- | interface to the X11 library function XStoreBytes().
storeBytes :: Display -> String -> IO ()
-- | interface to the X11 library function XStoreBuffer().
storeBuffer :: Display -> String -> CInt -> IO ()
-- | interface to the X11 library function XDrawImageString().
drawImageString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO ()
-- | interface to the X11 library function XDrawString().
drawString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO ()
-- | interface to the X11 library function XFillArcs().
fillArcs :: Display -> Drawable -> GC -> [Arc] -> IO ()
-- | interface to the X11 library function XFillPolygon().
fillPolygon :: Display -> Drawable -> GC -> [Point] -> PolygonShape -> CoordinateMode -> IO ()
-- | interface to the X11 library function XFillRectangles().
fillRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO ()
-- | interface to the X11 library function XDrawArcs().
drawArcs :: Display -> Drawable -> GC -> [Arc] -> IO ()
-- | interface to the X11 library function XDrawRectangles().
drawRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO ()
-- | interface to the X11 library function XDrawSegments().
drawSegments :: Display -> Drawable -> GC -> [Segment] -> IO ()
-- | interface to the X11 library function XDrawLines().
drawLines :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO ()
-- | interface to the X11 library function XDrawPoints().
drawPoints :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO ()
set_cursor :: Ptr SetWindowAttributes -> Cursor -> IO ()
set_colormap :: Ptr SetWindowAttributes -> Colormap -> IO ()
set_override_redirect :: Ptr SetWindowAttributes -> Bool -> IO ()
set_do_not_propagate_mask :: Ptr SetWindowAttributes -> EventMask -> IO ()
set_event_mask :: Ptr SetWindowAttributes -> EventMask -> IO ()
set_save_under :: Ptr SetWindowAttributes -> Bool -> IO ()
set_backing_pixel :: Ptr SetWindowAttributes -> Pixel -> IO ()
set_backing_planes :: Ptr SetWindowAttributes -> Pixel -> IO ()
set_backing_store :: Ptr SetWindowAttributes -> BackingStore -> IO ()
set_win_gravity :: Ptr SetWindowAttributes -> WindowGravity -> IO ()
set_bit_gravity :: Ptr SetWindowAttributes -> BitGravity -> IO ()
set_border_pixel :: Ptr SetWindowAttributes -> Pixel -> IO ()
set_border_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO ()
set_background_pixel :: Ptr SetWindowAttributes -> Pixel -> IO ()
set_background_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO ()
allocaSetWindowAttributes :: (Ptr SetWindowAttributes -> IO a) -> IO a
-- | interface to the X11 library function XSetWMProtocols().
setWMProtocols :: Display -> Window -> [Atom] -> IO ()
-- | interface to the X11 library function XRecolorCursor().
recolorCursor :: Display -> Cursor -> Color -> Color -> IO ()
-- | interface to the X11 library function XCreateGlyphCursor().
createGlyphCursor :: Display -> Font -> Font -> Glyph -> Glyph -> Color -> Color -> IO Cursor
-- | interface to the X11 library function XCreatePixmapCursor().
createPixmapCursor :: Display -> Pixmap -> Pixmap -> Color -> Color -> Dimension -> Dimension -> IO Cursor
-- | interface to the X11 library function XSetIconName().
setIconName :: Display -> Window -> String -> IO ()
-- | interface to the X11 library function XGetIconName().
getIconName :: Display -> Window -> IO String
-- | interface to the X11 library function XLookupString().
lookupString :: XKeyEventPtr -> IO (Maybe KeySym, String)
noSymbol :: KeySym
-- | interface to the X11 library function XStringToKeysym().
stringToKeysym :: String -> KeySym
-- | interface to the X11 library function XKeysymToString().
keysymToString :: KeySym -> String
-- | interface to the X11 library function XDisplayKeycodes().
displayKeycodes :: Display -> (CInt, CInt)
-- | interface to the X11 library function XReadBitmapFile.
readBitmapFile :: Display -> Drawable -> String -> IO (Either String (Dimension, Dimension, Pixmap, Maybe CInt, Maybe CInt))
-- | interface to the X11 library function XMatchVisualInfo()
matchVisualInfo :: Display -> ScreenNumber -> CInt -> CInt -> IO (Maybe VisualInfo)
getVisualInfo :: Display -> VisualInfoMask -> VisualInfo -> IO [VisualInfo]
visualAllMask :: VisualInfoMask
visualBitsPerRGBMask :: VisualInfoMask
visualColormapSizeMask :: VisualInfoMask
-- | interface to the X11 library function XGetVisualInfo()
visualBlueMaskMask :: VisualInfoMask
visualGreenMaskMask :: VisualInfoMask
visualRedMaskMask :: VisualInfoMask
visualClassMask :: VisualInfoMask
visualDepthMask :: VisualInfoMask
visualScreenMask :: VisualInfoMask
visualIDMask :: VisualInfoMask
visualNoMask :: VisualInfoMask
-- | interface to the X11 library function XGetPointerControl().
getPointerControl :: Display -> IO (CInt, CInt, CInt)
getScreenSaver :: Display -> IO (CInt, CInt, PreferBlankingMode, AllowExposuresMode)
screenSaverReset :: ScreenSaverMode
screenSaverActive :: ScreenSaverMode
defaultBlanking :: PreferBlankingMode
preferBlanking :: PreferBlankingMode
dontPreferBlanking :: PreferBlankingMode
defaultExposures :: AllowExposuresMode
allowExposures :: AllowExposuresMode
dontAllowExposures :: AllowExposuresMode
-- | interface to the X11 library function XSetLocaleModifiers().
setLocaleModifiers :: String -> IO String
-- | interface to the X11 library function XGetGeometry().
getGeometry :: Display -> Drawable -> IO (Window, Position, Position, Dimension, Dimension, Dimension, CInt)
-- | interface to the X11 library function XGeometry().
geometry :: Display -> CInt -> String -> String -> Dimension -> Dimension -> Dimension -> CInt -> CInt -> IO (CInt, Position, Position, Dimension, Dimension)
-- | The Xlib library reports most errors by invoking a user-provided error
-- handler. This function installs an error handler that prints a textual
-- representation of the error.
setDefaultErrorHandler :: IO ()
-- | interface to the X11 library function XDisplayName().
displayName :: String -> String
-- | interface to the X11 library function XQueryPointer().
queryPointer :: Display -> Window -> IO (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier)
-- | interface to the X11 library function XQueryBestSize().
queryBestSize :: Display -> QueryBestSizeClass -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension)
-- | interface to the X11 library function XQueryBestCursor().
queryBestCursor :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension)
-- | interface to the X11 library function XQueryBestStipple().
queryBestStipple :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension)
-- | interface to the X11 library function XQueryBestTile().
queryBestTile :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension)
-- | interface to the X11 library function XGetInputFocus().
getInputFocus :: Display -> IO (Window, FocusMode)
-- | interface to the X11 library function XrmInitialize().
rmInitialize :: IO ()
-- | interface to the X11 library function XAutoRepeatOff().
autoRepeatOff :: Display -> IO ()
-- | interface to the X11 library function XAutoRepeatOn().
autoRepeatOn :: Display -> IO ()
-- | interface to the X11 library function XBell().
bell :: Display -> CInt -> IO ()
-- | interface to the X11 library function XSetCloseDownMode().
setCloseDownMode :: Display -> CloseDownMode -> IO ()
-- | interface to the X11 library function
-- XLastKnownRequestProcessed().
lastKnownRequestProcessed :: Display -> IO CInt
-- | interface to the X11 library function XSetInputFocus().
setInputFocus :: Display -> Window -> FocusMode -> Time -> IO ()
-- | interface to the X11 library function XGrabButton().
grabButton :: Display -> Button -> ButtonMask -> Window -> Bool -> EventMask -> GrabMode -> GrabMode -> Window -> Cursor -> IO ()
-- | interface to the X11 library function XUngrabButton().
ungrabButton :: Display -> Button -> ButtonMask -> Window -> IO ()
-- | interface to the X11 library function XGrabPointer().
grabPointer :: Display -> Window -> Bool -> EventMask -> GrabMode -> GrabMode -> Window -> Cursor -> Time -> IO GrabStatus
-- | interface to the X11 library function XUngrabPointer().
ungrabPointer :: Display -> Time -> IO ()
-- | interface to the X11 library function XGrabKey().
grabKey :: Display -> KeyCode -> KeyMask -> Window -> Bool -> GrabMode -> GrabMode -> IO ()
-- | interface to the X11 library function XUngrabKey().
ungrabKey :: Display -> KeyCode -> KeyMask -> Window -> IO ()
-- | interface to the X11 library function XGrabKeyboard().
grabKeyboard :: Display -> Window -> Bool -> GrabMode -> GrabMode -> Time -> IO GrabStatus
-- | interface to the X11 library function XUngrabKeyboard().
ungrabKeyboard :: Display -> Time -> IO ()
-- | interface to the X11 library function XGrabServer().
grabServer :: Display -> IO ()
-- | interface to the X11 library function XUngrabServer().
ungrabServer :: Display -> IO ()
-- | interface to the X11 library function XSupportsLocale().
supportsLocale :: IO Bool
-- | interface to the X11 library function XSetScreenSaver().
setScreenSaver :: Display -> CInt -> CInt -> PreferBlankingMode -> AllowExposuresMode -> IO ()
-- | interface to the X11 library function XActivateScreenSaver().
activateScreenSaver :: Display -> IO ()
-- | interface to the X11 library function XResetScreenSaver().
resetScreenSaver :: Display -> IO ()
-- | interface to the X11 library function XForceScreenSaver().
forceScreenSaver :: Display -> ScreenSaverMode -> IO ()
-- | interface to the X11 library function XWarpPointer().
warpPointer :: Display -> Window -> Window -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> IO ()
-- | see XVisualIDFromVisual()
visualIDFromVisual :: Visual -> IO VisualID
initThreads :: IO Status
lockDisplay :: Display -> IO ()
unlockDisplay :: Display -> IO ()
-- | interface to the X11 library function XCreatePixmap().
createPixmap :: Display -> Drawable -> Dimension -> Dimension -> CInt -> IO Pixmap
-- | interface to the X11 library function XFreePixmap().
freePixmap :: Display -> Pixmap -> IO ()
-- | interface to the X11 library function XBitmapBitOrder().
bitmapBitOrder :: Display -> ByteOrder
-- | interface to the X11 library function XBitmapUnit().
bitmapUnit :: Display -> CInt
-- | interface to the X11 library function XBitmapPad().
bitmapPad :: Display -> CInt
-- | interface to the X11 library function XLookupKeysym().
lookupKeysym :: XKeyEventPtr -> CInt -> IO KeySym
-- | interface to the X11 library function XKeycodeToKeysym().
keycodeToKeysym :: Display -> KeyCode -> CInt -> IO KeySym
-- | interface to the X11 library function XKeysymToKeycode().
keysymToKeycode :: Display -> KeySym -> IO KeyCode
-- | interface to the X11 library function XDefineCursor().
defineCursor :: Display -> Window -> Cursor -> IO ()
-- | interface to the X11 library function XUndefineCursor().
undefineCursor :: Display -> Window -> IO ()
-- | interface to the X11 library function XCreateFontCursor().
createFontCursor :: Display -> Glyph -> IO Cursor
-- | interface to the X11 library function XFreeCursor().
freeCursor :: Display -> Font -> IO ()
-- | interface to the X11 library function XDrawPoint().
drawPoint :: Display -> Drawable -> GC -> Position -> Position -> IO ()
-- | interface to the X11 library function XDrawLine().
drawLine :: Display -> Drawable -> GC -> Position -> Position -> Position -> Position -> IO ()
-- | interface to the X11 library function XDrawRectangle().
drawRectangle :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> IO ()
-- | interface to the X11 library function XDrawArc().
drawArc :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> IO ()
-- | interface to the X11 library function XFillRectangle().
fillRectangle :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> IO ()
-- | interface to the X11 library function XFillArc().
fillArc :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> IO ()
-- | interface to the X11 library function XCopyArea().
copyArea :: Display -> Drawable -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> IO ()
-- | interface to the X11 library function XCopyPlane().
copyPlane :: Display -> Drawable -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> Pixel -> IO ()
type AllowExposuresMode = CInt
type PreferBlankingMode = CInt
type ScreenSaverMode = CInt
type VisualInfoMask = CLong
lAST_PREDEFINED :: Atom
wM_TRANSIENT_FOR :: Atom
wM_CLASS :: Atom
cAP_HEIGHT :: Atom
fULL_NAME :: Atom
fAMILY_NAME :: Atom
fONT_NAME :: Atom
nOTICE :: Atom
cOPYRIGHT :: Atom
rESOLUTION :: Atom
pOINT_SIZE :: Atom
wEIGHT :: Atom
qUAD_WIDTH :: Atom
x_HEIGHT :: Atom
iTALIC_ANGLE :: Atom
sTRIKEOUT_DESCENT :: Atom
sTRIKEOUT_ASCENT :: Atom
uNDERLINE_THICKNESS :: Atom
uNDERLINE_POSITION :: Atom
sUBSCRIPT_Y :: Atom
sUBSCRIPT_X :: Atom
sUPERSCRIPT_Y :: Atom
sUPERSCRIPT_X :: Atom
eND_SPACE :: Atom
mAX_SPACE :: Atom
nORM_SPACE :: Atom
mIN_SPACE :: Atom
wM_ZOOM_HINTS :: Atom
wM_SIZE_HINTS :: Atom
wM_NORMAL_HINTS :: Atom
wM_NAME :: Atom
wM_ICON_SIZE :: Atom
wM_ICON_NAME :: Atom
wM_CLIENT_MACHINE :: Atom
wM_HINTS :: Atom
wM_COMMAND :: Atom
wINDOW :: Atom
vISUALID :: Atom
sTRING :: Atom
rGB_RED_MAP :: Atom
rGB_GREEN_MAP :: Atom
rGB_GRAY_MAP :: Atom
rGB_DEFAULT_MAP :: Atom
rGB_BLUE_MAP :: Atom
rGB_BEST_MAP :: Atom
rGB_COLOR_MAP :: Atom
rESOURCE_MANAGER :: Atom
rECTANGLE :: Atom
pOINT :: Atom
pIXMAP :: Atom
iNTEGER :: Atom
fONT :: Atom
dRAWABLE :: Atom
cUT_BUFFER7 :: Atom
cUT_BUFFER6 :: Atom
cUT_BUFFER5 :: Atom
cUT_BUFFER4 :: Atom
cUT_BUFFER3 :: Atom
cUT_BUFFER2 :: Atom
cUT_BUFFER1 :: Atom
cUT_BUFFER0 :: Atom
cURSOR :: Atom
cOLORMAP :: Atom
cARDINAL :: Atom
bITMAP :: Atom
aTOM :: Atom
aRC :: Atom
sECONDARY :: Atom
pRIMARY :: Atom
getAtomNames :: Display -> [Atom] -> IO [String]
getAtomName :: Display -> Atom -> IO (Maybe String)
-- | interface to the X11 library function XInternAtom().
internAtom :: Display -> String -> Bool -> IO Atom
-- | interface to the X11 library function XQueryColors().
queryColors :: Display -> Colormap -> [Color] -> IO [Color]
-- | interface to the X11 library function XQueryColor().
queryColor :: Display -> Colormap -> Color -> IO Color
-- | interface to the X11 library function XStoreColor().
storeColor :: Display -> Colormap -> Color -> IO ()
-- | interface to the X11 library function XFreeColors().
freeColors :: Display -> Colormap -> [Pixel] -> Pixel -> IO ()
-- | interface to the X11 library function XParseColor().
parseColor :: Display -> Colormap -> String -> IO Color
-- | interface to the X11 library function XAllocColor().
allocColor :: Display -> Colormap -> Color -> IO Color
-- | interface to the X11 library function XAllocNamedColor().
allocNamedColor :: Display -> Colormap -> String -> IO (Color, Color)
-- | interface to the X11 library function XLookupColor().
lookupColor :: Display -> Colormap -> String -> IO (Color, Color)
-- | interface to the X11 library function XInstallColormap().
installColormap :: Display -> Colormap -> IO ()
-- | interface to the X11 library function XUninstallColormap().
uninstallColormap :: Display -> Colormap -> IO ()
-- | interface to the X11 library function XCopyColormapAndFree().
copyColormapAndFree :: Display -> Colormap -> IO Colormap
-- | interface to the X11 library function XCreateColormap().
createColormap :: Display -> Window -> Visual -> ColormapAlloc -> IO Colormap
-- | interface to the X11 library function XFreeColormap().
freeColormap :: Display -> Colormap -> IO ()
-- | partial interface to the X11 library function XCreateGC().
createGC :: Display -> Drawable -> IO GC
-- | interface to the X11 library function XSetDashes().
setDashes :: Display -> GC -> CInt -> String -> CInt -> IO ()
-- | interface to the X11 library function XSetArcMode().
setArcMode :: Display -> GC -> ArcMode -> IO ()
-- | interface to the X11 library function XSetBackground().
setBackground :: Display -> GC -> Pixel -> IO ()
-- | interface to the X11 library function XSetForeground().
setForeground :: Display -> GC -> Pixel -> IO ()
-- | interface to the X11 library function XSetFunction().
setFunction :: Display -> GC -> GXFunction -> IO ()
-- | interface to the X11 library function
-- XSetGraphicsExposures().
setGraphicsExposures :: Display -> GC -> Bool -> IO ()
-- | interface to the X11 library function XSetClipMask().
setClipMask :: Display -> GC -> Pixmap -> IO ()
-- | interface to the X11 library function XSetClipOrigin().
setClipOrigin :: Display -> GC -> Position -> Position -> IO ()
-- | interface to the X11 library function XSetFillRule().
setFillRule :: Display -> GC -> FillRule -> IO ()
-- | interface to the X11 library function XSetFillStyle().
setFillStyle :: Display -> GC -> FillStyle -> IO ()
-- | interface to the X11 library function XSetFont().
setFont :: Display -> GC -> Font -> IO ()
-- | interface to the X11 library function XSetLineAttributes().
setLineAttributes :: Display -> GC -> CInt -> LineStyle -> CapStyle -> JoinStyle -> IO ()
-- | interface to the X11 library function XSetPlaneMask().
setPlaneMask :: Display -> GC -> Pixel -> IO ()
-- | interface to the X11 library function XSetState().
setState :: Display -> GC -> Pixel -> Pixel -> GXFunction -> Pixel -> IO ()
-- | interface to the X11 library function XSetStipple().
setStipple :: Display -> GC -> Pixmap -> IO ()
-- | interface to the X11 library function XSetSubwindowMode().
setSubwindowMode :: Display -> GC -> SubWindowMode -> IO ()
-- | interface to the X11 library function XSetTSOrigin().
setTSOrigin :: Display -> GC -> Position -> Position -> IO ()
-- | interface to the X11 library function XSetTile().
setTile :: Display -> GC -> Pixmap -> IO ()
-- | interface to the X11 library function XGContextFromGC().
gContextFromGC :: GC -> GContext
-- | interface to the X11 library function XFreeGC().
freeGC :: Display -> GC -> IO ()
-- | interface to the X11 library function XFlushGC().
flushGC :: Display -> GC -> IO ()
-- | interface to the X11 library function XCopyGC().
copyGC :: Display -> GC -> Mask -> GC -> IO ()
-- | interface to the X11 library function XSendEvent().
sendEvent :: Display -> Window -> Bool -> EventMask -> XEventPtr -> IO ()
-- | This function is somewhat compatible with Win32's
-- TimeGetTime()
gettimeofday_in_milliseconds :: IO Integer
-- | Reads an event with a timeout (in microseconds). Returns True if
-- timeout occurs.
waitForEvent :: Display -> Word32 -> IO Bool
get_ConfigureEvent :: XEventPtr -> IO XConfigureEvent
get_ExposeEvent :: XEventPtr -> IO XExposeEvent
get_MotionEvent :: XEventPtr -> IO XMotionEvent
get_ButtonEvent :: XEventPtr -> IO XButtonEvent
asKeyEvent :: XEventPtr -> XKeyEventPtr
get_KeyEvent :: XEventPtr -> IO XKeyEvent
get_Window :: XEventPtr -> IO Window
get_EventType :: XEventPtr -> IO EventType
allocaXEvent :: (XEventPtr -> IO a) -> IO a
queuedAfterReading :: QueuedMode
queuedAfterFlush :: QueuedMode
queuedAlready :: QueuedMode
-- | interface to the X11 library function XFlush().
flush :: Display -> IO ()
-- | interface to the X11 library function XSync().
sync :: Display -> Bool -> IO ()
-- | interface to the X11 library function XPending().
pending :: Display -> IO CInt
-- | interface to the X11 library function XEventsQueued().
eventsQueued :: Display -> QueuedMode -> IO CInt
-- | interface to the X11 library function XNextEvent().
nextEvent :: Display -> XEventPtr -> IO ()
-- | interface to the X11 library function XAllowEvents().
allowEvents :: Display -> AllowEvents -> Time -> IO ()
-- | interface to the X11 library function XSelectInput().
selectInput :: Display -> Window -> EventMask -> IO ()
-- | interface to the X11 library function XWindowEvent().
windowEvent :: Display -> Window -> EventMask -> XEventPtr -> IO ()
-- | interface to the X11 library function XCheckWindowEvent().
checkWindowEvent :: Display -> Window -> EventMask -> XEventPtr -> IO Bool
-- | interface to the X11 library function XMaskEvent().
maskEvent :: Display -> EventMask -> XEventPtr -> IO ()
-- | interface to the X11 library function XCheckMaskEvent().
checkMaskEvent :: Display -> EventMask -> XEventPtr -> IO Bool
-- | interface to the X11 library function XCheckTypedEvent().
checkTypedEvent :: Display -> EventType -> XEventPtr -> IO Bool
-- | interface to the X11 library function
-- XCheckTypedWindowEvent().
checkTypedWindowEvent :: Display -> Window -> EventType -> XEventPtr -> IO Bool
-- | interface to the X11 library function XPutBackEvent().
putBackEvent :: Display -> XEventPtr -> IO ()
-- | interface to the X11 library function XPeekEvent().
peekEvent :: Display -> XEventPtr -> IO ()
type QueuedMode = CInt
newtype XEvent
XEvent :: XEventPtr -> XEvent
type XEventPtr = Ptr XEvent
type XKeyEvent = (Window, Window, Time, CInt, CInt, CInt, CInt, Modifier, KeyCode, Bool)
type XKeyEventPtr = Ptr XKeyEvent
type XButtonEvent = (Window, Window, Time, CInt, CInt, CInt, CInt, Modifier, Button, Bool)
type XMotionEvent = (Window, Window, Time, CInt, CInt, CInt, CInt, Modifier, NotifyMode, Bool)
type XExposeEvent = (Position, Position, Dimension, Dimension, CInt)
type XMappingEvent = (MappingRequest, KeyCode, CInt)
type XConfigureEvent = (Position, Position, Dimension, Dimension)
-- | interface to the X11 library function XOpenDisplay().
openDisplay :: String -> IO Display
-- | interface to the X11 library function XServerVendor().
serverVendor :: Display -> String
-- | interface to the X11 library function XDisplayString().
displayString :: Display -> String
-- | interface to the X11 library function
-- XScreenResourceString().
screenResourceString :: Screen -> String
-- | interface to the X11 library function
-- XResourceManagerString().
resourceManagerString :: Display -> String
-- | interface to the X11 library function XAllPlanes().
allPlanes_aux :: Pixel
-- | interface to the X11 library function XBlackPixel().
blackPixel :: Display -> ScreenNumber -> Pixel
-- | interface to the X11 library function XWhitePixel().
whitePixel :: Display -> ScreenNumber -> Pixel
-- | interface to the X11 library function XConnectionNumber().
connectionNumber :: Display -> CInt
-- | interface to the X11 library function XDefaultColormap().
defaultColormap :: Display -> ScreenNumber -> Colormap
-- | interface to the X11 library function XDefaultGC().
defaultGC :: Display -> ScreenNumber -> GC
-- | interface to the X11 library function XDefaultDepth().
defaultDepth :: Display -> ScreenNumber -> CInt
-- | interface to the X11 library function XDefaultScreen().
defaultScreen :: Display -> ScreenNumber
-- | interface to the X11 library function
-- XDefaultScreenOfDisplay().
defaultScreenOfDisplay :: Display -> Screen
-- | interface to the X11 library function XDisplayHeight().
displayHeight :: Display -> ScreenNumber -> CInt
-- | interface to the X11 library function XDisplayHeightMM().
displayHeightMM :: Display -> ScreenNumber -> CInt
-- | interface to the X11 library function XDisplayWidth().
displayWidth :: Display -> ScreenNumber -> CInt
-- | interface to the X11 library function XDisplayWidthMM().
displayWidthMM :: Display -> ScreenNumber -> CInt
-- | interface to the X11 library function XMaxRequestSize().
maxRequestSize :: Display -> CInt
-- | interface to the X11 library function
-- XDisplayMotionBufferSize().
displayMotionBufferSize :: Display -> CInt
-- | interface to the X11 library function XImageByteOrder().
imageByteOrder :: Display -> CInt
-- | interface to the X11 library function XProtocolRevision().
protocolRevision :: Display -> CInt
-- | interface to the X11 library function XProtocolVersion().
protocolVersion :: Display -> CInt
-- | interface to the X11 library function XScreenCount().
screenCount :: Display -> CInt
-- | interface to the X11 library function XDefaultVisual().
defaultVisual :: Display -> ScreenNumber -> Visual
-- | interface to the X11 library function XDisplayCells().
displayCells :: Display -> ScreenNumber -> CInt
-- | interface to the X11 library function XDisplayPlanes().
displayPlanes :: Display -> ScreenNumber -> CInt
-- | interface to the X11 library function XScreenOfDisplay().
screenOfDisplay :: Display -> ScreenNumber -> Screen
-- | interface to the X11 library function XDefaultRootWindow().
defaultRootWindow :: Display -> Window
-- | interface to the X11 library function XRootWindow().
rootWindow :: Display -> ScreenNumber -> IO Window
-- | interface to the X11 library function XQLength().
qLength :: Display -> IO CInt
-- | interface to the X11 library function XNoOp().
noOp :: Display -> IO ()
-- | interface to the X11 library function XCloseDisplay().
closeDisplay :: Display -> IO ()
xC_xterm :: Glyph
xC_watch :: Glyph
xC_ur_angle :: Glyph
xC_umbrella :: Glyph
xC_ul_angle :: Glyph
xC_trek :: Glyph
xC_top_tee :: Glyph
xC_top_side :: Glyph
xC_top_right_corner :: Glyph
xC_top_left_corner :: Glyph
xC_top_left_arrow :: Glyph
xC_tcross :: Glyph
xC_target :: Glyph
xC_star :: Glyph
xC_spraycan :: Glyph
xC_spider :: Glyph
xC_sizing :: Glyph
xC_shuttle :: Glyph
xC_sb_v_double_arrow :: Glyph
xC_sb_up_arrow :: Glyph
xC_sb_right_arrow :: Glyph
xC_sb_left_arrow :: Glyph
xC_sb_h_double_arrow :: Glyph
xC_sb_down_arrow :: Glyph
xC_sailboat :: Glyph
xC_rtl_logo :: Glyph
xC_rightbutton :: Glyph
xC_right_tee :: Glyph
xC_right_side :: Glyph
xC_right_ptr :: Glyph
xC_question_arrow :: Glyph
xC_plus :: Glyph
xC_pirate :: Glyph
xC_pencil :: Glyph
xC_mouse :: Glyph
xC_man :: Glyph
xC_lr_angle :: Glyph
xC_ll_angle :: Glyph
xC_leftbutton :: Glyph
xC_left_tee :: Glyph
xC_left_side :: Glyph
xC_left_ptr :: Glyph
xC_iron_cross :: Glyph
xC_icon :: Glyph
xC_heart :: Glyph
xC_hand2 :: Glyph
xC_hand1 :: Glyph
xC_gumby :: Glyph
xC_gobbler :: Glyph
xC_fleur :: Glyph
xC_exchange :: Glyph
xC_draped_box :: Glyph
xC_draft_small :: Glyph
xC_draft_large :: Glyph
xC_double_arrow :: Glyph
xC_dotbox :: Glyph
xC_dot :: Glyph
xC_diamond_cross :: Glyph
xC_crosshair :: Glyph
xC_cross_reverse :: Glyph
xC_cross :: Glyph
xC_coffee_mug :: Glyph
xC_clock :: Glyph
xC_circle :: Glyph
xC_center_ptr :: Glyph
xC_box_spiral :: Glyph
xC_bottom_tee :: Glyph
xC_bottom_side :: Glyph
xC_bottom_right_corner :: Glyph
xC_bottom_left_corner :: Glyph
xC_bogosity :: Glyph
xC_boat :: Glyph
xC_based_arrow_up :: Glyph
xC_based_arrow_down :: Glyph
xC_arrow :: Glyph
xC_X_cursor :: Glyph
-- | interface to the X11 library function XTextWidth().
textWidth :: FontStruct -> String -> Int32
-- | interface to the X11 library function XTextExtents().
textExtents :: FontStruct -> String -> (FontDirection, Int32, Int32, CharStruct)
descentFromFontStruct :: FontStruct -> Int32
ascentFromFontStruct :: FontStruct -> Int32
fontFromFontStruct :: FontStruct -> Font
-- | interface to the X11 library function XLoadQueryFont().
loadQueryFont :: Display -> String -> IO FontStruct
-- | interface to the X11 library function XGetGCValues().
fontFromGC :: Display -> GC -> IO Font
-- | interface to the X11 library function XQueryFont().
queryFont :: Display -> Font -> IO FontStruct
-- | interface to the X11 library function XFreeFont().
freeFont :: Display -> FontStruct -> IO ()
type Glyph = Word16
-- | pointer to an X11 XFontStruct structure
data FontStruct
type CharStruct = (CInt, CInt, CInt, CInt, CInt)
-- | interface to the X11 library function XGetPixel().
getPixel :: Image -> CInt -> CInt -> CULong
-- | interface to the X11 library function XGetImage().
getImage :: Display -> Drawable -> CInt -> CInt -> CUInt -> CUInt -> CULong -> ImageFormat -> IO Image
-- | interface to the X11 library function XCreateImage().
createImage :: Display -> Visual -> CInt -> ImageFormat -> CInt -> Ptr CChar -> Dimension -> Dimension -> CInt -> CInt -> IO Image
-- | interface to the X11 library function XPutImage().
putImage :: Display -> Drawable -> GC -> Image -> Position -> Position -> Position -> Position -> Dimension -> Dimension -> IO ()
-- | interface to the X11 library function XDestroyImage().
destroyImage :: Image -> IO ()
xGetPixel :: Image -> CInt -> CInt -> IO CULong
-- | interface to the X11 library function XSetRegion().
setRegion :: Display -> GC -> Region -> IO CInt
-- | interface to the X11 library function XShrinkRegion().
shrinkRegion :: Region -> Point -> IO CInt
-- | interface to the X11 library function XOffsetRegion().
offsetRegion :: Region -> Point -> IO CInt
-- | interface to the X11 library function XClipBox().
clipBox :: Region -> IO (Rectangle, CInt)
-- | interface to the X11 library function XRectInRegion().
rectInRegion :: Region -> Rectangle -> IO RectInRegionResult
-- | interface to the X11 library function XPointInRegion().
pointInRegion :: Region -> Point -> IO Bool
-- | interface to the X11 library function XEqualRegion().
equalRegion :: Region -> Region -> IO Bool
-- | interface to the X11 library function XEmptyRegion().
emptyRegion :: Region -> IO Bool
-- | interface to the X11 library function XXorRegion().
xorRegion :: Region -> Region -> Region -> IO CInt
-- | interface to the X11 library function XUnionRegion().
unionRegion :: Region -> Region -> Region -> IO CInt
-- | interface to the X11 library function XUnionRectWithRegion().
unionRectWithRegion :: Rectangle -> Region -> Region -> IO CInt
-- | interface to the X11 library function XSubtractRegion().
subtractRegion :: Region -> Region -> Region -> IO CInt
-- | interface to the X11 library function XIntersectRegion().
intersectRegion :: Region -> Region -> Region -> IO CInt
-- | interface to the X11 library function XPolygonRegion().
polygonRegion :: [Point] -> FillRule -> IO Region
-- | interface to the X11 library function XCreateRegion().
createRegion :: IO Region
rectanglePart :: RectInRegionResult
rectangleIn :: RectInRegionResult
rectangleOut :: RectInRegionResult
data Region
type RectInRegionResult = CInt
-- | interface to the X11 library function XBlackPixelOfScreen().
blackPixelOfScreen :: Screen -> Pixel
-- | interface to the X11 library function XWhitePixelOfScreen().
whitePixelOfScreen :: Screen -> Pixel
-- | interface to the X11 library function XCellsOfScreen().
cellsOfScreen :: Screen -> CInt
-- | interface to the X11 library function
-- XDefaultColormapOfScreen().
defaultColormapOfScreen :: Screen -> Colormap
-- | interface to the X11 library function
-- XDefaultDepthOfScreen().
defaultDepthOfScreen :: Screen -> CInt
-- | interface to the X11 library function XDefaultGCOfScreen().
defaultGCOfScreen :: Screen -> GC
-- | interface to the X11 library function
-- XDefaultVisualOfScreen().
defaultVisualOfScreen :: Screen -> Visual
-- | interface to the X11 library function XDoesBackingStore().
doesBackingStore :: Screen -> Bool
-- | interface to the X11 library function XDoesSaveUnders().
doesSaveUnders :: Screen -> Bool
-- | interface to the X11 library function XDisplayOfScreen().
displayOfScreen :: Screen -> Display
-- | interface to the X11 library function XEventMaskOfScreen().
-- Event mask at connection setup time - not current event mask!
eventMaskOfScreen :: Screen -> EventMask
-- | interface to the X11 library function XMinCmapsOfScreen().
minCmapsOfScreen :: Screen -> CInt
-- | interface to the X11 library function XMaxCmapsOfScreen().
maxCmapsOfScreen :: Screen -> CInt
-- | interface to the X11 library function XRootWindowOfScreen().
rootWindowOfScreen :: Screen -> Window
-- | interface to the X11 library function XWidthOfScreen().
widthOfScreen :: Screen -> Dimension
-- | interface to the X11 library function XWidthMMOfScreen().
widthMMOfScreen :: Screen -> Dimension
-- | interface to the X11 library function XHeightOfScreen().
heightOfScreen :: Screen -> Dimension
-- | interface to the X11 library function XHeightMMOfScreen().
heightMMOfScreen :: Screen -> Dimension
-- | interface to the X11 library function XPlanesOfScreen().
planesOfScreen :: Screen -> CInt
-- | interface to the X11 library function
-- XScreenNumberOfScreen().
screenNumberOfScreen :: Screen -> ScreenNumber
-- | pointer to an X11 Display structure
newtype Display
Display :: Ptr Display -> Display
-- | pointer to an X11 Screen structure
data Screen
-- | pointer to an X11 Visual structure
data Visual
-- | pointer to an X11 GC structure
data GC
-- | pointer to an X11 XSetWindowAttributes structure
data SetWindowAttributes
-- | counterpart of an X11 XVisualInfo structure
data VisualInfo
VisualInfo :: Visual -> VisualID -> ScreenNumber -> CInt -> CInt -> CULong -> CULong -> CULong -> CInt -> CInt -> VisualInfo
[visualInfo_visual] :: VisualInfo -> Visual
[visualInfo_visualID] :: VisualInfo -> VisualID
[visualInfo_screen] :: VisualInfo -> ScreenNumber
[visualInfo_depth] :: VisualInfo -> CInt
[visualInfo_class] :: VisualInfo -> CInt
[visualInfo_redMask] :: VisualInfo -> CULong
[visualInfo_greenMask] :: VisualInfo -> CULong
[visualInfo_blueMask] :: VisualInfo -> CULong
[visualInfo_colormapSize] :: VisualInfo -> CInt
[visualInfo_bitsPerRGB] :: VisualInfo -> CInt
-- | pointer to an X11 XImage structure
data Image
type Pixel = Word64
type Position = Int32
type Dimension = Word32
type Angle = CInt
type ScreenNumber = Word32
type Buffer = CInt
-- | counterpart of an X11 XPoint structure
data Point
Point :: !Position -> !Position -> Point
[pt_x] :: Point -> !Position
[pt_y] :: Point -> !Position
-- | counterpart of an X11 XRectangle structure
data Rectangle
Rectangle :: !Position -> !Position -> !Dimension -> !Dimension -> Rectangle
[rect_x] :: Rectangle -> !Position
[rect_y] :: Rectangle -> !Position
[rect_width] :: Rectangle -> !Dimension
[rect_height] :: Rectangle -> !Dimension
-- | counterpart of an X11 XArc structure
data Arc
Arc :: Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> Arc
[arc_x] :: Arc -> Position
[arc_y] :: Arc -> Position
[arc_width] :: Arc -> Dimension
[arc_height] :: Arc -> Dimension
[arc_angle1] :: Arc -> Angle
[arc_angle2] :: Arc -> Angle
-- | counterpart of an X11 XSegment structure
data Segment
Segment :: Position -> Position -> Position -> Position -> Segment
[seg_x1] :: Segment -> Position
[seg_y1] :: Segment -> Position
[seg_x2] :: Segment -> Position
[seg_y2] :: Segment -> Position
-- | counterpart of an X11 XColor structure
data Color
Color :: Pixel -> Word16 -> Word16 -> Word16 -> Word8 -> Color
[color_pixel] :: Color -> Pixel
[color_red] :: Color -> Word16
[color_green] :: Color -> Word16
[color_blue] :: Color -> Word16
[color_flags] :: Color -> Word8
xRR_UnknownConnection :: Connection
xRR_Disconnected :: Connection
xRR_Connected :: Connection
xRR_Reflect_Y :: Reflection
xRR_Reflect_X :: Reflection
xRR_Rotate_270 :: Rotation
xRR_Rotate_180 :: Rotation
xRR_Rotate_90 :: Rotation
xRR_Rotate_0 :: Rotation
zPixmap :: ImageFormat
xyPixmap :: ImageFormat
xyBitmap :: ImageFormat
fontRightToLeft :: FontDirection
fontLeftToRight :: FontDirection
doBlue :: Word8
doGreen :: Word8
doRed :: Word8
always :: BackingStore
whenMapped :: BackingStore
notUseful :: BackingStore
unmapGravity :: WindowGravity
staticGravity :: BitGravity
southEastGravity :: BitGravity
southGravity :: BitGravity
southWestGravity :: BitGravity
eastGravity :: BitGravity
centerGravity :: BitGravity
westGravity :: BitGravity
northEastGravity :: BitGravity
northGravity :: BitGravity
northWestGravity :: BitGravity
forgetGravity :: BitGravity
setModeDelete :: ChangeSaveSetMode
setModeInsert :: ChangeSaveSetMode
mappingPointer :: MappingRequest
mappingKeyboard :: MappingRequest
mappingModifier :: MappingRequest
allocAll :: ColormapAlloc
allocNone :: ColormapAlloc
mSBFirst :: ByteOrder
lSBFirst :: ByteOrder
lowerHighest :: CirculationDirection
raiseLowest :: CirculationDirection
gCLastBit :: GCMask
gCArcMode :: GCMask
gCDashList :: GCMask
gCDashOffset :: GCMask
gCClipMask :: GCMask
gCClipYOrigin :: GCMask
gCClipXOrigin :: GCMask
gCGraphicsExposures :: GCMask
gCSubwindowMode :: GCMask
gCFont :: GCMask
gCTileStipYOrigin :: GCMask
gCTileStipXOrigin :: GCMask
gCStipple :: GCMask
gCTile :: GCMask
gCFillRule :: GCMask
gCFillStyle :: GCMask
gCJoinStyle :: GCMask
gCCapStyle :: GCMask
gCLineStyle :: GCMask
gCLineWidth :: GCMask
gCBackground :: GCMask
gCForeground :: GCMask
gCPlaneMask :: GCMask
gCFunction :: GCMask
arcPieSlice :: ArcMode
arcChord :: ArcMode
convex :: PolygonShape
nonconvex :: PolygonShape
complex :: PolygonShape
coordModePrevious :: CoordinateMode
coordModeOrigin :: CoordinateMode
includeInferiors :: SubWindowMode
clipByChildren :: SubWindowMode
windingRule :: FillRule
evenOddRule :: FillRule
fillOpaqueStippled :: FillStyle
fillStippled :: FillStyle
fillTiled :: FillStyle
fillSolid :: FillStyle
joinBevel :: JoinStyle
joinRound :: JoinStyle
joinMiter :: JoinStyle
capProjecting :: CapStyle
capRound :: CapStyle
capButt :: CapStyle
capNotLast :: CapStyle
lineDoubleDash :: LineStyle
lineOnOffDash :: LineStyle
lineSolid :: LineStyle
gXset :: GXFunction
gXnand :: GXFunction
gXorInverted :: GXFunction
gXcopyInverted :: GXFunction
gXorReverse :: GXFunction
gXinvert :: GXFunction
gXequiv :: GXFunction
gXnor :: GXFunction
gXor :: GXFunction
gXxor :: GXFunction
gXnoop :: GXFunction
gXandInverted :: GXFunction
gXcopy :: GXFunction
gXandReverse :: GXFunction
gXand :: GXFunction
gXclear :: GXFunction
stippleShape :: QueryBestSizeClass
tileShape :: QueryBestSizeClass
cursorShape :: QueryBestSizeClass
retainTemporary :: CloseDownMode
retainPermanent :: CloseDownMode
destroyAll :: CloseDownMode
cWHeight :: AttributeMask
cWWidth :: AttributeMask
cWY :: AttributeMask
cWX :: AttributeMask
cWCursor :: AttributeMask
cWColormap :: AttributeMask
cWDontPropagate :: AttributeMask
cWEventMask :: AttributeMask
cWSaveUnder :: AttributeMask
cWOverrideRedirect :: AttributeMask
cWBackingPixel :: AttributeMask
cWBackingPlanes :: AttributeMask
cWBackingStore :: AttributeMask
cWWinGravity :: AttributeMask
cWBitGravity :: AttributeMask
cWBorderPixel :: AttributeMask
cWBorderPixmap :: AttributeMask
cWBackPixel :: AttributeMask
cWBackPixmap :: AttributeMask
inputOnly :: WindowClass
inputOutput :: WindowClass
copyFromParent :: WindowClass
throwIfZero :: String -> IO Status -> IO ()
lastExtensionError :: ErrorCode
firstExtensionError :: ErrorCode
badImplementation :: ErrorCode
badLength :: ErrorCode
badName :: ErrorCode
badIDChoice :: ErrorCode
-- | Xlib functions with return values of type Status return zero
-- on failure and nonzero on success.
badGC :: ErrorCode
badColor :: ErrorCode
badAlloc :: ErrorCode
badAccess :: ErrorCode
badDrawable :: ErrorCode
badMatch :: ErrorCode
badFont :: ErrorCode
badCursor :: ErrorCode
badAtom :: ErrorCode
badPixmap :: ErrorCode
badWindow :: ErrorCode
badValue :: ErrorCode
badRequest :: ErrorCode
success :: ErrorCode
revertToParent :: FocusMode
revertToPointerRoot :: FocusMode
revertToNone :: FocusMode
syncBoth :: AllowEvents
asyncBoth :: AllowEvents
replayKeyboard :: AllowEvents
syncKeyboard :: AllowEvents
asyncKeyboard :: AllowEvents
replayPointer :: AllowEvents
syncPointer :: AllowEvents
asyncPointer :: AllowEvents
grabFrozen :: GrabStatus
grabNotViewable :: GrabStatus
grabInvalidTime :: GrabStatus
alreadyGrabbed :: GrabStatus
grabSuccess :: GrabStatus
grabModeAsync :: GrabMode
grabModeSync :: GrabMode
colormapInstalled :: ColormapNotification
colormapUninstalled :: ColormapNotification
propertyDelete :: PropertyNotification
propertyNewValue :: PropertyNotification
familyChaos :: Protocol
familyDECnet :: Protocol
familyInternet :: Protocol
placeOnBottom :: Place
placeOnTop :: Place
visibilityFullyObscured :: Visibility
visibilityPartiallyObscured :: Visibility
visibilityUnobscured :: Visibility
notifyDetailNone :: NotifyDetail
notifyPointerRoot :: NotifyDetail
notifyPointer :: NotifyDetail
notifyNonlinearVirtual :: NotifyDetail
notifyNonlinear :: NotifyDetail
notifyInferior :: NotifyDetail
notifyVirtual :: NotifyDetail
notifyAncestor :: NotifyDetail
notifyHint :: NotifyMode
notifyWhileGrabbed :: NotifyMode
notifyUngrab :: NotifyMode
notifyGrab :: NotifyMode
notifyNormal :: NotifyMode
button5 :: Button
button4 :: Button
button3 :: Button
button2 :: Button
button1 :: Button
button5Mask :: ButtonMask
button4Mask :: ButtonMask
button3Mask :: ButtonMask
button2Mask :: ButtonMask
button1Mask :: ButtonMask
mod5Mask :: KeyMask
mod4Mask :: KeyMask
mod3Mask :: KeyMask
mod2Mask :: KeyMask
mod1Mask :: KeyMask
controlMask :: KeyMask
lockMask :: KeyMask
shiftMask :: KeyMask
noModMask :: KeyMask
anyModifier :: Modifier
mod5MapIndex :: Modifier
mod4MapIndex :: Modifier
mod3MapIndex :: Modifier
mod2MapIndex :: Modifier
mod1MapIndex :: Modifier
controlMapIndex :: Modifier
lockMapIndex :: Modifier
shiftMapIndex :: Modifier
screenSaverNotify :: EventType
lASTEvent :: EventType
rrNotifyOutputProperty :: EventType
rrNotifyOutputChange :: EventType
rrNotifyCrtcChange :: EventType
rrNotify :: EventType
rrScreenChangeNotify :: EventType
mappingNotify :: EventType
clientMessage :: EventType
colormapNotify :: EventType
selectionNotify :: EventType
selectionRequest :: EventType
selectionClear :: EventType
propertyNotify :: EventType
circulateRequest :: EventType
circulateNotify :: EventType
resizeRequest :: EventType
gravityNotify :: EventType
configureRequest :: EventType
configureNotify :: EventType
reparentNotify :: EventType
mapRequest :: EventType
mapNotify :: EventType
unmapNotify :: EventType
destroyNotify :: EventType
createNotify :: EventType
visibilityNotify :: EventType
noExpose :: EventType
graphicsExpose :: EventType
expose :: EventType
keymapNotify :: EventType
focusOut :: EventType
focusIn :: EventType
leaveNotify :: EventType
enterNotify :: EventType
motionNotify :: EventType
buttonRelease :: EventType
buttonPress :: EventType
keyRelease :: EventType
keyPress :: EventType
screenSaverNotifyMask :: EventMask
screenSaverCycleMask :: EventMask
rrOutputPropertyNotifyMask :: EventMask
rrOutputChangeNotifyMask :: EventMask
rrCrtcChangeNotifyMask :: EventMask
rrScreenChangeNotifyMask :: EventMask
ownerGrabButtonMask :: EventMask
colormapChangeMask :: EventMask
propertyChangeMask :: EventMask
focusChangeMask :: EventMask
substructureRedirectMask :: EventMask
substructureNotifyMask :: EventMask
resizeRedirectMask :: EventMask
structureNotifyMask :: EventMask
visibilityChangeMask :: EventMask
exposureMask :: EventMask
keymapStateMask :: EventMask
buttonMotionMask :: EventMask
button5MotionMask :: EventMask
button4MotionMask :: EventMask
button3MotionMask :: EventMask
button2MotionMask :: EventMask
button1MotionMask :: EventMask
pointerMotionHintMask :: EventMask
pointerMotionMask :: EventMask
leaveWindowMask :: EventMask
enterWindowMask :: EventMask
buttonReleaseMask :: EventMask
buttonPressMask :: EventMask
keyReleaseMask :: EventMask
keyPressMask :: EventMask
noEventMask :: EventMask
xK_ydiaeresis :: KeySym
xK_thorn :: KeySym
xK_yacute :: KeySym
xK_udiaeresis :: KeySym
xK_ucircumflex :: KeySym
xK_uacute :: KeySym
xK_ugrave :: KeySym
xK_oslash :: KeySym
xK_division :: KeySym
xK_odiaeresis :: KeySym
xK_otilde :: KeySym
xK_ocircumflex :: KeySym
xK_oacute :: KeySym
xK_ograve :: KeySym
xK_ntilde :: KeySym
xK_eth :: KeySym
xK_idiaeresis :: KeySym
xK_icircumflex :: KeySym
xK_iacute :: KeySym
xK_igrave :: KeySym
xK_ediaeresis :: KeySym
xK_ecircumflex :: KeySym
xK_eacute :: KeySym
xK_egrave :: KeySym
xK_ccedilla :: KeySym
xK_ae :: KeySym
xK_aring :: KeySym
xK_adiaeresis :: KeySym
xK_atilde :: KeySym
xK_acircumflex :: KeySym
xK_aacute :: KeySym
xK_agrave :: KeySym
xK_ssharp :: KeySym
xK_Thorn :: KeySym
xK_THORN :: KeySym
xK_Yacute :: KeySym
xK_Udiaeresis :: KeySym
xK_Ucircumflex :: KeySym
xK_Uacute :: KeySym
xK_Ugrave :: KeySym
xK_Ooblique :: KeySym
xK_multiply :: KeySym
xK_Odiaeresis :: KeySym
xK_Otilde :: KeySym
xK_Ocircumflex :: KeySym
xK_Oacute :: KeySym
xK_Ograve :: KeySym
xK_Ntilde :: KeySym
xK_Eth :: KeySym
xK_ETH :: KeySym
xK_Idiaeresis :: KeySym
xK_Icircumflex :: KeySym
xK_Iacute :: KeySym
xK_Igrave :: KeySym
xK_Ediaeresis :: KeySym
xK_Ecircumflex :: KeySym
xK_Eacute :: KeySym
xK_Egrave :: KeySym
xK_Ccedilla :: KeySym
xK_AE :: KeySym
xK_Aring :: KeySym
xK_Adiaeresis :: KeySym
xK_Atilde :: KeySym
xK_Acircumflex :: KeySym
xK_Aacute :: KeySym
xK_Agrave :: KeySym
xK_questiondown :: KeySym
xK_threequarters :: KeySym
xK_onehalf :: KeySym
xK_onequarter :: KeySym
xK_guillemotright :: KeySym
xK_masculine :: KeySym
xK_onesuperior :: KeySym
xK_cedilla :: KeySym
xK_periodcentered :: KeySym
xK_paragraph :: KeySym
xK_mu :: KeySym
xK_acute :: KeySym
xK_threesuperior :: KeySym
xK_twosuperior :: KeySym
xK_plusminus :: KeySym
xK_degree :: KeySym
xK_macron :: KeySym
xK_registered :: KeySym
xK_hyphen :: KeySym
xK_notsign :: KeySym
xK_guillemotleft :: KeySym
xK_ordfeminine :: KeySym
xK_copyright :: KeySym
xK_diaeresis :: KeySym
xK_section :: KeySym
xK_brokenbar :: KeySym
xK_yen :: KeySym
xK_currency :: KeySym
xK_sterling :: KeySym
xK_cent :: KeySym
xK_exclamdown :: KeySym
xK_nobreakspace :: KeySym
xK_asciitilde :: KeySym
xK_braceright :: KeySym
xK_bar :: KeySym
xK_braceleft :: KeySym
xK_z :: KeySym
xK_y :: KeySym
xK_x :: KeySym
xK_w :: KeySym
xK_v :: KeySym
xK_u :: KeySym
xK_t :: KeySym
xK_s :: KeySym
xK_r :: KeySym
xK_q :: KeySym
xK_p :: KeySym
xK_o :: KeySym
xK_n :: KeySym
xK_m :: KeySym
xK_l :: KeySym
xK_k :: KeySym
xK_j :: KeySym
xK_i :: KeySym
xK_h :: KeySym
xK_g :: KeySym
xK_f :: KeySym
xK_e :: KeySym
xK_d :: KeySym
xK_c :: KeySym
xK_b :: KeySym
xK_a :: KeySym
xK_quoteleft :: KeySym
xK_grave :: KeySym
xK_underscore :: KeySym
xK_asciicircum :: KeySym
xK_bracketright :: KeySym
xK_backslash :: KeySym
xK_bracketleft :: KeySym
xK_Z :: KeySym
xK_Y :: KeySym
xK_X :: KeySym
xK_W :: KeySym
xK_V :: KeySym
xK_U :: KeySym
xK_T :: KeySym
xK_S :: KeySym
xK_R :: KeySym
xK_Q :: KeySym
xK_P :: KeySym
xK_O :: KeySym
xK_N :: KeySym
xK_M :: KeySym
xK_L :: KeySym
xK_K :: KeySym
xK_J :: KeySym
xK_I :: KeySym
xK_H :: KeySym
xK_G :: KeySym
xK_F :: KeySym
xK_E :: KeySym
xK_D :: KeySym
xK_C :: KeySym
xK_B :: KeySym
xK_A :: KeySym
xK_at :: KeySym
xK_question :: KeySym
xK_greater :: KeySym
xK_equal :: KeySym
xK_less :: KeySym
xK_semicolon :: KeySym
xK_colon :: KeySym
xK_9 :: KeySym
xK_8 :: KeySym
xK_7 :: KeySym
xK_6 :: KeySym
xK_5 :: KeySym
xK_4 :: KeySym
xK_3 :: KeySym
xK_2 :: KeySym
xK_1 :: KeySym
xK_0 :: KeySym
xK_slash :: KeySym
xK_period :: KeySym
xK_minus :: KeySym
xK_comma :: KeySym
xK_plus :: KeySym
xK_asterisk :: KeySym
xK_parenright :: KeySym
xK_parenleft :: KeySym
xK_quoteright :: KeySym
xK_apostrophe :: KeySym
xK_ampersand :: KeySym
xK_percent :: KeySym
xK_dollar :: KeySym
xK_numbersign :: KeySym
xK_quotedbl :: KeySym
xK_exclam :: KeySym
xK_space :: KeySym
xK_Hyper_R :: KeySym
xK_Hyper_L :: KeySym
xK_Super_R :: KeySym
xK_Super_L :: KeySym
xK_Alt_R :: KeySym
xK_Alt_L :: KeySym
xK_Meta_R :: KeySym
xK_Meta_L :: KeySym
xK_Shift_Lock :: KeySym
xK_Caps_Lock :: KeySym
xK_Control_R :: KeySym
xK_Control_L :: KeySym
xK_Shift_R :: KeySym
xK_Shift_L :: KeySym
xK_R15 :: KeySym
xK_F35 :: KeySym
xK_R14 :: KeySym
xK_F34 :: KeySym
xK_R13 :: KeySym
xK_F33 :: KeySym
xK_R12 :: KeySym
xK_F32 :: KeySym
xK_R11 :: KeySym
xK_F31 :: KeySym
xK_R10 :: KeySym
xK_F30 :: KeySym
xK_R9 :: KeySym
xK_F29 :: KeySym
xK_R8 :: KeySym
xK_F28 :: KeySym
xK_R7 :: KeySym
xK_F27 :: KeySym
xK_R6 :: KeySym
xK_F26 :: KeySym
xK_R5 :: KeySym
xK_F25 :: KeySym
xK_R4 :: KeySym
xK_F24 :: KeySym
xK_R3 :: KeySym
xK_F23 :: KeySym
xK_R2 :: KeySym
xK_F22 :: KeySym
xK_R1 :: KeySym
xK_F21 :: KeySym
xK_L10 :: KeySym
xK_F20 :: KeySym
xK_L9 :: KeySym
xK_F19 :: KeySym
xK_L8 :: KeySym
xK_F18 :: KeySym
xK_L7 :: KeySym
xK_F17 :: KeySym
xK_L6 :: KeySym
xK_F16 :: KeySym
xK_L5 :: KeySym
xK_F15 :: KeySym
xK_L4 :: KeySym
xK_F14 :: KeySym
xK_L3 :: KeySym
xK_F13 :: KeySym
xK_L2 :: KeySym
xK_F12 :: KeySym
xK_L1 :: KeySym
xK_F11 :: KeySym
xK_F10 :: KeySym
xK_F9 :: KeySym
xK_F8 :: KeySym
xK_F7 :: KeySym
xK_F6 :: KeySym
xK_F5 :: KeySym
xK_F4 :: KeySym
xK_F3 :: KeySym
xK_F2 :: KeySym
xK_F1 :: KeySym
xK_KP_9 :: KeySym
xK_KP_8 :: KeySym
xK_KP_7 :: KeySym
xK_KP_6 :: KeySym
xK_KP_5 :: KeySym
xK_KP_4 :: KeySym
xK_KP_3 :: KeySym
xK_KP_2 :: KeySym
xK_KP_1 :: KeySym
xK_KP_0 :: KeySym
xK_KP_Divide :: KeySym
xK_KP_Decimal :: KeySym
xK_KP_Subtract :: KeySym
xK_KP_Separator :: KeySym
xK_KP_Add :: KeySym
xK_KP_Multiply :: KeySym
xK_KP_Equal :: KeySym
xK_KP_Delete :: KeySym
xK_KP_Insert :: KeySym
xK_KP_Begin :: KeySym
xK_KP_End :: KeySym
xK_KP_Page_Down :: KeySym
xK_KP_Next :: KeySym
xK_KP_Page_Up :: KeySym
xK_KP_Prior :: KeySym
xK_KP_Down :: KeySym
xK_KP_Right :: KeySym
xK_KP_Up :: KeySym
xK_KP_Left :: KeySym
xK_KP_Home :: KeySym
xK_KP_F4 :: KeySym
xK_KP_F3 :: KeySym
xK_KP_F2 :: KeySym
xK_KP_F1 :: KeySym
xK_KP_Enter :: KeySym
xK_KP_Tab :: KeySym
xK_KP_Space :: KeySym
xK_Num_Lock :: KeySym
xK_script_switch :: KeySym
xK_Mode_switch :: KeySym
xK_Break :: KeySym
xK_Help :: KeySym
xK_Cancel :: KeySym
xK_Find :: KeySym
xK_Menu :: KeySym
xK_Redo :: KeySym
xK_Undo :: KeySym
xK_Insert :: KeySym
xK_Execute :: KeySym
xK_Print :: KeySym
xK_Select :: KeySym
xK_Begin :: KeySym
xK_End :: KeySym
xK_Page_Down :: KeySym
xK_Next :: KeySym
xK_Page_Up :: KeySym
xK_Prior :: KeySym
xK_Down :: KeySym
xK_Right :: KeySym
xK_Up :: KeySym
xK_Left :: KeySym
xK_Home :: KeySym
xK_PreviousCandidate :: KeySym
xK_MultipleCandidate :: KeySym
xK_SingleCandidate :: KeySym
xK_Codeinput :: KeySym
xK_Multi_key :: KeySym
xK_Delete :: KeySym
xK_Escape :: KeySym
xK_Sys_Req :: KeySym
xK_Scroll_Lock :: KeySym
xK_Pause :: KeySym
xK_Return :: KeySym
xK_Clear :: KeySym
xK_Linefeed :: KeySym
xK_Tab :: KeySym
xK_BackSpace :: KeySym
xK_VoidSymbol :: KeySym
type XID = Word64
type Mask = Word64
type Atom = Word64
type VisualID = Word64
type Time = Word64
type Window = XID
type Drawable = XID
type Font = XID
type Pixmap = XID
type Cursor = XID
type Colormap = XID
type GContext = XID
type KeyCode = Word8
type KeySym = XID
type EventMask = Mask
type EventType = Word32
type Modifier = CUInt
type KeyMask = Modifier
type ButtonMask = Modifier
type Button = Word32
type NotifyMode = CInt
type NotifyDetail = CInt
type Visibility = CInt
-- | Place of window relative to siblings (used in Circulation requests or
-- events)
type Place = CInt
type Protocol = CInt
type PropertyNotification = CInt
type ColormapNotification = CInt
type GrabMode = CInt
type GrabStatus = CInt
type AllowEvents = CInt
type FocusMode = CInt
type ErrorCode = CInt
type Status = CInt
type WindowClass = CInt
type AttributeMask = Mask
type CloseDownMode = CInt
type QueryBestSizeClass = CInt
type GXFunction = CInt
type LineStyle = CInt
type CapStyle = CInt
type JoinStyle = CInt
type FillStyle = CInt
type FillRule = CInt
type SubWindowMode = CInt
type CoordinateMode = CInt
type PolygonShape = CInt
type ArcMode = CInt
type GCMask = CInt
type CirculationDirection = CInt
type ByteOrder = CInt
type ColormapAlloc = CInt
type MappingRequest = CInt
type ChangeSaveSetMode = CInt
type BitGravity = CInt
type WindowGravity = CInt
type BackingStore = CInt
type FontDirection = CInt
type ImageFormat = CInt
type Rotation = Word16
type Reflection = Word16
type SizeID = Word16
type SubpixelOrder = Word16
type Connection = Word16
type RROutput = Word64
type RRCrtc = Word64
type RRMode = Word64
type XRRModeFlags = Word64
-- | Bitwise "or"
(.|.) :: Bits a => a -> a -> a
infixl 5 .|.
-- | Minimal definition is either both of get and put or
-- just state
class Monad m => MonadState s (m :: Type -> Type) | m -> s
-- | Return the state from the internals of the monad.
get :: MonadState s m => m s
-- | Replace the state inside the monad.
put :: MonadState s m => s -> m ()
-- | Embed a simple state action into the monad.
state :: MonadState s m => (s -> (a, s)) -> m a
-- | Gets specific component of the state, using a projection function
-- supplied.
gets :: MonadState s m => (s -> a) -> m a
-- | 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.
modify :: MonadState s m => (s -> s) -> m ()
-- | See examples in Control.Monad.Reader. Note, the partially
-- applied function type (->) r is a simple reader monad. See
-- the instance declaration below.
class Monad m => MonadReader r (m :: Type -> Type) | m -> r
-- | Retrieves the monad environment.
ask :: MonadReader r m => m r
-- | Executes a computation in a modified environment.
local :: MonadReader r m => (r -> r) -> m a -> m a
-- | Retrieves a function of the current environment.
reader :: MonadReader r m => (r -> a) -> m a
-- | Retrieves a function of the current environment.
asks :: MonadReader r m => (r -> a) -> m a
-- | Monads in which IO computations may be embedded. Any monad
-- built by applying a sequence of monad transformers to the IO
-- monad will be an instance of this class.
--
-- Instances should satisfy the following laws, which state that
-- liftIO is a transformer of monads:
--
--
class Monad m => MonadIO (m :: Type -> Type)
-- | Lift a computation from the IO monad. This allows us to run IO
-- computations in any monadic stack, so long as it supports these kinds
-- of operations (i.e. IO is the base monad for the stack).
--
-- Example
--
--
-- import Control.Monad.Trans.State -- from the "transformers" library
--
-- printState :: Show s => StateT s IO ()
-- printState = do
-- state <- get
-- liftIO $ print state
--
--
-- Had we omitted liftIO, we would have ended up with
-- this error:
--
--
-- • Couldn't match type ‘IO’ with ‘StateT s IO’
-- Expected type: StateT s IO ()
-- Actual type: IO ()
--
--
-- The important part here is the mismatch between StateT s IO
-- () and IO ().
--
-- Luckily, we know of a function that takes an IO a and
-- returns an (m a): liftIO, enabling us to run
-- the program and see the expected results:
--
--
-- > evalStateT printState "hello"
-- "hello"
--
-- > evalStateT printState 3
-- 3
--
liftIO :: MonadIO m => IO a -> m a