xmonad-contrib-0.18.1.9: Community-maintained extensions for xmonad
CopyrightDevin Mullins <devin.mullins@gmail.com>
LicenseBSD-style (see LICENSE)
MaintainerDevin Mullins <devin.mullins@gmail.com>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
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 :: (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 :: 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 :: Settable String (XConfig l) Source #

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

focusedBorderColor :: Settable String (XConfig l) Source #

Focused windows border color. Default: "#ff0000"

terminal :: Settable String (XConfig l) Source #

The preferred terminal application. Default: "xterm"

modMask :: Settable KeyMask (XConfig l) Source #

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

borderWidth :: Settable Dimension (XConfig l) Source #

The border width (in pixels). Default: 1

focusFollowsMouse :: 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 :: 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 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 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 :: 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 :: 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 :: 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 :: 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 :: 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 :: 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 :: 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 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 :: 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 :: 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 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 :: 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 :: 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 :: (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 :: 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 :: 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 :: (XConfig l -> XConfig l') -> Prime l l' Source #

Turns a pure function on XConfig into a Prime.

applyIO :: (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.

class Typeable (a :: k) #

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

Minimal complete definition

typeRep#

getErrorEvent :: XErrorEventPtr -> IO ErrorEvent #

Retrieves error event data from a pointer to an XErrorEvent and puts it into an ErrorEvent.

setErrorHandler :: XErrorHandler -> IO () #

A binding to XSetErrorHandler. NOTE: This is pretty experimental because of safe vs. unsafe calls. I changed sync to a safe call, but there *might* be other calls that cause a problem

setClassHint :: Display -> Window -> ClassHint -> IO () #

Set the WM_CLASS property for the given window.

changeProperty32 :: Display -> Window -> Atom -> Atom -> CInt -> [CLong] -> IO () #

changeProperty16 :: Display -> Window -> Atom -> Atom -> CInt -> [CShort] -> IO () #

changeProperty8 :: Display -> Window -> Atom -> Atom -> CInt -> [CChar] -> IO () #

refreshKeyboardMapping :: Event -> IO () #

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

setConfigureEvent :: XEventPtr -> Window -> Window -> CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> IO () #

getWMProtocols :: Display -> Window -> IO [Atom] #

The XGetWMProtocols function returns the list of atoms stored in the WM_PROTOCOLS property on the specified window. These atoms describe window manager protocols in which the owner of this window is willing to participate. If the property exists, is of type ATOM, is of format 32, and the atom WM_PROTOCOLS can be interned, XGetWMProtocols sets the protocols_return argument to a list of atoms, sets the count_return argument to the number of elements in the list, and returns a nonzero status. Otherwise, it sets neither of the return arguments and returns a zero status. To release the list of atoms, use XFree.

withServer :: Display -> IO () -> IO () #

Run an action with the server

changeWindowAttributes :: Display -> Window -> AttributeMask -> Ptr SetWindowAttributes -> IO () #

interface to the X11 library function XChangeWindowAttributes().

mapRaised :: Display -> Window -> IO CInt #

A binding to XMapRaised.

data Event #

Constructors

AnyEvent 
ConfigureRequestEvent 
ConfigureEvent 
MapRequestEvent 
KeyEvent 
ButtonEvent 
MotionEvent 
DestroyWindowEvent 
UnmapEvent 
MapNotifyEvent 
MappingNotifyEvent 
CrossingEvent 
SelectionRequest 
SelectionClear 
PropertyEvent 
ExposeEvent 
FocusChangeEvent 
ClientMessageEvent 
RRScreenChangeNotifyEvent 
RRNotifyEvent 
RRCrtcChangeNotifyEvent 
RROutputChangeNotifyEvent 
RROutputPropertyNotifyEvent 
ScreenSaverNotifyEvent 

Instances

Instances details
Show Event 
Instance details

Defined in Graphics.X11.Xlib.Extras

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Message Event 
Instance details

Defined in XMonad.Core

newtype FontSet #

Constructors

FontSet (Ptr FontSet) 

Instances

Instances details
Show FontSet 
Instance details

Defined in Graphics.X11.Xlib.Extras

Eq FontSet 
Instance details

Defined in Graphics.X11.Xlib.Extras

Methods

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

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

Ord FontSet 
Instance details

Defined in Graphics.X11.Xlib.Extras

data ClassHint #

Constructors

ClassHint 

Fields

type XErrorEventPtr = Ptr () #

restackWindows :: Display -> [Window] -> IO () #

interface to the X11 library function XRestackWindows().

withdrawWindow :: Display -> Window -> ScreenNumber -> IO () #

interface to the X11 library function XWithdrawWindow().

iconifyWindow :: Display -> Window -> ScreenNumber -> IO () #

interface to the X11 library function XIconifyWindow().

translateCoordinates :: Display -> Window -> Window -> Position -> Position -> IO (Bool, Position, Position, Window) #

interface to the X11 library function XTranslateCoordinates().

storeName :: Display -> Window -> String -> IO () #

interface to the X11 library function XStoreName().

createSimpleWindow :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> CInt -> Pixel -> Pixel -> IO Window #

interface to the X11 library function XCreateSimpleWindow().

createWindow :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> CInt -> CInt -> WindowClass -> Visual -> AttributeMask -> Ptr SetWindowAttributes -> IO Window #

interface to the X11 library function XCreateWindow().

moveResizeWindow :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> IO () #

interface to the X11 library function XMoveResizeWindow().

resizeWindow :: Display -> Window -> Dimension -> Dimension -> IO () #

interface to the X11 library function XResizeWindow().

moveWindow :: Display -> Window -> Position -> Position -> IO () #

interface to the X11 library function XMoveWindow().

reparentWindow :: Display -> Window -> Window -> Position -> Position -> IO () #

interface to the X11 library function XReparentWindow().

mapSubwindows :: Display -> Window -> IO () #

interface to the X11 library function XMapSubwindows().

unmapSubwindows :: Display -> Window -> IO () #

interface to the X11 library function XUnmapSubwindows().

mapWindow :: Display -> Window -> IO () #

interface to the X11 library function XMapWindow().

lowerWindow :: Display -> Window -> IO () #

interface to the X11 library function XLowerWindow().

raiseWindow :: Display -> Window -> IO () #

interface to the X11 library function XRaiseWindow().

circulateSubwindowsDown :: Display -> Window -> IO () #

interface to the X11 library function XCirculateSubwindowsDown().

circulateSubwindowsUp :: Display -> Window -> IO () #

interface to the X11 library function XCirculateSubwindowsUp().

circulateSubwindows :: Display -> Window -> CirculationDirection -> IO () #

interface to the X11 library function XCirculateSubwindows().

destroyWindow :: Display -> Window -> IO () #

interface to the X11 library function XDestroyWindow().

destroySubwindows :: Display -> Window -> IO () #

interface to the X11 library function XDestroySubwindows().

setWindowBorder :: Display -> Window -> Pixel -> IO () #

interface to the X11 library function XSetWindowBorder().

setWindowBorderPixmap :: Display -> Window -> Pixmap -> IO () #

interface to the X11 library function XSetWindowBorderPixmap().

setWindowBorderWidth :: Display -> Window -> Dimension -> IO () #

interface to the X11 library function XSetWindowBorderWidth().

setWindowBackground :: Display -> Window -> Pixel -> IO () #

interface to the X11 library function XSetWindowBackground().

setWindowBackgroundPixmap :: Display -> Window -> Pixmap -> IO () #

interface to the X11 library function XSetWindowBackgroundPixmap().

setWindowColormap :: Display -> Window -> Colormap -> IO () #

interface to the X11 library function XSetWindowColormap().

addToSaveSet :: Display -> Window -> IO () #

interface to the X11 library function XAddToSaveSet().

removeFromSaveSet :: Display -> Window -> IO () #

interface to the X11 library function XRemoveFromSaveSet().

changeSaveSet :: Display -> Window -> ChangeSaveSetMode -> IO () #

interface to the X11 library function XChangeSaveSet().

clearWindow :: Display -> Window -> IO () #

interface to the X11 library function XClearWindow().

clearArea :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> Bool -> IO () #

interface to the X11 library function XClearArea().

setTextProperty :: Display -> Window -> String -> Atom -> IO () #

interface to the X11 library function XSetTextProperty().

rotateBuffers :: Display -> CInt -> IO () #

interface to the X11 library function XRotateBuffers().

fetchBytes :: Display -> IO String #

interface to the X11 library function XFetchBytes().

fetchBuffer :: Display -> CInt -> IO String #

interface to the X11 library function XFetchBuffer().

storeBytes :: Display -> String -> IO () #

interface to the X11 library function XStoreBytes().

storeBuffer :: Display -> String -> CInt -> IO () #

interface to the X11 library function XStoreBuffer().

drawImageString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO () #

interface to the X11 library function XDrawImageString().

drawString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO () #

interface to the X11 library function XDrawString().

fillArcs :: Display -> Drawable -> GC -> [Arc] -> IO () #

interface to the X11 library function XFillArcs().

fillPolygon :: Display -> Drawable -> GC -> [Point] -> PolygonShape -> CoordinateMode -> IO () #

interface to the X11 library function XFillPolygon().

fillRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO () #

interface to the X11 library function XFillRectangles().

drawArcs :: Display -> Drawable -> GC -> [Arc] -> IO () #

interface to the X11 library function XDrawArcs().

drawRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO () #

interface to the X11 library function XDrawRectangles().

drawSegments :: Display -> Drawable -> GC -> [Segment] -> IO () #

interface to the X11 library function XDrawSegments().

drawLines :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO () #

interface to the X11 library function XDrawLines().

drawPoints :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO () #

interface to the X11 library function XDrawPoints().

setWMProtocols :: Display -> Window -> [Atom] -> IO () #

interface to the X11 library function XSetWMProtocols().

recolorCursor :: Display -> Cursor -> Color -> Color -> IO () #

interface to the X11 library function XRecolorCursor().

createGlyphCursor :: Display -> Font -> Font -> Glyph -> Glyph -> Color -> Color -> IO Cursor #

interface to the X11 library function XCreateGlyphCursor().

createPixmapCursor :: Display -> Pixmap -> Pixmap -> Color -> Color -> Dimension -> Dimension -> IO Cursor #

interface to the X11 library function XCreatePixmapCursor().

setIconName :: Display -> Window -> String -> IO () #

interface to the X11 library function XSetIconName().

getIconName :: Display -> Window -> IO String #

interface to the X11 library function XGetIconName().

lookupString :: XKeyEventPtr -> IO (Maybe KeySym, String) #

interface to the X11 library function XLookupString().

stringToKeysym :: String -> KeySym #

interface to the X11 library function XStringToKeysym().

keysymToString :: KeySym -> String #

interface to the X11 library function XKeysymToString().

displayKeycodes :: Display -> (CInt, CInt) #

interface to the X11 library function XDisplayKeycodes().

readBitmapFile :: Display -> Drawable -> String -> IO (Either String (Dimension, Dimension, Pixmap, Maybe CInt, Maybe CInt)) #

interface to the X11 library function XReadBitmapFile.

matchVisualInfo :: Display -> ScreenNumber -> CInt -> CInt -> IO (Maybe VisualInfo) #

interface to the X11 library function XMatchVisualInfo()

visualBlueMaskMask :: VisualInfoMask #

interface to the X11 library function XGetVisualInfo()

getPointerControl :: Display -> IO (CInt, CInt, CInt) #

interface to the X11 library function XGetPointerControl().

setLocaleModifiers :: String -> IO String #

interface to the X11 library function XSetLocaleModifiers().

getGeometry :: Display -> Drawable -> IO (Window, Position, Position, Dimension, Dimension, Dimension, CInt) #

interface to the X11 library function XGetGeometry().

geometry :: Display -> CInt -> String -> String -> Dimension -> Dimension -> Dimension -> CInt -> CInt -> IO (CInt, Position, Position, Dimension, Dimension) #

interface to the X11 library function XGeometry().

setDefaultErrorHandler :: IO () #

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.

displayName :: String -> String #

interface to the X11 library function XDisplayName().

queryPointer :: Display -> Window -> IO (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier) #

interface to the X11 library function XQueryPointer().

queryBestSize :: Display -> QueryBestSizeClass -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) #

interface to the X11 library function XQueryBestSize().

queryBestCursor :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) #

interface to the X11 library function XQueryBestCursor().

queryBestStipple :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) #

interface to the X11 library function XQueryBestStipple().

queryBestTile :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) #

