xmonad-contrib-0.18.1: Community-maintained extensions for xmonad
CopyrightDevin Mullins <devin.mullins@gmail.com>
LicenseBSD-style (see LICENSE)
MaintainerDevin Mullins <devin.mullins@gmail.com>
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell2010

XMonad.Config.Prime

Description

Deprecated: This module is a perpetual draft and will therefore be removed from xmonad-contrib in the near future.

This is a draft of a brand new config syntax for xmonad. It aims to be:

  • easier to copy/paste snippets from the docs
  • easier to get the gist for what's going on, for you imperative programmers

It's brand new, so it's pretty much guaranteed to break or change syntax. But what's the worst that could happen? Xmonad crashes and logs you out? It probably won't do that. Give it a try.

Synopsis

Start here

To start with, create a xmonad.hs that looks like this:

{-# LANGUAGE RebindableSyntax #-}
import XMonad.Config.Prime

-- Imports go here.

main = xmonad $ do
  nothing
  -- Configs go here.

This will give you a default xmonad install, with room to grow. The lines starting with double dashes are comments. You may delete them. Note that Haskell is a bit precise about indentation. Make sure all the statements in your do-block start at the same column, and make sure that any multi-line statements are formatted with a hanging indent. (For an example, see the 'keys =+' statement in the Example config section, below.)

After changing your config file, restart xmonad with mod-q (where, by default, "mod" == "alt").

xmonad :: forall a (l :: Type -> Type). (Default a, Read (l Window), LayoutClass l Window) => (a -> IO (XConfig l)) -> IO () Source #

This is the xmonad main function. It passes def (the default XConfig) into your do-block, takes the modified config out of your do-block, and then runs xmonad.

The do-block is a Prime. Advanced readers can skip right to that definition.

nothing :: forall (l :: Type -> Type). Prime l l Source #

This doesn't modify the config in any way. It's just here for your initial config because Haskell doesn't allow empty do-blocks. Feel free to delete it once you've added other stuff.

Attributes you can set

These are a bunch of attributes that you can set. Syntax looks like this:

  terminal =: "urxvt"

Strings are double quoted, Dimensions are unquoted integers, booleans are True or False (case-sensitive), and modMask is usually mod1Mask or mod4Mask.

normalBorderColor :: forall (l :: Type -> Type). Settable String (XConfig l) Source #

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

focusedBorderColor :: forall (l :: Type -> Type). Settable String (XConfig l) Source #

Focused windows border color. Default: "#ff0000"

terminal :: forall (l :: Type -> Type). Settable String (XConfig l) Source #

The preferred terminal application. Default: "xterm"

modMask :: forall (l :: Type -> Type). Settable KeyMask (XConfig l) Source #

The mod modifier, as used by key bindings. Default: mod1Mask (which is probably alt on your computer).

borderWidth :: forall (l :: Type -> Type). Settable Dimension (XConfig l) Source #

The border width (in pixels). Default: 1

focusFollowsMouse :: forall (l :: Type -> Type). Settable Bool (XConfig l) Source #

Whether window focus follows the mouse cursor on move, or requires a mouse click. (Mouse? What's that?) Default: True

clickJustFocuses :: forall (l :: Type -> Type). Settable Bool (XConfig l) Source #

If True, a mouse click on an inactive window focuses it, but the click is not passed to the window. If False, the click is also passed to the window. Default True

class SettableClass (s :: Type -> Type) x y | s -> x y where Source #

Methods

(=:) :: s c -> y -> Arr c c Source #

This lets you modify an attribute.

Instances

Instances details
UpdateableClass s x y => SettableClass s x y Source # 
Instance details

Defined in XMonad.Config.Prime

Methods

(=:) :: s c -> y -> Arr c c Source #

class UpdateableClass (s :: Type -> Type) x y | s -> x y where Source #

Methods

(=.) :: s c -> (x -> y) -> Arr c c Source #

This lets you apply a function to an attribute (i.e. read, modify, write).

Attributes you can add to

In addition to being able to set these attributes, they have a special syntax for being able to add to them. The operator is =+ (the plus comes after the equals), but each attribute has a different syntax for what comes after the operator.

manageHook :: forall (l :: Type -> Type). Summable ManageHook ManageHook (XConfig l) Source #

The action to run when a new window is opened. Default:

  manageHook =: composeAll [className =? "MPlayer" --> doFloat, className =? "Gimp" --> doFloat]

To add more rules to this list, you can say, for instance:

import XMonad.StackSet
...
  manageHook =+ (className =? "Emacs" --> doF kill)
  manageHook =+ (className =? "Vim" --> doF shiftMaster)

Note that operator precedence mandates the parentheses here.

handleEventHook :: forall (l :: Type -> Type). Summable (Event -> X All) (Event -> X All) (XConfig l) Source #

Custom X event handler. Return All True if the default handler should also be run afterwards. Default does nothing. To add an event handler:

import XMonad.Hooks.ServerMode
...
  handleEventHook =+ serverModeEventHook

workspaces :: forall (l :: Type -> Type). Summable [String] [String] (XConfig l) Source #

List of workspaces' names. Default: map show [1 .. 9 :: Int]. Adding appends to the end:

  workspaces =+ ["0"]

This is useless unless you also create keybindings for this.

logHook :: forall (l :: Type -> Type). Summable (X ()) (X ()) (XConfig l) Source #

The action to perform when the windows set is changed. This happens whenever focus change, a window is moved, etc. logHook =+ takes an X () and appends it via (>>). For instance:

import XMonad.Hooks.ICCCMFocus
...
  logHook =+ takeTopFocus

Note that if your expression is parametrically typed (e.g. of type MonadIO m => m ()), you'll need to explicitly annotate it, like so:

  logHook =+ (io $ putStrLn "Hello, world!" :: X ())

startupHook :: forall (l :: Type -> Type). Summable (X ()) (X ()) (XConfig l) Source #

The action to perform on startup. startupHook =+ takes an X () and appends it via (>>). For instance:

import XMonad.Hooks.SetWMName
...
  startupHook =+ setWMName "LG3D"

Note that if your expression is parametrically typed (e.g. of type MonadIO m => m ()), you'll need to explicitly annotate it, as documented in logHook.

clientMask :: forall (l :: Type -> Type). Summable EventMask EventMask (XConfig l) Source #

The client events that xmonad is interested in. This is useful in combination with handleEventHook. Default: structureNotifyMask .|. enterWindowMask .|. propertyChangeMask

  clientMask =+ keyPressMask .|. keyReleaseMask

rootMask :: forall (l :: Type -> Type). Summable EventMask EventMask (XConfig l) Source #

The root events that xmonad is interested in. This is useful in combination with handleEventHook. Default: substructureRedirectMask .|. substructureNotifyMask .|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask .|. buttonPressMask

class SummableClass (s :: Type -> Type) y | s -> y where Source #

Methods

(=+) :: s c -> y -> Arr c c infix 0 Source #

This lets you add to an attribute.

Attributes you can add to or remove from

The following support the the =+ for adding items and the =- operator for removing items.

keys :: forall (l :: Type -> Type). Keys (XConfig l) Source #

Key bindings to X actions. Default: see `man xmonad`. keys takes a list of keybindings specified emacs-style, as documented in mkKeyMap. For example, to change the "kill window" key:

  keys =- ["M-S-c"]
  keys =+ [("M-M1-x", kill)]

mouseBindings :: forall (l :: Type -> Type). MouseBindings (XConfig l) Source #

Mouse button bindings to an X actions on a window. Default: see `man xmonad`. To make mod-<scrollwheel> switch workspaces:

import XMonad.Actions.CycleWS (nextWS, prevWS)
...
  mouseBindings =+ [((mod4Mask, button4), const prevWS),
                    ((mod4Mask, button5), const nextWS)]

Note that you need to specify the numbered mod-mask e.g. mod4Mask instead of just modMask.

class RemovableClass (r :: Type -> Type) y | r -> y where Source #

Methods

(=-) :: r c -> y -> Arr c c infix 0 Source #

This lets you remove from an attribute.

Modifying the list of workspaces

Workspaces can be configured through workspaces, but then the keys need to be set, and this can be a bit laborious. withWorkspaces provides a convenient mechanism for common workspace updates.

withWorkspaces :: forall (l :: Type -> Type). Arr WorkspaceConfig WorkspaceConfig -> Prime l l Source #

Configure workspaces through a Prime-like interface. Example:

  withWorkspaces $ do
    wsKeys =+ ["0"]
    wsActions =+ [("M-M1-", windows . swapWithCurrent)]
    wsSetName 1 "mail"

This will set workspaces and add the necessary keybindings to keys. Note that it won't remove old keybindings; it's just not that clever.

wsNames :: Settable [String] WorkspaceConfig Source #

The list of workspace names, like workspaces but with two differences:

  1. If any entry is the empty string, it'll be replaced with the corresponding entry in wsKeys.
  2. The list is truncated to the size of wsKeys.

The default value is repeat "".

If you'd like to create workspaces without associated keyspecs, you can do that afterwards, outside the withWorkspaces block, with workspaces =+.

wsKeys :: Summable [String] [String] WorkspaceConfig Source #

The list of workspace keys. These are combined with the modifiers in wsActions to form the keybindings for navigating to workspaces. Default: ["1","2",...,"9"].

wsActions :: Summable [(String, String -> X ())] [(String, String -> X ())] WorkspaceConfig Source #

Mapping from key prefix to command. Its type is [(String, String -> X())]. The key prefix may be a modifier such as "M-", or a submap prefix such as "M-a ", or both, as in "M-a M-". The command is a function that takes a workspace name and returns an X (). withWorkspaces creates keybindings for the cartesian product of wsKeys and wsActions.

Default:

[("M-", windows . W.greedyView),
 ("M-S-", windows . W.shift)]

wsSetName :: Int -> String -> Arr WorkspaceConfig WorkspaceConfig Source #

A convenience for just modifying one entry in wsNames, in case you only want a few named workspaces. Example:

    wsSetName 1 "mail"
    wsSetName 2 "web"

Modifying the screen keybindings

withScreens provides a convenient mechanism to set keybindings for moving between screens, much like withWorkspaces.

withScreens :: forall (l :: Type -> Type). Arr ScreenConfig ScreenConfig -> Prime l l Source #

Configure screen keys through a Prime-like interface:

  withScreens $ do
    sKeys =: ["e", "r"]

This will add the necessary keybindings to keys. Note that it won't remove old keybindings; it's just not that clever.

sKeys :: Summable [String] [String] ScreenConfig Source #

The list of screen keys. These are combined with the modifiers in sActions to form the keybindings for navigating to workspaces. Default: ["w","e","r"].

sActions :: Summable [(String, ScreenId -> X ())] [(String, ScreenId -> X ())] ScreenConfig Source #

Mapping from key prefix to command. Its type is [(String, ScreenId -> X())]. Works the same as wsActions except for a different function type.

Default:

[("M-", windows . onScreens W.view),
 ("M-S-", windows . onScreens W.shift)]

onScreens :: Eq s => (i -> StackSet i l a s sd -> StackSet i l a s sd) -> s -> StackSet i l a s sd -> StackSet i l a s sd Source #

Converts a stackset transformer parameterized on the workspace type into one parameterized on the screen type. For example, you can use onScreens W.view 0 to navigate to the workspace on the 0th screen. If the screen id is not recognized, the returned transformer acts as an identity function.

Modifying the layoutHook

Layouts are special. You can't modify them using the =: or =. operator. You need to use the following functions.

addLayout :: forall (l :: Type -> Type) r. (LayoutClass l Window, LayoutClass r Window) => r Window -> Prime l (Choose l r) Source #

Add a layout to the list of layouts choosable with mod-space. For instance:

import XMonad.Layout.Tabbed
...
  addLayout simpleTabbed

resetLayout :: forall r (l :: Type -> Type). LayoutClass r Window => r Window -> Prime l r Source #

Reset the layoutHook from scratch. For instance, to get rid of the wide layout:

  resetLayout $ Tall 1 (3/100) (1/2) ||| Full

(The dollar is like an auto-closing parenthesis, so all the stuff to the right of it is treated like an argument to resetLayout.)

modifyLayout :: LayoutClass r Window => (l Window -> r Window) -> Prime l r Source #

Modify your layoutHook with some wrapper function. You probably want to call this after you're done calling addLayout. Example:

import XMonad.Layout.NoBorders
...
  modifyLayout smartBorders

Updating the XConfig en masse

Finally, there are a few contrib modules that bundle multiple attribute updates together. There are three types: 1) wholesale replacements for the default config, 2) pure functions on the config, and 3) IO actions on the config. The syntax for each is different. Examples:

1) To start with a gnomeConfig instead of the default, we use startWith:

import XMonad.Config.Gnome
...
  startWith gnomeConfig

2) withUrgencyHook is a pure function, so we need to use apply:

import XMonad.Hooks.UrgencyHook
...
  apply $ withUrgencyHook dzenUrgencyHook

3) xmobar returns an IO (XConfig l), so we need to use applyIO:

import XMonad.Hooks.DynamicLog
...
  applyIO xmobar

startWith :: forall (l' :: Type -> Type) (l :: Type -> Type). XConfig l' -> Prime l l' Source #

Replace the current XConfig with the given one. If you use this, you probably want it to be the first line of your config.

apply :: forall (l :: Type -> Type) (l' :: Type -> Type). (XConfig l -> XConfig l') -> Prime l l' Source #

Turns a pure function on XConfig into a Prime.

applyIO :: forall (l :: Type -> Type) (l' :: Type -> Type). (XConfig l -> IO (XConfig l')) -> Prime l l' Source #

Turns an IO function on XConfig into a Prime.

The rest of the world

Everything you know and love from the core XMonad module is available for use in your config file, too.

type RRMode = Word64 #

type RRCrtc = Word64 #

type SizeID = Word16 #

type GCMask = CInt #

type ArcMode = CInt #

