xmonad-0.17.2: A tiling window manager
Copyright(c) Don Stewart
LicenseBSD3
MaintainerDon Stewart <dons@galois.com>
Stabilityprovisional
Portability
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad

Description

 
Synopsis

Documentation

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

interface to the X11 library function XRestackWindows().

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

interface to the X11 library function XWithdrawWindow().

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

interface to the X11 library function XIconifyWindow().

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

interface to the X11 library function XTranslateCoordinates().

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

interface to the X11 library function XStoreName().

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

interface to the X11 library function XCreateSimpleWindow().

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

interface to the X11 library function XCreateWindow().

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

interface to the X11 library function XMoveResizeWindow().

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

interface to the X11 library function XResizeWindow().

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

interface to the X11 library function XMoveWindow().

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

interface to the X11 library function XReparentWindow().

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

interface to the X11 library function XMapSubwindows().

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

interface to the X11 library function XUnmapSubwindows().

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

interface to the X11 library function XMapWindow().

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

interface to the X11 library function XLowerWindow().

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

interface to the X11 library function XRaiseWindow().

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

interface to the X11 library function XCirculateSubwindowsDown().

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

interface to the X11 library function XCirculateSubwindowsUp().

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

interface to the X11 library function XCirculateSubwindows().

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

interface to the X11 library function XDestroyWindow().

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

interface to the X11 library function XDestroySubwindows().

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

interface to the X11 library function XSetWindowBorder().

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

interface to the X11 library function XSetWindowBorderPixmap().

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

interface to the X11 library function XSetWindowBorderWidth().

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

interface to the X11 library function XSetWindowBackground().

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

interface to the X11 library function XSetWindowBackgroundPixmap().

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

interface to the X11 library function XSetWindowColormap().

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

interface to the X11 library function XAddToSaveSet().

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

interface to the X11 library function XRemoveFromSaveSet().

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

interface to the X11 library function XChangeSaveSet().

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

interface to the X11 library function XClearWindow().

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

interface to the X11 library function XClearArea().

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

interface to the X11 library function XSetTextProperty().

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

interface to the X11 library function XRotateBuffers().

fetchBytes :: Display -> IO String Source #

interface to the X11 library function XFetchBytes().

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

interface to the X11 library function XFetchBuffer().

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

interface to the X11 library function XStoreBytes().

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

interface to the X11 library function XStoreBuffer().

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

interface to the X11 library function XDrawImageString().

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

interface to the X11 library function XDrawString().

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

interface to the X11 library function XFillArcs().

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

interface to the X11 library function XFillPolygon().

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

interface to the X11 library function XFillRectangles().

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

interface to the X11 library function XDrawArcs().

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

interface to the X11 library function XDrawRectangles().

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

interface to the X11 library function XDrawSegments().

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

interface to the X11 library function XDrawLines().

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

interface to the X11 library function XDrawPoints().

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

interface to the X11 library function XSetWMProtocols().

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

interface to the X11 library function XRecolorCursor().

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

interface to the X11 library function XCreateGlyphCursor().

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

interface to the X11 library function XCreatePixmapCursor().

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

interface to the X11 library function XSetIconName().

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

interface to the X11 library function XGetIconName().

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

interface to the X11 library function XLookupString().

stringToKeysym :: String -> KeySym Source #

interface to the X11 library function XStringToKeysym().

keysymToString :: KeySym -> String Source #

interface to the X11 library function XKeysymToString().

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

interface to the X11 library function XDisplayKeycodes().

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

interface to the X11 library function XReadBitmapFile.

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

interface to the X11 library function XMatchVisualInfo()

visualBlueMaskMask :: VisualInfoMask Source #

interface to the X11 library function XGetVisualInfo()

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

interface to the X11 library function XGetPointerControl().

setLocaleModifiers :: String -> IO String Source #

interface to the X11 library function XSetLocaleModifiers().

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

interface to the X11 library function XGetGeometry().

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

interface to the X11 library function XGeometry().

setDefaultErrorHandler :: IO () Source #

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

interface to the X11 library function XDisplayName().

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

interface to the X11 library function XQueryPointer().

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