interface to the X11 library function XQueryBestTile().

getInputFocus :: Display -> IO (Window, FocusMode) #

interface to the X11 library function XGetInputFocus().

rmInitialize :: IO () #

interface to the X11 library function XrmInitialize().

autoRepeatOff :: Display -> IO () #

interface to the X11 library function XAutoRepeatOff().

autoRepeatOn :: Display -> IO () #

interface to the X11 library function XAutoRepeatOn().

bell :: Display -> CInt -> IO () #

interface to the X11 library function XBell().

setCloseDownMode :: Display -> CloseDownMode -> IO () #

interface to the X11 library function XSetCloseDownMode().

lastKnownRequestProcessed :: Display -> IO CInt #

interface to the X11 library function XLastKnownRequestProcessed().

setInputFocus :: Display -> Window -> FocusMode -> Time -> IO () #

interface to the X11 library function XSetInputFocus().

grabButton :: Display -> Button -> ButtonMask -> Window -> Bool -> EventMask -> GrabMode -> GrabMode -> Window -> Cursor -> IO () #

interface to the X11 library function XGrabButton().

ungrabButton :: Display -> Button -> ButtonMask -> Window -> IO () #

interface to the X11 library function XUngrabButton().

grabPointer :: Display -> Window -> Bool -> EventMask -> GrabMode -> GrabMode -> Window -> Cursor -> Time -> IO GrabStatus #