type FillRule = CInt #

type CapStyle = CInt #

type Status = CInt #

type GrabMode = CInt #

type Protocol = CInt #

type Place = CInt #

Place of window relative to siblings (used in Circulation requests or events)

type Button = Word32 #

type KeySym = XID #

type KeyCode = Word8 #

type GContext = XID #

type Colormap = XID #

type Cursor = XID #

type Pixmap = XID #

type Font = XID #

type Drawable = XID #

type Window = XID #

type Time = Word64 #

type Atom = Word64 #

type Mask = Word64 #

type XID = Word64 #

badGC :: ErrorCode #

Xlib functions with return values of type Status return zero on failure and nonzero on success.

xFree :: Ptr a -> IO CInt #

data Color #

counterpart of an X11 XColor structure

Instances

Instances details
Data Color 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Color -> c Color #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Color #

toConstr :: Color -> Constr #

dataTypeOf :: Color -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Color) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color) #

gmapT :: (forall b. Data b => b -> b) -> Color -> Color #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r #

gmapQ :: (forall d. Data d => d -> u) -> Color -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Color -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Color -> m Color #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Color -> m Color #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Color -> m Color #

Storable Color 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

sizeOf :: Color -> Int #

alignment :: Color -> Int #

peekElemOff :: Ptr Color -> Int -> IO Color #

pokeElemOff :: Ptr Color -> Int -> Color -> IO () #

peekByteOff :: Ptr b -> Int -> IO Color #

pokeByteOff :: Ptr b -> Int -> Color -> IO () #

peek :: Ptr Color -> IO Color #

poke :: Ptr Color -> Color -> IO () #

