|
Graphics.X11.Xlib.Misc | Portability | portable | Stability | provisional | Maintainer | libraries@haskell.org |
|
|
|
|
|
Description |
A collection of FFI declarations for interfacing with Xlib.
|
|
Synopsis |
|
rmInitialize :: IO () | | autoRepeatOff :: Display -> IO () | | autoRepeatOn :: Display -> IO () | | bell :: Display -> CInt -> IO () | | setCloseDownMode :: Display -> CloseDownMode -> IO () | | lastKnownRequestProcessed :: Display -> IO CInt | | getInputFocus :: Display -> IO (Window, FocusMode) | | setInputFocus :: Display -> Window -> FocusMode -> Time -> IO () | | grabButton :: Display -> Button -> ButtonMask -> Window -> Bool -> EventMask -> GrabMode -> GrabMode -> Window -> Cursor -> IO () | | ungrabButton :: Display -> Button -> ButtonMask -> Window -> IO () | | grabPointer :: Display -> Window -> Bool -> EventMask -> GrabMode -> GrabMode -> Window -> Cursor -> Time -> IO GrabStatus | | ungrabPointer :: Display -> Time -> IO () | | grabKey :: Display -> KeyCode -> ButtonMask -> Window -> Bool -> GrabMode -> GrabMode -> IO () | | ungrabKey :: Display -> KeyCode -> ButtonMask -> Window -> IO () | | grabKeyboard :: Display -> Window -> Bool -> GrabMode -> GrabMode -> Time -> IO GrabStatus | | ungrabKeyboard :: Display -> Time -> IO () | | grabServer :: Display -> IO () | | ungrabServer :: Display -> IO () | | queryBestTile :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) | | queryBestStipple :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) | | queryBestCursor :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) | | queryBestSize :: Display -> QueryBestSizeClass -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) | | queryPointer :: Display -> Window -> IO (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier) | | displayName :: String -> String | | setDefaultErrorHandler :: IO () | | geometry :: Display -> CInt -> String -> String -> Dimension -> Dimension -> Dimension -> CInt -> CInt -> IO (CInt, Position, Position, Dimension, Dimension) | | getGeometry :: Display -> Drawable -> IO (Window, Position, Position, Dimension, Dimension, Dimension, CInt) | | supportsLocale :: IO Bool | | setLocaleModifiers :: String -> IO String | | type AllowExposuresMode = CInt | | dontAllowExposures :: AllowExposuresMode | | allowExposures :: AllowExposuresMode | | defaultExposures :: AllowExposuresMode | | type PreferBlankingMode = CInt | | dontPreferBlanking :: PreferBlankingMode | | preferBlanking :: PreferBlankingMode | | defaultBlanking :: PreferBlankingMode | | type ScreenSaverMode = CInt | | screenSaverActive :: ScreenSaverMode | | screenSaverReset :: ScreenSaverMode | | getScreenSaver :: Display -> IO (CInt, CInt, PreferBlankingMode, AllowExposuresMode) | | setScreenSaver :: Display -> CInt -> CInt -> PreferBlankingMode -> AllowExposuresMode -> IO () | | activateScreenSaver :: Display -> IO () | | resetScreenSaver :: Display -> IO () | | forceScreenSaver :: Display -> ScreenSaverMode -> IO () | | getPointerControl :: Display -> IO (CInt, CInt, CInt) | | warpPointer :: Display -> Window -> Window -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> IO () | | initThreads :: IO Status | | lockDisplay :: Display -> IO () | | unlockDisplay :: Display -> IO () | | createPixmap :: Display -> Drawable -> Dimension -> Dimension -> CInt -> IO Pixmap | | freePixmap :: Display -> Pixmap -> IO () | | bitmapBitOrder :: Display -> ByteOrder | | bitmapUnit :: Display -> CInt | | bitmapPad :: Display -> CInt | | displayKeycodes :: Display -> (CInt, CInt) | | lookupKeysym :: XKeyEventPtr -> CInt -> IO KeySym | | keycodeToKeysym :: Display -> KeyCode -> CInt -> IO KeySym | | keysymToKeycode :: Display -> KeySym -> IO KeyCode | | keysymToString :: KeySym -> String | | stringToKeysym :: String -> KeySym | | noSymbol :: KeySym | | lookupString :: XKeyEventPtr -> IO (Maybe KeySym, String) | | getIconName :: Display -> Window -> IO String | | setIconName :: Display -> Window -> String -> IO () | | defineCursor :: Display -> Window -> Cursor -> IO () | | undefineCursor :: Display -> Window -> IO () | | createPixmapCursor :: Display -> Pixmap -> Pixmap -> Color -> Color -> Dimension -> Dimension -> IO Cursor | | createGlyphCursor :: Display -> Font -> Font -> Glyph -> Glyph -> Color -> Color -> IO Cursor | | createFontCursor :: Display -> Glyph -> IO Cursor | | freeCursor :: Display -> Font -> IO () | | recolorCursor :: Display -> Cursor -> Color -> Color -> IO () | | setWMProtocols :: Display -> Window -> [Atom] -> IO () | | allocaSetWindowAttributes :: (Ptr SetWindowAttributes -> IO a) -> IO a | | set_background_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO () | | set_background_pixel :: Ptr SetWindowAttributes -> Pixel -> IO () | | set_border_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO () | | set_border_pixel :: Ptr SetWindowAttributes -> Pixel -> IO () | | set_bit_gravity :: Ptr SetWindowAttributes -> BitGravity -> IO () | | set_win_gravity :: Ptr SetWindowAttributes -> WindowGravity -> IO () | | set_backing_store :: Ptr SetWindowAttributes -> BackingStore -> IO () | | set_backing_planes :: Ptr SetWindowAttributes -> Pixel -> IO () | | set_backing_pixel :: Ptr SetWindowAttributes -> Pixel -> IO () | | set_save_under :: Ptr SetWindowAttributes -> Bool -> IO () | | set_event_mask :: Ptr SetWindowAttributes -> EventMask -> IO () | | set_do_not_propagate_mask :: Ptr SetWindowAttributes -> EventMask -> IO () | | set_override_redirect :: Ptr SetWindowAttributes -> Bool -> IO () | | set_colormap :: Ptr SetWindowAttributes -> Colormap -> IO () | | set_cursor :: Ptr SetWindowAttributes -> Cursor -> IO () | | drawPoint :: Display -> Drawable -> GC -> Position -> Position -> IO () | | drawPoints :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO () | | drawLine :: Display -> Drawable -> GC -> Position -> Position -> Position -> Position -> IO () | | drawLines :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO () | | drawSegments :: Display -> Drawable -> GC -> [Segment] -> IO () | | drawRectangle :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> IO () | | drawRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO () | | drawArc :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> IO () | | drawArcs :: Display -> Drawable -> GC -> [Arc] -> IO () | | fillRectangle :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> IO () | | fillRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO () | | fillPolygon :: Display -> Drawable -> GC -> [Point] -> PolygonShape -> CoordinateMode -> IO () | | fillArc :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> IO () | | fillArcs :: Display -> Drawable -> GC -> [Arc] -> IO () | | copyArea :: Display -> Drawable -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> IO () | | copyPlane :: Display -> Drawable -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> Pixel -> IO () | | drawString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO () | | drawImageString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO () | | storeBuffer :: Display -> String -> CInt -> IO () | | storeBytes :: Display -> String -> IO () | | fetchBuffer :: Display -> CInt -> IO String | | fetchBytes :: Display -> IO String | | rotateBuffers :: Display -> CInt -> IO () | | setTextProperty :: Display -> Window -> String -> Atom -> IO () |
|
|
Documentation |
|
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().
|
|
getInputFocus :: Display -> IO (Window, FocusMode) |
interface to the X11 library function XGetInputFocus().
|
|
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 -> ButtonMask -> Window -> Bool -> GrabMode -> GrabMode -> IO () |
interface to the X11 library function XGrabKey().
|
|
ungrabKey :: Display -> KeyCode -> ButtonMask -> 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().
|
|
queryBestTile :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) |
interface to the X11 library function XQueryBestTile().
|
|
queryBestStipple :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) |
interface to the X11 library function XQueryBestStipple().
|
|
queryBestCursor :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) |
interface to the X11 library function XQueryBestCursor().
|
|
queryBestSize :: Display -> QueryBestSizeClass -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension) |
interface to the X11 library function XQueryBestSize().
|
|
queryPointer :: Display -> Window -> IO (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier) |
interface to the X11 library function XQueryPointer().
|
|
Error reporting
|
|
displayName :: String -> String |
interface to the X11 library function XDisplayName().
|
|
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.
|
|
Geometry
|
|
geometry :: Display -> CInt -> String -> String -> Dimension -> Dimension -> Dimension -> CInt -> CInt -> IO (CInt, Position, Position, Dimension, Dimension) |
interface to the X11 library function XGeometry().
|
|
getGeometry :: Display -> Drawable -> IO (Window, Position, Position, Dimension, Dimension, Dimension, CInt) |
interface to the X11 library function XGetGeometry().
|
|
Locale
|
|
supportsLocale :: IO Bool |
interface to the X11 library function XSupportsLocale().
|
|
setLocaleModifiers :: String -> IO String |
interface to the X11 library function XSetLocaleModifiers().
|
|
Screen saver
|
|
type AllowExposuresMode = CInt |
|
dontAllowExposures :: AllowExposuresMode |
|
allowExposures :: AllowExposuresMode |
|
defaultExposures :: AllowExposuresMode |
|
type PreferBlankingMode = CInt |
|
dontPreferBlanking :: PreferBlankingMode |
|
preferBlanking :: PreferBlankingMode |
|
defaultBlanking :: PreferBlankingMode |
|
type ScreenSaverMode = CInt |
|
screenSaverActive :: ScreenSaverMode |
|
screenSaverReset :: ScreenSaverMode |
|
getScreenSaver :: Display -> IO (CInt, CInt, PreferBlankingMode, AllowExposuresMode) |
|
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().
|
|
Pointer
|
|
getPointerControl :: Display -> IO (CInt, CInt, CInt) |
interface to the X11 library function XGetPointerControl().
|
|
warpPointer :: Display -> Window -> Window -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> IO () |
interface to the X11 library function XWarpPointer().
|
|
Threads
|
|
initThreads :: IO Status |
|
lockDisplay :: Display -> IO () |
|
unlockDisplay :: Display -> IO () |
|
Pixmaps
|
|
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().
|
|
Keycodes
|
|
displayKeycodes :: Display -> (CInt, CInt) |
interface to the X11 library function XDisplayKeycodes().
|
|
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().
|
|
keysymToString :: KeySym -> String |
interface to the X11 library function XKeysymToString().
|
|
stringToKeysym :: String -> KeySym |
interface to the X11 library function XStringToKeysym().
|
|
noSymbol :: KeySym |
|
lookupString :: XKeyEventPtr -> IO (Maybe KeySym, String) |
interface to the X11 library function XLookupString().
|
|
Icons
|
|
getIconName :: Display -> Window -> IO String |
interface to the X11 library function XGetIconName().
|
|
setIconName :: Display -> Window -> String -> IO () |
interface to the X11 library function XSetIconName().
|
|
Cursors
|
|
defineCursor :: Display -> Window -> Cursor -> IO () |
interface to the X11 library function XDefineCursor().
|
|
undefineCursor :: Display -> Window -> IO () |
interface to the X11 library function XUndefineCursor().
|
|
createPixmapCursor :: Display -> Pixmap -> Pixmap -> Color -> Color -> Dimension -> Dimension -> IO Cursor |
interface to the X11 library function XCreatePixmapCursor().
|
|
createGlyphCursor :: Display -> Font -> Font -> Glyph -> Glyph -> Color -> Color -> IO Cursor |
interface to the X11 library function XCreateGlyphCursor().
|
|
createFontCursor :: Display -> Glyph -> IO Cursor |
interface to the X11 library function XCreateFontCursor().
|
|
freeCursor :: Display -> Font -> IO () |
interface to the X11 library function XFreeCursor().
|
|
recolorCursor :: Display -> Cursor -> Color -> Color -> IO () |
interface to the X11 library function XRecolorCursor().
|
|
Window manager stuff
|
|
setWMProtocols :: Display -> Window -> [Atom] -> IO () |
interface to the X11 library function XSetWMProtocols().
|
|
Set window attributes
|
|
allocaSetWindowAttributes :: (Ptr SetWindowAttributes -> IO a) -> IO a |
|
set_background_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO () |
|
set_background_pixel :: Ptr SetWindowAttributes -> Pixel -> IO () |
|
set_border_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO () |
|
set_border_pixel :: Ptr SetWindowAttributes -> Pixel -> IO () |
|
set_bit_gravity :: Ptr SetWindowAttributes -> BitGravity -> IO () |
|
set_win_gravity :: Ptr SetWindowAttributes -> WindowGravity -> IO () |
|
set_backing_store :: Ptr SetWindowAttributes -> BackingStore -> IO () |
|
set_backing_planes :: Ptr SetWindowAttributes -> Pixel -> IO () |
|
set_backing_pixel :: Ptr SetWindowAttributes -> Pixel -> IO () |
|
set_save_under :: Ptr SetWindowAttributes -> Bool -> IO () |
|
set_event_mask :: Ptr SetWindowAttributes -> EventMask -> IO () |
|
set_do_not_propagate_mask :: Ptr SetWindowAttributes -> EventMask -> IO () |
|
set_override_redirect :: Ptr SetWindowAttributes -> Bool -> IO () |
|
set_colormap :: Ptr SetWindowAttributes -> Colormap -> IO () |
|
set_cursor :: Ptr SetWindowAttributes -> Cursor -> IO () |
|
Drawing
|
|
drawPoint :: Display -> Drawable -> GC -> Position -> Position -> IO () |
interface to the X11 library function XDrawPoint().
|
|
drawPoints :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO () |
interface to the X11 library function XDrawPoints().
|
|
drawLine :: Display -> Drawable -> GC -> Position -> Position -> Position -> Position -> IO () |
interface to the X11 library function XDrawLine().
|
|
drawLines :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO () |
interface to the X11 library function XDrawLines().
|
|
drawSegments :: Display -> Drawable -> GC -> [Segment] -> IO () |
interface to the X11 library function XDrawSegments().
|
|
drawRectangle :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> IO () |
interface to the X11 library function XDrawRectangle().
|
|
drawRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO () |
interface to the X11 library function XDrawRectangles().
|
|
drawArc :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> IO () |
interface to the X11 library function XDrawArc().
|
|
drawArcs :: Display -> Drawable -> GC -> [Arc] -> IO () |
interface to the X11 library function XDrawArcs().
|
|
fillRectangle :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> IO () |
interface to the X11 library function XFillRectangle().
|
|
fillRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO () |
interface to the X11 library function XFillRectangles().
|
|
fillPolygon :: Display -> Drawable -> GC -> [Point] -> PolygonShape -> CoordinateMode -> IO () |
interface to the X11 library function XFillPolygon().
|
|
fillArc :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> IO () |
interface to the X11 library function XFillArc().
|
|
fillArcs :: Display -> Drawable -> GC -> [Arc] -> IO () |
interface to the X11 library function XFillArcs().
|
|
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().
|
|
drawString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO () |
interface to the X11 library function XDrawString().
|
|
drawImageString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO () |
interface to the X11 library function XDrawImageString().
|
|
Cut and paste buffers
|
|
storeBuffer :: Display -> String -> CInt -> IO () |
interface to the X11 library function XStoreBuffer().
|
|
storeBytes :: Display -> String -> IO () |
interface to the X11 library function XStoreBytes().
|
|
fetchBuffer :: Display -> CInt -> IO String |
interface to the X11 library function XFetchBuffer().
|
|
fetchBytes :: Display -> IO String |
interface to the X11 library function XFetchBytes().
|
|
rotateBuffers :: Display -> CInt -> IO () |
interface to the X11 library function XRotateBuffers().
|
|
Window properties
|
|
setTextProperty :: Display -> Window -> String -> Atom -> IO () |
interface to the X11 library function XSetTextProperty().
|
|
Produced by Haddock version 0.8 |