interface to the X11 library function XGrabPointer().

ungrabPointer :: Display -> Time -> IO () #

interface to the X11 library function XUngrabPointer().

grabKey :: Display -> KeyCode -> KeyMask -> Window -> Bool -> GrabMode -> GrabMode -> IO () #

interface to the X11 library function XGrabKey().

ungrabKey :: Display -> KeyCode -> KeyMask -> Window -> IO () #

interface to the X11 library function XUngrabKey().

grabKeyboard :: Display -> Window -> Bool -> GrabMode -> GrabMode -> Time -> IO GrabStatus #

interface to the X11 library function XGrabKeyboard().

ungrabKeyboard :: Display -> Time -> IO () #

interface to the X11 library function XUngrabKeyboard().

grabServer :: Display -> IO () #

interface to the X11 library function XGrabServer().

ungrabServer :: Display -> IO () #

interface to the X11 library function XUngrabServer().

supportsLocale :: IO Bool #

interface to the X11 library function XSupportsLocale().

setScreenSaver :: Display -> CInt -> CInt -> PreferBlankingMode -> AllowExposuresMode -> IO () #

interface to the X11 library function XSetScreenSaver().

activateScreenSaver :: Display -> IO () #

interface to the X11 library function XActivateScreenSaver().

resetScreenSaver :: Display -> IO () #