Show Color 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Eq Color 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

data Segment #

counterpart of an X11 XSegment structure

Constructors

Segment 

Instances

Instances details
Data Segment 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Segment -> c Segment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Segment #

toConstr :: Segment -> Constr #

dataTypeOf :: Segment -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Segment) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Segment) #

gmapT :: (forall b. Data b => b -> b) -> Segment -> Segment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Segment -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Segment -> r #

gmapQ :: (forall d. Data d => d -> u) -> Segment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Segment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Segment -> m Segment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Segment -> m Segment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Segment -> m Segment #

Storable Segment 
Instance details

Defined in Graphics.X11.Xlib.Types

Show Segment 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Segment 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

(==) :: Segment -> Segment -> Bool #

(/=) :: Segment -> Segment -> Bool #

data Arc #

counterpart of an X11 XArc structure

Instances

Instances details
Storable Arc 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

sizeOf :: Arc -> Int #

alignment :: Arc -> Int #

peekElemOff :: Ptr Arc -> Int -> IO Arc #

pokeElemOff :: Ptr Arc -> Int -> Arc -> IO () #

peekByteOff :: Ptr b -> Int -> IO Arc #

pokeByteOff :: Ptr b -> Int -> Arc -> IO () #

peek :: Ptr Arc -> IO Arc #

poke :: Ptr Arc -> Arc -> IO () #

Show Arc 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

showsPrec :: Int -> Arc -> ShowS #

show :: Arc -> String #

showList :: [Arc] -> ShowS #

Eq Arc 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

(==) :: Arc -> Arc -> Bool #

(/=) :: Arc -> Arc -> Bool #

data Rectangle #

counterpart of an X11 XRectangle structure

Instances

Instances details
Data Rectangle 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rectangle -> c Rectangle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rectangle #

toConstr :: Rectangle -> Constr #

dataTypeOf :: Rectangle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rectangle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rectangle) #

gmapT :: (forall b. Data b => b -> b) -> Rectangle -> Rectangle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rectangle -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rectangle -> r #

gmapQ :: (forall d. Data d => d -> u) -> Rectangle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rectangle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rectangle -> m Rectangle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rectangle -> m Rectangle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rectangle -> m Rectangle #

Storable Rectangle 
Instance details

Defined in Graphics.X11.Xlib.Types

Read Rectangle 
Instance details

Defined in Graphics.X11.Xlib.Types

Show Rectangle 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Rectangle 
Instance details

Defined in Graphics.X11.Xlib.Types

PPrint Rectangle Source # 
Instance details

Defined in XMonad.Config.Dmwit

Methods

pprint :: Int -> Rectangle -> String Source #

data Point #

counterpart of an X11 XPoint structure

Constructors

Point 

Fields

Instances

Instances details
Data Point 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Point -> c Point #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Point #

toConstr :: Point -> Constr #

dataTypeOf :: Point -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Point) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Point) #

gmapT :: (forall b. Data b => b -> b) -> Point -> Point #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r #

gmapQ :: (forall d. Data d => d -> u) -> Point -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Point -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Point -> m Point #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Point -> m Point #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Point -> m Point #

Storable Point 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

sizeOf :: Point -> Int #

alignment :: Point -> Int #

peekElemOff :: Ptr Point -> Int -> IO Point #

pokeElemOff :: Ptr Point -> Int -> Point -> IO () #

peekByteOff :: Ptr b -> Int -> IO Point #

pokeByteOff :: Ptr b -> Int -> Point -> IO () #

peek :: Ptr Point -> IO Point #

poke :: Ptr Point -> Point -> IO () #

Show Point 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Eq Point 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

(==) :: Point -> Point -> Bool #

(/=) :: Point -> Point -> Bool #

type Buffer = CInt #

type Angle = CInt #

type Pixel = Word64 #

data Image #

pointer to an X11 XImage structure

Instances

Instances details
Data Image 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Image -> c Image #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Image #

toConstr :: Image -> Constr #

dataTypeOf :: Image -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Image) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image) #

gmapT :: (forall b. Data b => b -> b) -> Image -> Image #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r #

gmapQ :: (forall d. Data d => d -> u) -> Image -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Image -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Image -> m Image #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image #

Show Image 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Eq Image 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

(==) :: Image -> Image -> Bool #

(/=) :: Image -> Image -> Bool #

Ord Image 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

compare :: Image -> Image -> Ordering #

(<) :: Image -> Image -> Bool #

(<=) :: Image -> Image -> Bool #

(>) :: Image -> Image -> Bool #

(>=) :: Image -> Image -> Bool #

max :: Image -> Image -> Image #

min :: Image -> Image -> Image #

data SetWindowAttributes #

pointer to an X11 XSetWindowAttributes structure

Instances

Instances details
Data SetWindowAttributes 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetWindowAttributes -> c SetWindowAttributes #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SetWindowAttributes #

toConstr :: SetWindowAttributes -> Constr #

dataTypeOf :: SetWindowAttributes -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SetWindowAttributes) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetWindowAttributes) #

gmapT :: (forall b. Data b => b -> b) -> SetWindowAttributes -> SetWindowAttributes #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetWindowAttributes -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetWindowAttributes -> r #