interface to the X11 library function XQueryBestSize().

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

interface to the X11 library function XQueryBestCursor().

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

interface to the X11 library function XQueryBestStipple().

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

interface to the X11 library function XQueryBestTile().

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

interface to the X11 library function XGetInputFocus().

rmInitialize :: IO () Source #

interface to the X11 library function XrmInitialize().

autoRepeatOff :: Display -> IO () Source #

interface to the X11 library function XAutoRepeatOff().

autoRepeatOn :: Display -> IO () Source #

interface to the X11 library function XAutoRepeatOn().

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

interface to the X11 library function XBell().

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

interface to the X11 library function XSetCloseDownMode().

lastKnownRequestProcessed :: Display -> IO CInt Source #

interface to the X11 library function XLastKnownRequestProcessed().

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

interface to the X11 library function XSetInputFocus().

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

interface to the X11 library function XGrabButton().

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

interface to the X11 library function XUngrabButton().

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

interface to the X11 library function XGrabPointer().

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

interface to the X11 library function XUngrabPointer().

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

interface to the X11 library function XGrabKey().

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

interface to the X11 library function XUngrabKey().

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

interface to the X11 library function XGrabKeyboard().

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

interface to the X11 library function XUngrabKeyboard().

grabServer :: Display -> IO () Source #

interface to the X11 library function XGrabServer().

ungrabServer :: Display -> IO () Source #

interface to the X11 library function XUngrabServer().

supportsLocale :: IO Bool Source #

interface to the X11 library function XSupportsLocale().

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

interface to the X11 library function XSetScreenSaver().

activateScreenSaver :: Display -> IO () Source #

interface to the X11 library function XActivateScreenSaver().

resetScreenSaver :: Display -> IO () Source #

interface to the X11 library function XResetScreenSaver().

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

interface to the X11 library function XForceScreenSaver().

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

interface to the X11 library function XWarpPointer().

visualIDFromVisual :: Visual -> IO VisualID Source #

see XVisualIDFromVisual()

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

interface to the X11 library function XCreatePixmap().

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

interface to the X11 library function XFreePixmap().

bitmapBitOrder :: Display -> ByteOrder Source #

interface to the X11 library function XBitmapBitOrder().

bitmapUnit :: Display -> CInt Source #

interface to the X11 library function XBitmapUnit().

bitmapPad :: Display -> CInt Source #

interface to the X11 library function XBitmapPad().

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

interface to the X11 library function XLookupKeysym().

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

interface to the X11 library function XKeycodeToKeysym().

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

interface to the X11 library function XKeysymToKeycode().

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

interface to the X11 library function XDefineCursor().

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

interface to the X11 library function XUndefineCursor().

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

interface to the X11 library function XCreateFontCursor().

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

interface to the X11 library function XFreeCursor().

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

interface to the X11 library function XDrawPoint().

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

interface to the X11 library function XDrawLine().

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

interface to the X11 library function XDrawRectangle().

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

interface to the X11 library function XDrawArc().

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

interface to the X11 library function XFillRectangle().

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

interface to the X11 library function XFillArc().

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

interface to the X11 library function XCopyArea().

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

interface to the X11 library function XCopyPlane().

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

interface to the X11 library function XInternAtom().

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

interface to the X11 library function XQueryColors().

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

interface to the X11 library function XQueryColor().

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

interface to the X11 library function XStoreColor().

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

interface to the X11 library function XFreeColors().

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

interface to the X11 library function XParseColor().

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

interface to the X11 library function XAllocColor().

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

interface to the X11 library function XAllocNamedColor().

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

interface to the X11 library function XLookupColor().

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

interface to the X11 library function XInstallColormap().

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

interface to the X11 library function XUninstallColormap().

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

interface to the X11 library function XCopyColormapAndFree().

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

interface to the X11 library function XCreateColormap().

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

interface to the X11 library function XFreeColormap().

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

partial interface to the X11 library function XCreateGC().

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

interface to the X11 library function XSetDashes().

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

interface to the X11 library function XSetArcMode().

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

interface to the X11 library function XSetBackground().

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

interface to the X11 library function XSetForeground().

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

interface to the X11 library function XSetFunction().

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