interface to the X11 library function XResetScreenSaver().

forceScreenSaver :: Display -> ScreenSaverMode -> IO () #

interface to the X11 library function XForceScreenSaver().

warpPointer :: Display -> Window -> Window -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> IO () #

interface to the X11 library function XWarpPointer().

visualIDFromVisual :: Visual -> IO VisualID #

see XVisualIDFromVisual()

createPixmap :: Display -> Drawable -> Dimension -> Dimension -> CInt -> IO Pixmap #

interface to the X11 library function XCreatePixmap().

freePixmap :: Display -> Pixmap -> IO () #

interface to the X11 library function XFreePixmap().

bitmapBitOrder :: Display -> ByteOrder #

interface to the X11 library function XBitmapBitOrder().

bitmapUnit :: Display -> CInt #

interface to the X11 library function XBitmapUnit().

bitmapPad :: Display -> CInt #

interface to the X11 library function XBitmapPad().

lookupKeysym :: XKeyEventPtr -> CInt -> IO KeySym #

interface to the X11 library function XLookupKeysym().

keycodeToKeysym :: Display -> KeyCode -> CInt -> IO KeySym #

interface to the X11 library function XKeycodeToKeysym().

keysymToKeycode :: Display -> KeySym -> IO KeyCode #

interface to the X11 library function XKeysymToKeycode().