gmapQ :: (forall d. Data d => d -> u) -> SetWindowAttributes -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SetWindowAttributes -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetWindowAttributes -> m SetWindowAttributes #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetWindowAttributes -> m SetWindowAttributes #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetWindowAttributes -> m SetWindowAttributes #

Show SetWindowAttributes 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq SetWindowAttributes 
Instance details

Defined in Graphics.X11.Xlib.Types

Ord SetWindowAttributes 
Instance details

Defined in Graphics.X11.Xlib.Types

data GC #

pointer to an X11 GC structure

Instances

Instances details
Data GC 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GC -> c GC #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GC #

toConstr :: GC -> Constr #

dataTypeOf :: GC -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GC) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GC) #

gmapT :: (forall b. Data b => b -> b) -> GC -> GC #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r #

gmapQ :: (forall d. Data d => d -> u) -> GC -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GC -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GC -> m GC #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GC -> m GC #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GC -> m GC #

Show GC 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

showsPrec :: Int -> GC -> ShowS #

show :: GC -> String #

showList :: [GC] -> ShowS #

Eq GC 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

(==) :: GC -> GC -> Bool #

(/=) :: GC -> GC -> Bool #

Ord GC 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

compare :: GC -> GC -> Ordering #

(<) :: GC -> GC -> Bool #

(<=) :: GC -> GC -> Bool #

(>) :: GC -> GC -> Bool #

(>=) :: GC -> GC -> Bool #

max :: GC -> GC -> GC #

min :: GC -> GC -> GC #

data Visual #

pointer to an X11 Visual structure

Instances

Instances details
Data Visual 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Visual -> c Visual #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Visual #

toConstr :: Visual -> Constr #

dataTypeOf :: Visual -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Visual) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Visual) #

gmapT :: (forall b. Data b => b -> b) -> Visual -> Visual #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Visual -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Visual -> r #

gmapQ :: (forall d. Data d => d -> u) -> Visual -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Visual -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Visual -> m Visual #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Visual -> m Visual #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Visual -> m Visual #

Show Visual 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Visual 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

(==) :: Visual -> Visual -> Bool #

(/=) :: Visual -> Visual -> Bool #

Ord Visual 
Instance details

Defined in Graphics.X11.Xlib.Types

data Screen #

pointer to an X11 Screen structure

Instances

Instances details
Data Screen 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Screen -> c Screen #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Screen #

toConstr :: Screen -> Constr #

dataTypeOf :: Screen -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Screen) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Screen) #

gmapT :: (forall b. Data b => b -> b) -> Screen -> Screen #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Screen -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Screen -> r #

gmapQ :: (forall d. Data d => d -> u) -> Screen -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Screen -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Screen -> m Screen #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Screen -> m Screen #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Screen -> m Screen #

Show Screen 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Screen 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

(==) :: Screen -> Screen -> Bool #

(/=) :: Screen -> Screen -> Bool #

Ord Screen 
Instance details

Defined in Graphics.X11.Xlib.Types

PPrint Screen Source # 
Instance details

Defined in XMonad.Config.Dmwit

Methods

pprint :: Int -> Screen -> String Source #

newtype Display #

pointer to an X11 Display structure

Constructors

Display (Ptr Display) 

Instances

Instances details
Data Display 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Display -> c Display #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Display #

toConstr :: Display -> Constr #

dataTypeOf :: Display -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Display) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Display) #

gmapT :: (forall b. Data b => b -> b) -> Display -> Display #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Display -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Display -> r #

gmapQ :: (forall d. Data d => d -> u) -> Display -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Display -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Display -> m Display #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Display -> m Display #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Display -> m Display #

Show Display 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Display 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

(==) :: Display -> Display -> Bool #

(/=) :: Display -> Display -> Bool #

Ord Display 
Instance details

Defined in Graphics.X11.Xlib.Types

screenNumberOfScreen :: Screen -> ScreenNumber #

interface to the X11 library function XScreenNumberOfScreen().

planesOfScreen :: Screen -> CInt #

interface to the X11 library function XPlanesOfScreen().

heightMMOfScreen :: Screen -> Dimension #

interface to the X11 library function XHeightMMOfScreen().

heightOfScreen :: Screen -> Dimension #

interface to the X11 library function XHeightOfScreen().

widthMMOfScreen :: Screen -> Dimension #

interface to the X11 library function XWidthMMOfScreen().

widthOfScreen :: Screen -> Dimension #

interface to the X11 library function XWidthOfScreen().

rootWindowOfScreen :: Screen -> Window #

interface to the X11 library function XRootWindowOfScreen().

maxCmapsOfScreen :: Screen -> CInt #

interface to the X11 library function XMaxCmapsOfScreen().

minCmapsOfScreen :: Screen -> CInt #

interface to the X11 library function XMinCmapsOfScreen().

eventMaskOfScreen :: Screen -> EventMask #

interface to the X11 library function XEventMaskOfScreen(). Event mask at connection setup time - not current event mask!

displayOfScreen :: Screen -> Display #

interface to the X11 library function XDisplayOfScreen().

doesSaveUnders :: Screen -> Bool #

interface to the X11 library function XDoesSaveUnders().

doesBackingStore :: Screen -> Bool #

interface to the X11 library function XDoesBackingStore().

defaultVisualOfScreen :: Screen -> Visual #