interface to the X11 library function XSetGraphicsExposures().

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

interface to the X11 library function XSetClipMask().

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

interface to the X11 library function XSetClipOrigin().

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

interface to the X11 library function XSetFillRule().

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

interface to the X11 library function XSetFillStyle().

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

interface to the X11 library function XSetFont().

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

interface to the X11 library function XSetLineAttributes().

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

interface to the X11 library function XSetPlaneMask().

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

interface to the X11 library function XSetState().

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

interface to the X11 library function XSetStipple().

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

interface to the X11 library function XSetSubwindowMode().

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

interface to the X11 library function XSetTSOrigin().

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

interface to the X11 library function XSetTile().

gContextFromGC :: GC -> GContext Source #

interface to the X11 library function XGContextFromGC().

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

interface to the X11 library function XFreeGC().

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

interface to the X11 library function XFlushGC().

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

interface to the X11 library function XCopyGC().

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

interface to the X11 library function XSendEvent().

gettimeofday_in_milliseconds :: IO Integer Source #

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

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

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

flush :: Display -> IO () Source #

interface to the X11 library function XFlush().

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

interface to the X11 library function XSync().

pending :: Display -> IO CInt Source #

interface to the X11 library function XPending().

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

interface to the X11 library function XEventsQueued().

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

interface to the X11 library function XNextEvent().

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

interface to the X11 library function XAllowEvents().

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

interface to the X11 library function XSelectInput().

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

interface to the X11 library function XWindowEvent().

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

interface to the X11 library function XCheckWindowEvent().

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

interface to the X11 library function XMaskEvent().

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

interface to the X11 library function XCheckMaskEvent().

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

interface to the X11 library function XCheckTypedEvent().

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

interface to the X11 library function XCheckTypedWindowEvent().

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

interface to the X11 library function XPutBackEvent().

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

interface to the X11 library function XPeekEvent().

newtype XEvent Source #

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

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

toConstr :: XEvent -> Constr Source #

dataTypeOf :: XEvent -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show XEvent 
Instance details

Defined in Graphics.X11.Xlib.Event

Eq XEvent 
Instance details

Defined in Graphics.X11.Xlib.Event

Ord XEvent 
Instance details

Defined in Graphics.X11.Xlib.Event

openDisplay :: String -> IO Display Source #

interface to the X11 library function XOpenDisplay().

serverVendor :: Display -> String Source #

interface to the X11 library function XServerVendor().

displayString :: Display -> String Source #

interface to the X11 library function XDisplayString().

screenResourceString :: Screen -> String Source #

interface to the X11 library function XScreenResourceString().

resourceManagerString :: Display -> String Source #

interface to the X11 library function XResourceManagerString().

allPlanes_aux :: Pixel Source #

interface to the X11 library function XAllPlanes().

blackPixel :: Display -> ScreenNumber -> Pixel Source #

interface to the X11 library function XBlackPixel().

whitePixel :: Display -> ScreenNumber -> Pixel Source #

interface to the X11 library function XWhitePixel().

connectionNumber :: Display -> CInt Source #

interface to the X11 library function XConnectionNumber().

defaultColormap :: Display -> ScreenNumber -> Colormap Source #

interface to the X11 library function XDefaultColormap().

defaultGC :: Display -> ScreenNumber -> GC Source #

interface to the X11 library function XDefaultGC().

defaultDepth :: Display -> ScreenNumber -> CInt Source #

interface to the X11 library function XDefaultDepth().

defaultScreen :: Display -> ScreenNumber Source #

interface to the X11 library function XDefaultScreen().

defaultScreenOfDisplay :: Display -> Screen Source #

interface to the X11 library function XDefaultScreenOfDisplay().

displayHeight :: Display -> ScreenNumber -> CInt Source #

interface to the X11 library function XDisplayHeight().

displayHeightMM :: Display -> ScreenNumber -> CInt Source #

interface to the X11 library function XDisplayHeightMM().

displayWidth :: Display -> ScreenNumber -> CInt Source #

interface to the X11 library function XDisplayWidth().

displayWidthMM :: Display -> ScreenNumber -> CInt Source #