defineCursor :: Display -> Window -> Cursor -> IO () #

interface to the X11 library function XDefineCursor().

undefineCursor :: Display -> Window -> IO () #

interface to the X11 library function XUndefineCursor().

createFontCursor :: Display -> Glyph -> IO Cursor #

interface to the X11 library function XCreateFontCursor().

freeCursor :: Display -> Font -> IO () #

interface to the X11 library function XFreeCursor().

drawPoint :: Display -> Drawable -> GC -> Position -> Position -> IO () #

interface to the X11 library function XDrawPoint().

drawLine :: Display -> Drawable -> GC -> Position -> Position -> Position -> Position -> IO () #

interface to the X11 library function XDrawLine().

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

interface to the X11 library function XDrawRectangle().

drawArc :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> IO () #

interface to the X11 library function XDrawArc().

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

interface to the X11 library function XFillRectangle().

fillArc :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> IO () #

interface to the X11 library function XFillArc().

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

interface to the X11 library function XCopyArea().

copyPlane :: Display -> Drawable -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> Pixel -> IO () #

interface to the X11 library function XCopyPlane().

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

interface to the X11 library function XInternAtom().

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

interface to the X11 library function XQueryColors().

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

interface to the X11 library function XQueryColor().

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

interface to the X11 library function XStoreColor().

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

interface to the X11 library function XFreeColors().

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

interface to the X11 library function XParseColor().

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

interface to the X11 library function XAllocColor().

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

interface to the X11 library function XAllocNamedColor().

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

interface to the X11 library function XLookupColor().

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

interface to the X11 library function XInstallColormap().

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

interface to the X11 library function XUninstallColormap().

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

interface to the X11 library function XCopyColormapAndFree().

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

interface to the X11 library function XCreateColormap().

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

interface to the X11 library function XFreeColormap().

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

partial interface to the X11 library function XCreateGC().

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

interface to the X11 library function XSetDashes().

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

interface to the X11 library function XSetArcMode().

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

interface to the X11 library function XSetBackground().

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

interface to the X11 library function XSetForeground().

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

interface to the X11 library function XSetFunction().

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

interface to the X11 library function XSetGraphicsExposures().

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

interface to the X11 library function XSetClipMask().

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

interface to the X11 library function XSetClipOrigin().

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

interface to the X11 library function XSetFillRule().

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

interface to the X11 library function XSetFillStyle().

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

interface to the X11 library function XSetFont().

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

interface to the X11 library function XSetLineAttributes().

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

interface to the X11 library function XSetPlaneMask().

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

interface to the X11 library function XSetState().

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

interface to the X11 library function XSetStipple().

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

interface to the X11 library function XSetSubwindowMode().

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