interface to the X11 library function XDefaultVisualOfScreen().

defaultGCOfScreen :: Screen -> GC #

interface to the X11 library function XDefaultGCOfScreen().

defaultDepthOfScreen :: Screen -> CInt #

interface to the X11 library function XDefaultDepthOfScreen().

defaultColormapOfScreen :: Screen -> Colormap #

interface to the X11 library function XDefaultColormapOfScreen().

cellsOfScreen :: Screen -> CInt #

interface to the X11 library function XCellsOfScreen().

whitePixelOfScreen :: Screen -> Pixel #

interface to the X11 library function XWhitePixelOfScreen().

blackPixelOfScreen :: Screen -> Pixel #

interface to the X11 library function XBlackPixelOfScreen().

data Region #

Instances

Instances details
Data Region 
Instance details

Defined in Graphics.X11.Xlib.Region

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Region -> c Region #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Region #

toConstr :: Region -> Constr #

dataTypeOf :: Region -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Region) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region) #

gmapT :: (forall b. Data b => b -> b) -> Region -> Region #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r #

gmapQ :: (forall d. Data d => d -> u) -> Region -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Region -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Region -> m Region #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region #

Show Region 
Instance details

Defined in Graphics.X11.Xlib.Region

Eq Region 
Instance details

Defined in Graphics.X11.Xlib.Region

Methods

(==) :: Region -> Region -> Bool #

(/=) :: Region -> Region -> Bool #

Ord Region 
Instance details

Defined in Graphics.X11.Xlib.Region

createRegion :: IO Region #

interface to the X11 library function XCreateRegion().

polygonRegion :: [Point] -> FillRule -> IO Region #

interface to the X11 library function XPolygonRegion().

intersectRegion :: Region -> Region -> Region -> IO CInt #

interface to the X11 library function XIntersectRegion().

subtractRegion :: Region -> Region -> Region -> IO CInt #

interface to the X11 library function XSubtractRegion().

unionRectWithRegion :: Rectangle -> Region -> Region -> IO CInt #

interface to the X11 library function XUnionRectWithRegion().

unionRegion :: Region -> Region -> Region -> IO CInt #

interface to the X11 library function XUnionRegion().

xorRegion :: Region -> Region -> Region -> IO CInt #

interface to the X11 library function XXorRegion().

emptyRegion :: Region -> IO Bool #

interface to the X11 library function XEmptyRegion().

equalRegion :: Region -> Region -> IO Bool #

interface to the X11 library function XEqualRegion().

pointInRegion :: Region -> Point -> IO Bool #

interface to the X11 library function XPointInRegion().

rectInRegion :: Region -> Rectangle -> IO RectInRegionResult #

interface to the X11 library function XRectInRegion().

clipBox :: Region -> IO (Rectangle, CInt) #

interface to the X11 library function XClipBox().

offsetRegion :: Region -> Point -> IO CInt #

interface to the X11 library function XOffsetRegion().

shrinkRegion :: Region -> Point -> IO CInt #

interface to the X11 library function XShrinkRegion().

setRegion :: Display -> GC -> Region -> IO CInt #

interface to the X11 library function XSetRegion().

destroyImage :: Image -> IO () #

interface to the X11 library function XDestroyImage().

putImage :: Display -> Drawable -> GC -> Image -> Position -> Position -> Position -> Position -> Dimension -> Dimension -> IO () #

interface to the X11 library function XPutImage().

createImage :: Display -> Visual -> CInt -> ImageFormat -> CInt -> Ptr CChar -> Dimension -> Dimension -> CInt -> CInt -> IO Image #

interface to the X11 library function XCreateImage().

getImage :: Display -> Drawable -> CInt -> CInt -> CUInt -> CUInt -> CULong -> ImageFormat -> IO Image #

interface to the X11 library function XGetImage().

getPixel :: Image -> CInt -> CInt -> CULong #

interface to the X11 library function XGetPixel().

data FontStruct #

pointer to an X11 XFontStruct structure

Instances

Instances details
Data FontStruct 
Instance details

Defined in Graphics.X11.Xlib.Font

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FontStruct -> c FontStruct #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FontStruct #

toConstr :: FontStruct -> Constr #

dataTypeOf :: FontStruct -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FontStruct) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FontStruct) #

gmapT :: (forall b. Data b => b -> b) -> FontStruct -> FontStruct #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FontStruct -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FontStruct -> r #

gmapQ :: (forall d. Data d => d -> u) -> FontStruct -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FontStruct -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct #

Show FontStruct 
Instance details

Defined in Graphics.X11.Xlib.Font

Eq FontStruct 
Instance details

Defined in Graphics.X11.Xlib.Font

Ord FontStruct 
Instance details

Defined in Graphics.X11.Xlib.Font

type Glyph = Word16 #

freeFont :: Display -> FontStruct -> IO () #

interface to the X11 library function XFreeFont().

queryFont :: Display -> Font -> IO FontStruct #

interface to the X11 library function XQueryFont().

fontFromGC :: Display -> GC -> IO Font #

interface to the X11 library function XGetGCValues().

loadQueryFont :: Display -> String -> IO FontStruct #

interface to the X11 library function XLoadQueryFont().

textExtents :: FontStruct -> String -> (FontDirection, Int32, Int32, CharStruct) #