interface to the X11 library function XDisplayWidthMM().

maxRequestSize :: Display -> CInt Source #

interface to the X11 library function XMaxRequestSize().

displayMotionBufferSize :: Display -> CInt Source #

interface to the X11 library function XDisplayMotionBufferSize().

imageByteOrder :: Display -> CInt Source #

interface to the X11 library function XImageByteOrder().

protocolRevision :: Display -> CInt Source #

interface to the X11 library function XProtocolRevision().

protocolVersion :: Display -> CInt Source #

interface to the X11 library function XProtocolVersion().

screenCount :: Display -> CInt Source #

interface to the X11 library function XScreenCount().

defaultVisual :: Display -> ScreenNumber -> Visual Source #

interface to the X11 library function XDefaultVisual().

displayCells :: Display -> ScreenNumber -> CInt Source #

interface to the X11 library function XDisplayCells().

displayPlanes :: Display -> ScreenNumber -> CInt Source #

interface to the X11 library function XDisplayPlanes().

screenOfDisplay :: Display -> ScreenNumber -> Screen Source #

interface to the X11 library function XScreenOfDisplay().

defaultRootWindow :: Display -> Window Source #

interface to the X11 library function XDefaultRootWindow().

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

interface to the X11 library function XRootWindow().

qLength :: Display -> IO CInt Source #

interface to the X11 library function XQLength().

noOp :: Display -> IO () Source #

interface to the X11 library function XNoOp().

closeDisplay :: Display -> IO () Source #

interface to the X11 library function XCloseDisplay().

textWidth :: FontStruct -> String -> Int32 Source #

interface to the X11 library function XTextWidth().

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

interface to the X11 library function XTextExtents().

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

interface to the X11 library function XLoadQueryFont().

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

interface to the X11 library function XGetGCValues().

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

interface to the X11 library function XQueryFont().

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

interface to the X11 library function XFreeFont().

data FontStruct Source #

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

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

toConstr :: FontStruct -> Constr Source #

dataTypeOf :: FontStruct -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

interface to the X11 library function XGetPixel().

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

interface to the X11 library function XGetImage().

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

interface to the X11 library function XCreateImage().

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

interface to the X11 library function XPutImage().

destroyImage :: Image -> IO () Source #

interface to the X11 library function XDestroyImage().

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

interface to the X11 library function XSetRegion().

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

interface to the X11 library function XShrinkRegion().

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

interface to the X11 library function XOffsetRegion().

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

interface to the X11 library function XClipBox().

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

interface to the X11 library function XRectInRegion().

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

interface to the X11 library function XPointInRegion().

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

interface to the X11 library function XEqualRegion().

emptyRegion :: Region -> IO Bool Source #

interface to the X11 library function XEmptyRegion().

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

interface to the X11 library function XXorRegion().

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

interface to the X11 library function XUnionRegion().

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

interface to the X11 library function XUnionRectWithRegion().

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

interface to the X11 library function XSubtractRegion().

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

interface to the X11 library function XIntersectRegion().

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

interface to the X11 library function XPolygonRegion().

createRegion :: IO Region Source #

interface to the X11 library function XCreateRegion().

data Region Source #

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

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

toConstr :: Region -> Constr Source #

dataTypeOf :: Region -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show Region 
Instance details

Defined in Graphics.X11.Xlib.Region

Eq Region 
Instance details

Defined in Graphics.X11.Xlib.Region

Ord Region 
Instance details

Defined in Graphics.X11.Xlib.Region

blackPixelOfScreen :: Screen -> Pixel Source #

interface to the X11 library function XBlackPixelOfScreen().

whitePixelOfScreen :: Screen -> Pixel Source #

interface to the X11 library function XWhitePixelOfScreen().

cellsOfScreen :: Screen -> CInt Source #

interface to the X11 library function XCellsOfScreen().

defaultColormapOfScreen :: Screen -> Colormap Source #

interface to the X11 library function XDefaultColormapOfScreen().

defaultDepthOfScreen :: Screen -> CInt Source #

interface to the X11 library function XDefaultDepthOfScreen().

defaultGCOfScreen :: Screen -> GC Source #