interface to the X11 library function XSetTSOrigin().

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

interface to the X11 library function XSetTile().

gContextFromGC :: GC -> GContext #

interface to the X11 library function XGContextFromGC().

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

interface to the X11 library function XFreeGC().

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

interface to the X11 library function XFlushGC().

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

interface to the X11 library function XCopyGC().

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

interface to the X11 library function XSendEvent().

gettimeofday_in_milliseconds :: IO Integer #

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

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

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

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

flush :: Display -> IO () #

interface to the X11 library function XFlush().

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

interface to the X11 library function XSync().

pending :: Display -> IO CInt #

interface to the X11 library function XPending().

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

interface to the X11 library function XEventsQueued().

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

interface to the X11 library function XNextEvent().

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

interface to the X11 library function XAllowEvents().

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

interface to the X11 library function XSelectInput().

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

interface to the X11 library function XWindowEvent().

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

interface to the X11 library function XCheckWindowEvent().

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

interface to the X11 library function XMaskEvent().

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

interface to the X11 library function XCheckMaskEvent().

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

interface to the X11 library function XCheckTypedEvent().

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

interface to the X11 library function XCheckTypedWindowEvent().

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

interface to the X11 library function XPutBackEvent().

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

interface to the X11 library function XPeekEvent().

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

openDisplay :: String -> IO Display #

interface to the X11 library function XOpenDisplay().

serverVendor :: Display -> String #

interface to the X11 library function XServerVendor().

displayString :: Display -> String #

interface to the X11 library function XDisplayString().

screenResourceString :: Screen -> String #

interface to the X11 library function XScreenResourceString().

resourceManagerString :: Display -> String #

interface to the X11 library function XResourceManagerString().

allPlanes_aux :: Pixel #

interface to the X11 library function XAllPlanes().

blackPixel :: Display -> ScreenNumber -> Pixel #

interface to the X11 library function XBlackPixel().

whitePixel :: Display -> ScreenNumber -> Pixel #

interface to the X11 library function XWhitePixel().

connectionNumber :: Display -> CInt #

interface to the X11 library function XConnectionNumber().

defaultColormap :: Display -> ScreenNumber -> Colormap #

interface to the X11 library function XDefaultColormap().

defaultGC :: Display -> ScreenNumber -> GC #

interface to the X11 library function XDefaultGC().

defaultDepth :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDefaultDepth().

defaultScreen :: Display -> ScreenNumber #

interface to the X11 library function XDefaultScreen().

defaultScreenOfDisplay :: Display -> Screen #

interface to the X11 library function XDefaultScreenOfDisplay().

displayHeight :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayHeight().

displayHeightMM :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayHeightMM().

displayWidth :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayWidth().

displayWidthMM :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayWidthMM().

maxRequestSize :: Display -> CInt #

interface to the X11 library function XMaxRequestSize().

displayMotionBufferSize :: Display -> CInt #

interface to the X11 library function XDisplayMotionBufferSize().

imageByteOrder :: Display -> CInt #

interface to the X11 library function XImageByteOrder().

protocolRevision :: Display -> CInt #

interface to the X11 library function XProtocolRevision().

protocolVersion :: Display -> CInt #

interface to the X11 library function XProtocolVersion().

screenCount :: Display -> CInt #

interface to the X11 library function XScreenCount().

defaultVisual :: Display -> ScreenNumber -> Visual #

interface to the X11 library function XDefaultVisual().

displayCells :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayCells().

displayPlanes :: Display -> ScreenNumber -> CInt #

interface to the X11 library function XDisplayPlanes().

screenOfDisplay :: Display -> ScreenNumber -> Screen #

interface to the X11 library function XScreenOfDisplay().

defaultRootWindow :: Display -> Window #

interface to the X11 library function XDefaultRootWindow().

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

interface to the X11 library function XRootWindow().

qLength :: Display -> IO CInt #