interface to the X11 library function XTextExtents().

textWidth :: FontStruct -> String -> Int32 #

interface to the X11 library function XTextWidth().

closeDisplay :: Display -> IO () #

interface to the X11 library function XCloseDisplay().

noOp :: Display -> IO () #

interface to the X11 library function XNoOp().

qLength :: Display -> IO CInt #

interface to the X11 library function XQLength().

rootWindow :: Display -> ScreenNumber -> IO Window #

interface to the X11 library function XRootWindow().

defaultRootWindow :: Display -> Window #

interface to the X11 library function XDefaultRootWindow().

screenOfDisplay :: Display -> ScreenNumber -> Screen #

interface to the X11 library function XScreenOfDisplay().

displayPlanes :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayPlanes().

displayCells :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayCells().

defaultVisual :: Display -> ScreenNumber -> Visual #

interface to the X11 library function XDefaultVisual().

screenCount :: Display -> CInt #

interface to the X11 library function XScreenCount().

protocolVersion :: Display -> CInt #

interface to the X11 library function XProtocolVersion().

protocolRevision :: Display -> CInt #

interface to the X11 library function XProtocolRevision().

imageByteOrder :: Display -> CInt #

interface to the X11 library function XImageByteOrder().

displayMotionBufferSize :: Display -> CInt #

interface to the X11 library function XDisplayMotionBufferSize().

maxRequestSize :: Display -> CInt #

interface to the X11 library function XMaxRequestSize().

displayWidthMM :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayWidthMM().

displayWidth :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayWidth().

displayHeightMM :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayHeightMM().

displayHeight :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayHeight().

defaultScreenOfDisplay :: Display -> Screen #

interface to the X11 library function XDefaultScreenOfDisplay().

defaultScreen :: Display -> ScreenNumber #

interface to the X11 library function XDefaultScreen().

defaultDepth :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDefaultDepth().

defaultGC :: Display -> ScreenNumber -> GC #

interface to the X11 library function XDefaultGC().

defaultColormap :: Display -> ScreenNumber -> Colormap #

interface to the X11 library function XDefaultColormap().

connectionNumber :: Display -> CInt #

interface to the X11 library function XConnectionNumber().

whitePixel :: Display -> ScreenNumber -> Pixel #

interface to the X11 library function XWhitePixel().

blackPixel :: Display -> ScreenNumber -> Pixel #

interface to the X11 library function XBlackPixel().

allPlanes_aux :: Pixel #

interface to the X11 library function XAllPlanes().

resourceManagerString :: Display -> String #

interface to the X11 library function XResourceManagerString().

screenResourceString :: Screen -> String #

interface to the X11 library function XScreenResourceString().

displayString :: Display -> String #

interface to the X11 library function XDisplayString().

serverVendor :: Display -> String #

interface to the X11 library function XServerVendor().

openDisplay :: String -> IO Display #

interface to the X11 library function XOpenDisplay().

newtype XEvent #

Constructors

XEvent XEventPtr 

Instances

Instances details
Data XEvent 
Instance details

Defined in Graphics.X11.Xlib.Event

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XEvent -> c XEvent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XEvent #

toConstr :: XEvent -> Constr #

dataTypeOf :: XEvent -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XEvent) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XEvent) #

gmapT :: (forall b. Data b => b -> b) -> XEvent -> XEvent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XEvent -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XEvent -> r #

gmapQ :: (forall d. Data d => d -> u) -> XEvent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> XEvent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XEvent -> m XEvent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XEvent -> m XEvent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XEvent -> m XEvent #

Show XEvent 
Instance details

Defined in Graphics.X11.Xlib.Event

Eq XEvent 
Instance details

Defined in Graphics.X11.Xlib.Event

Methods

(==) :: XEvent -> XEvent -> Bool #

(/=) :: XEvent -> XEvent -> Bool #

Ord XEvent 
Instance details

Defined in Graphics.X11.Xlib.Event

peekEvent :: Display -> XEventPtr -> IO () #

interface to the X11 library function XPeekEvent().

putBackEvent :: Display -> XEventPtr -> IO () #

interface to the X11 library function XPutBackEvent().

checkTypedWindowEvent :: Display -> Window -> EventType -> XEventPtr -> IO Bool #

interface to the X11 library function XCheckTypedWindowEvent().

checkTypedEvent :: Display -> EventType -> XEventPtr -> IO Bool #

interface to the X11 library function XCheckTypedEvent().

checkMaskEvent :: Display -> EventMask -> XEventPtr -> IO Bool #

interface to the X11 library function XCheckMaskEvent().

maskEvent :: Display -> EventMask -> XEventPtr -> IO () #

interface to the X11 library function XMaskEvent().

checkWindowEvent :: Display -> Window -> EventMask -> XEventPtr -> IO Bool #

interface to the X11 library function XCheckWindowEvent().

windowEvent :: Display -> Window -> EventMask -> XEventPtr -> IO () #

interface to the X11 library function XWindowEvent().

selectInput :: Display -> Window -> EventMask -> IO () #

interface to the X11 library function XSelectInput().

allowEvents :: Display -> AllowEvents -> Time -> IO () #

interface to the X11 library function XAllowEvents().