interface to the X11 library function XDefaultGCOfScreen().

defaultVisualOfScreen :: Screen -> Visual Source #

interface to the X11 library function XDefaultVisualOfScreen().

doesBackingStore :: Screen -> Bool Source #

interface to the X11 library function XDoesBackingStore().

doesSaveUnders :: Screen -> Bool Source #

interface to the X11 library function XDoesSaveUnders().

displayOfScreen :: Screen -> Display Source #

interface to the X11 library function XDisplayOfScreen().

eventMaskOfScreen :: Screen -> EventMask Source #

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

minCmapsOfScreen :: Screen -> CInt Source #

interface to the X11 library function XMinCmapsOfScreen().

maxCmapsOfScreen :: Screen -> CInt Source #

interface to the X11 library function XMaxCmapsOfScreen().

rootWindowOfScreen :: Screen -> Window Source #

interface to the X11 library function XRootWindowOfScreen().

widthOfScreen :: Screen -> Dimension Source #

interface to the X11 library function XWidthOfScreen().

widthMMOfScreen :: Screen -> Dimension Source #

interface to the X11 library function XWidthMMOfScreen().

heightOfScreen :: Screen -> Dimension Source #

interface to the X11 library function XHeightOfScreen().

heightMMOfScreen :: Screen -> Dimension Source #

interface to the X11 library function XHeightMMOfScreen().

planesOfScreen :: Screen -> CInt Source #

interface to the X11 library function XPlanesOfScreen().

screenNumberOfScreen :: Screen -> ScreenNumber Source #

interface to the X11 library function XScreenNumberOfScreen().

newtype Display Source #

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

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

toConstr :: Display -> Constr Source #

dataTypeOf :: Display -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show Display 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Display 
Instance details

Defined in Graphics.X11.Xlib.Types

Ord Display 
Instance details

Defined in Graphics.X11.Xlib.Types

data Screen Source #

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

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

toConstr :: Screen -> Constr Source #

dataTypeOf :: Screen -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show Screen 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Screen 
Instance details

Defined in Graphics.X11.Xlib.Types

Ord Screen 
Instance details

Defined in Graphics.X11.Xlib.Types

data Visual Source #

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

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

toConstr :: Visual -> Constr Source #

dataTypeOf :: Visual -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show Visual 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Visual 
Instance details

Defined in Graphics.X11.Xlib.Types

Ord Visual 
Instance details

Defined in Graphics.X11.Xlib.Types

data GC Source #

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

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

toConstr :: GC -> Constr Source #

dataTypeOf :: GC -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show GC 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq GC 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

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

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

Ord GC 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

compare :: GC -> GC -> Ordering Source #

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

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

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

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

max :: GC -> GC -> GC Source #

min :: GC -> GC -> GC Source #

data SetWindowAttributes Source #

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

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

toConstr :: SetWindowAttributes -> Constr Source #

dataTypeOf :: SetWindowAttributes -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

toConstr :: Image -> Constr Source #

dataTypeOf :: Image -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show Image 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Image 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

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

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

Ord Image 
Instance details

Defined in Graphics.X11.Xlib.Types

data Point Source #

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

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

toConstr :: Point -> Constr Source #

dataTypeOf :: Point -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Storable Point 
Instance details

Defined in Graphics.X11.Xlib.Types

Show Point 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Point 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

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

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

data Rectangle Source #

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

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

toConstr :: Rectangle -> Constr Source #

dataTypeOf :: Rectangle -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

data Arc Source #

counterpart of an X11 XArc structure

Instances

Instances details
Storable Arc 
Instance details

Defined in Graphics.X11.Xlib.Types

Show Arc 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Arc 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

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

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

data Segment Source #

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

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

toConstr :: Segment -> Constr Source #

dataTypeOf :: Segment -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

data Color Source #

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

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

toConstr :: Color -> Constr Source #

dataTypeOf :: Color -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Storable Color 
Instance details

Defined in Graphics.X11.Xlib.Types

Show Color 
Instance details

Defined in Graphics.X11.Xlib.Types

Eq Color 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

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

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

badGC :: ErrorCode Source #

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

type Font = XID Source #

type Place = CInt Source #

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