interface to the X11 library function XQLength().

noOp :: Display -> IO () #

interface to the X11 library function XNoOp().

closeDisplay :: Display -> IO () #

interface to the X11 library function XCloseDisplay().

textWidth :: FontStruct -> String -> Int32 #

interface to the X11 library function XTextWidth().

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

interface to the X11 library function XTextExtents().

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

interface to the X11 library function XLoadQueryFont().

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

interface to the X11 library function XGetGCValues().

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

interface to the X11 library function XQueryFont().

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

interface to the X11 library function XFreeFont().

type Glyph = Word16 #

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

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

interface to the X11 library function XGetPixel().

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

interface to the X11 library function XGetImage().

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

interface to the X11 library function XCreateImage().

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

interface to the X11 library function XPutImage().

destroyImage :: Image -> IO () #

interface to the X11 library function XDestroyImage().

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

interface to the X11 library function XSetRegion().

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

interface to the X11 library function XShrinkRegion().

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

interface to the X11 library function XOffsetRegion().

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

interface to the X11 library function XClipBox().

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

interface to the X11 library function XRectInRegion().

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

interface to the X11 library function XPointInRegion().

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

interface to the X11 library function XEqualRegion().

emptyRegion :: Region -> IO Bool #

interface to the X11 library function XEmptyRegion().

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

interface to the X11 library function XXorRegion().

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

interface to the X11 library function XUnionRegion().

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

interface to the X11 library function XUnionRectWithRegion().

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

interface to the X11 library function XSubtractRegion().

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

interface to the X11 library function XIntersectRegion().

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

interface to the X11 library function XPolygonRegion().

createRegion :: IO Region #

interface to the X11 library function XCreateRegion().

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

blackPixelOfScreen :: Screen -> Pixel #

interface to the X11 library function XBlackPixelOfScreen().

whitePixelOfScreen :: Screen -> Pixel #

interface to the X11 library function XWhitePixelOfScreen().

cellsOfScreen :: Screen -> CInt #

interface to the X11 library function XCellsOfScreen().

defaultColormapOfScreen :: Screen -> Colormap #

interface to the X11 library function XDefaultColormapOfScreen().

defaultDepthOfScreen :: Screen -> CInt #

interface to the X11 library function XDefaultDepthOfScreen().

defaultGCOfScreen :: Screen -> GC #

interface to the X11 library function XDefaultGCOfScreen().

defaultVisualOfScreen :: Screen -> Visual #

interface to the X11 library function XDefaultVisualOfScreen().

doesBackingStore :: Screen -> Bool #

interface to the X11 library function XDoesBackingStore().

doesSaveUnders :: Screen -> Bool #

interface to the X11 library function XDoesSaveUnders().

displayOfScreen :: Screen -> Display #

interface to the X11 library function XDisplayOfScreen().

eventMaskOfScreen :: Screen -> EventMask #

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

minCmapsOfScreen :: Screen -> CInt #

interface to the X11 library function XMinCmapsOfScreen().

maxCmapsOfScreen :: Screen -> CInt #

interface to the X11 library function XMaxCmapsOfScreen().

rootWindowOfScreen :: Screen -> Window #

interface to the X11 library function XRootWindowOfScreen().

widthOfScreen :: Screen -> Dimension #

interface to the X11 library function XWidthOfScreen().

widthMMOfScreen :: Screen -> Dimension #

interface to the X11 library function XWidthMMOfScreen().

heightOfScreen :: Screen -> Dimension #

interface to the X11 library function XHeightOfScreen().

heightMMOfScreen :: Screen -> Dimension #

interface to the X11 library function XHeightMMOfScreen().

planesOfScreen :: Screen -> CInt #

interface to the X11 library function XPlanesOfScreen().

screenNumberOfScreen :: Screen -> ScreenNumber #

interface to the X11 library function XScreenNumberOfScreen().

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

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 #

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 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 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 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 ::