nextEvent :: Display -> XEventPtr -> IO () #

interface to the X11 library function XNextEvent().

eventsQueued :: Display -> QueuedMode -> IO CInt #

interface to the X11 library function XEventsQueued().

pending :: Display -> IO CInt #

interface to the X11 library function XPending().

sync :: Display -> Bool -> IO () #

interface to the X11 library function XSync().

flush :: Display -> IO () #

interface to the X11 library function XFlush().

allocaXEvent :: (XEventPtr -> IO a) -> IO a #

waitForEvent :: Display -> Word32 -> IO Bool #

Reads an event with a timeout (in microseconds). Returns True if timeout occurs.

gettimeofday_in_milliseconds :: IO Integer #

This function is somewhat compatible with Win32's TimeGetTime()

sendEvent :: Display -> Window -> Bool -> EventMask -> XEventPtr -> IO () #

interface to the X11 library function XSendEvent().

refreshKeyboardMapping :: Event -> IO () #

refreshKeyboardMapping. TODO Remove this binding when the fix has been commited to X11

copyGC :: Display -> GC -> Mask -> GC -> IO () #

interface to the X11 library function XCopyGC().

flushGC :: Display -> GC -> IO () #

interface to the X11 library function XFlushGC().

freeGC :: Display -> GC -> IO () #

interface to the X11 library function XFreeGC().

gContextFromGC :: GC -> GContext #

interface to the X11 library function XGContextFromGC().

setTile :: Display -> GC -> Pixmap -> IO () #

interface to the X11 library function XSetTile().

setTSOrigin :: Display -> GC -> Position -> Position -> IO () #

interface to the X11 library function XSetTSOrigin().

setSubwindowMode :: Display -> GC -> SubWindowMode -> IO () #

interface to the X11 library function XSetSubwindowMode().

setStipple :: Display -> GC -> Pixmap -> IO () #

interface to the X11 library function XSetStipple().

setState :: Display -> GC -> Pixel -> Pixel -> GXFunction -> Pixel -> IO () #

interface to the X11 library function XSetState().

setPlaneMask :: Display -> GC -> Pixel -> IO () #

interface to the X11 library function XSetPlaneMask().

setLineAttributes :: Display -> GC -> CInt -> LineStyle -> CapStyle -> JoinStyle -> IO () #

interface to the X11 library function XSetLineAttributes().

setFont :: Display -> GC -> Font -> IO () #

interface to the X11 library function XSetFont().

setFillStyle :: Display -> GC -> FillStyle -> IO () #

interface to the X11 library function XSetFillStyle().

setFillRule :: Display -> GC -> FillRule -> IO () #

interface to the X11 library function XSetFillRule().

setClipOrigin :: Display -> GC -> Position -> Position -> IO () #

interface to the X11 library function XSetClipOrigin().

setClipMask :: Display -> GC -> Pixmap -> IO () #

interface to the X11 library function XSetClipMask().

setGraphicsExposures :: Display -> GC -> Bool -> IO () #

interface to the X11 library function XSetGraphicsExposures().

setFunction :: Display -> GC -> GXFunction -> IO () #

interface to the X11 library function XSetFunction().

setForeground :: Display -> GC -> Pixel -> IO () #

interface to the X11 library function XSetForeground().

setBackground :: Display -> GC -> Pixel -> IO () #

interface to the X11 library function XSetBackground().

setArcMode :: Display -> GC -> ArcMode -> IO () #

interface to the X11 library function XSetArcMode().

setDashes :: Display -> GC -> CInt -> String -> CInt -> IO () #

interface to the X11 library function XSetDashes().

createGC :: Display -> Drawable -> IO GC #

partial interface to the X11 library function XCreateGC().

freeColormap :: Display -> Colormap -> IO () #

interface to the X11 library function XFreeColormap().

createColormap :: Display -> Window -> Visual -> ColormapAlloc -> IO Colormap #

interface to the X11 library function XCreateColormap().

copyColormapAndFree :: Display -> Colormap -> IO Colormap #

interface to the X11 library function XCopyColormapAndFree().

uninstallColormap :: Display -> Colormap -> IO () #

interface to the X11 library function XUninstallColormap().

installColormap :: Display -> Colormap -> IO () #

interface to the X11 library function XInstallColormap().

lookupColor :: Display -> Colormap -> String -> IO (Color, Color) #

interface to the X11 library function XLookupColor().

allocNamedColor :: Display -> Colormap -> String -> IO (Color, Color) #

interface to the X11 library function XAllocNamedColor().

allocColor :: Display -> Colormap -> Color -> IO Color #

interface to the X11 library function XAllocColor().

parseColor :: Display -> Colormap -> String -> IO Color #

interface to the X11 library function XParseColor().

freeColors :: Display -> Colormap -> [Pixel] -> Pixel -> IO () #

interface to the X11 library function XFreeColors().

storeColor :: Display -> Colormap -> Color -> IO () #

interface to the X11 library function XStoreColor().

queryColor :: Display -> Colormap -> Color -> IO Color #

interface to the X11 library function XQueryColor().

queryColors :: Display -> Colormap -> [Color] -> IO [Color] #

interface to the X11 library function XQueryColors().

internAtom :: Display -> String -> Bool -> IO Atom #

interface to the X11 library function XInternAtom().