(.|.) :: Bits a => a -> a -> a infixl 5 Source #

Bitwise "or"

class Monad m => MonadState s (m :: Type -> Type) | m -> s where Source #

Minimal definition is either both of get and put or just state

Minimal complete definition

state | get, put

Methods

get :: m s Source #

Return the state from the internals of the monad.

put :: s -> m () Source #

Replace the state inside the monad.

state :: (s -> (a, s)) -> m a Source #

Embed a simple state action into the monad.

Instances

Instances details
MonadState XState X Source # 
Instance details

Defined in XMonad.Core

Methods

get :: X XState Source #

put :: XState -> X () Source #

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

MonadState s m => MonadState s (ListT m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: ListT m s Source #

put :: s -> ListT m () Source #

state :: (s -> (a, s)) -> ListT m a Source #

MonadState s m => MonadState s (MaybeT m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: MaybeT m s Source #

put :: s -> MaybeT m () Source #

state :: (s -> (a, s)) -> MaybeT m a Source #

(Error e, MonadState s m) => MonadState s (ErrorT e m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: ErrorT e m s Source #

put :: s -> ErrorT e m () Source #

state :: (s -> (a, s)) -> ErrorT e m a Source #

MonadState s m => MonadState s (ExceptT e m)

Since: mtl-2.2

Instance details

Defined in Control.Monad.State.Class

Methods

get :: ExceptT e m s Source #

put :: s -> ExceptT e m () Source #

state :: (s -> (a, s)) -> ExceptT e m a Source #

MonadState s m => MonadState s (IdentityT m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: IdentityT m s Source #

put :: s -> IdentityT m () Source #

state :: (s -> (a, s)) -> IdentityT m a Source #

MonadState s m => MonadState s (ReaderT r m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: ReaderT r m s Source #

put :: s -> ReaderT r m () Source #

state :: (s -> (a, s)) -> ReaderT r m a Source #

Monad m => MonadState s (StateT s m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: StateT s m s Source #

put :: s -> StateT s m () Source #

state :: (s -> (a, s)) -> StateT s m a Source #

Monad m => MonadState s (StateT s m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: StateT s m s Source #

put :: s -> StateT s m () Source #

state :: (s -> (a, s)) -> StateT s m a Source #

(Monoid w, MonadState s m) => MonadState s (WriterT w m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: WriterT w m s Source #

put :: s -> WriterT w m () Source #

state :: (s -> (a, s)) -> WriterT w m a Source #

(Monoid w, MonadState s m) => MonadState s (WriterT w m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: WriterT w m s Source #

put :: s -> WriterT w m () Source #

state :: (s -> (a, s)) -> WriterT w m a Source #

MonadState s m => MonadState s (ContT r m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: ContT r m s Source #

put :: s -> ContT r m () Source #

state :: (s -> (a, s)) -> ContT r m a Source #

(Monad m, Monoid w) => MonadState s (RWST r w s m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: RWST r w s m s Source #

put :: s -> RWST r w s m () Source #

state :: (s -> (a, s)) -> RWST r w s m a Source #

(Monad m, Monoid w) => MonadState s (RWST r w s m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: RWST r w s m s Source #

put :: s -> RWST r w s m () Source #

state :: (s -> (a, s)) -> RWST r w s m a Source #

gets :: MonadState s m => (s -> a) -> m a Source #

Gets specific component of the state, using a projection function supplied.

modify :: MonadState s m => (s -> s) -> m () Source #

Monadic state transformer.

Maps an old state to a new state inside a state monad. The old state is thrown away.

     Main> :t modify ((+1) :: Int -> Int)
     modify (...) :: (MonadState Int a) => a ()

This says that modify (+1) acts over any Monad that is a member of the MonadState class, with an Int state.

class Monad m => MonadReader r (m :: Type -> Type) | m -> r where Source #

See examples in Control.Monad.Reader. Note, the partially applied function type (->) r is a simple reader monad. See the instance declaration below.

Minimal complete definition

(ask | reader), local

Methods

ask :: m r Source #

Retrieves the monad environment.

local Source #

Arguments

:: (r -> r)

The function to modify the environment.

-> m a

Reader to run in the modified environment.

-> m a 

Executes a computation in a modified environment.

reader Source #

Arguments

:: (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.

Instances

Instances details
MonadReader Window Query Source # 
Instance details

Defined in XMonad.Core

Methods

ask :: Query Window Source #

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

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

MonadReader XConf X Source # 
Instance details

Defined in XMonad.Core

Methods

ask :: X XConf Source #

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

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

MonadReader r m => MonadReader r (ListT m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ListT m r Source #

local :: (r -> r) -> ListT m a -> ListT m a Source #

reader :: (r -> a) -> ListT m a Source #

MonadReader r m => MonadReader r (MaybeT m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: MaybeT m r Source #

local :: (r -> r) -> MaybeT m a -> MaybeT m a Source #

reader :: (r -> a) -> MaybeT m a Source #

(Error e, MonadReader r m) => MonadReader r (ErrorT e m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ErrorT e m r Source #

local :: (r -> r) -> ErrorT e m a -> ErrorT e m a Source #

reader :: (r -> a) -> ErrorT e m a Source #

MonadReader r m => MonadReader r (ExceptT e m)

Since: mtl-2.2

Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ExceptT e m r Source #

local :: (r -> r) -> ExceptT e m a -> ExceptT e m a Source #

reader :: (r -> a) -> ExceptT e m a Source #

MonadReader r m => MonadReader r (IdentityT m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: IdentityT m r Source #

local :: (r -> r) -> IdentityT m a -> IdentityT m a Source #

reader :: (r -> a) -> IdentityT m a Source #

Monad m => MonadReader r (ReaderT r m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ReaderT r m r Source #

local :: (r -> r) -> ReaderT r m a -> ReaderT r m a Source #

reader :: (r -> a) -> ReaderT r m a Source #

MonadReader r m => MonadReader r (StateT s m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: StateT s m r Source #

local :: (r -> r) -> StateT s m a -> StateT s m a Source #

reader :: (r -> a) -> StateT s m a Source #

MonadReader r m => MonadReader r (StateT s m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: StateT s m r Source #

local :: (r -> r) -> StateT s m a -> StateT s m a Source #

reader :: (r -> a) -> StateT s m a Source #

(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: WriterT w m r Source #

local :: (r -> r) -> WriterT w m a -> WriterT w m a Source #

reader :: (r -> a) -> WriterT w m a Source #

(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: WriterT w m r Source #

local :: (r -> r) -> WriterT w m a -> WriterT w m a Source #

reader :: (r -> a) -> WriterT w m a Source #

MonadReader r ((->) r) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: r -> r Source #

local :: (r -> r) -> (r -> a) -> r -> a Source #

reader :: (r -> a) -> r -> a Source #

MonadReader r' m => MonadReader r' (ContT r m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ContT r m r' Source #

local :: (r' -> r') -> ContT r m a -> ContT r m a Source #

reader :: (r' -> a) -> ContT r m a Source #

(Monad m, Monoid w) => MonadReader r (RWST r w s m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: RWST r w s m r Source #

local :: (r -> r) -> RWST r w s m a -> RWST r w s m a Source #

reader :: (r -> a) -> RWST r w s m a Source #

(Monad m, Monoid w) => MonadReader r (RWST r w s m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: RWST r w s m r Source #

local :: (r -> r) -> RWST r w s m a -> RWST r w s m a Source #

reader :: (r -> a) -> RWST r w s m a Source #

asks Source #

Arguments

:: MonadReader r m 
=> (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.

class Monad m => MonadIO (m :: Type -> Type) where Source #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Methods

liftIO :: IO a -> m a Source #

Lift a computation from the IO monad. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

Instances

Instances details
MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Methods

liftIO :: IO a -> IO a Source #

MonadIO Query Source # 
Instance details

Defined in XMonad.Core

Methods

liftIO :: IO a -> Query a Source #

MonadIO X Source # 
Instance details

Defined in XMonad.Core

Methods

liftIO :: IO a -> X a Source #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

liftIO :: IO a -> ErrorT e m a Source #

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r m a Source #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

liftIO :: IO a -> StateT s m a Source #