Copyright | (c) Don Stewart |
---|---|
License | BSD3 |
Maintainer | Don Stewart <dons@galois.com> |
Stability | provisional |
Portability | |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- module XMonad.Main
- module XMonad.Core
- module XMonad.Config
- module XMonad.Layout
- module XMonad.ManageHook
- module XMonad.Operations
- restackWindows :: Display -> [Window] -> IO ()
- withdrawWindow :: Display -> Window -> ScreenNumber -> IO ()
- iconifyWindow :: Display -> Window -> ScreenNumber -> IO ()
- translateCoordinates :: Display -> Window -> Window -> Position -> Position -> IO (Bool, Position, Position, Window)
- storeName :: Display -> Window -> String -> IO ()
- createSimpleWindow :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> CInt -> Pixel -> Pixel -> IO Window
- createWindow :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> CInt -> CInt -> WindowClass -> Visual -> AttributeMask -> Ptr SetWindowAttributes -> IO Window
- moveResizeWindow :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> IO ()
- resizeWindow :: Display -> Window -> Dimension -> Dimension -> IO ()
- moveWindow :: Display -> Window -> Position -> Position -> IO ()
- reparentWindow :: Display -> Window -> Window -> Position -> Position -> IO ()
- mapSubwindows :: Display -> Window -> IO ()
- unmapSubwindows :: Display -> Window -> IO ()
- mapWindow :: Display -> Window -> IO ()
- lowerWindow :: Display -> Window -> IO ()
- raiseWindow :: Display -> Window -> IO ()
- circulateSubwindowsDown :: Display -> Window -> IO ()
- circulateSubwindowsUp :: Display -> Window -> IO ()
- circulateSubwindows :: Display -> Window -> CirculationDirection -> IO ()
- destroyWindow :: Display -> Window -> IO ()
- destroySubwindows :: Display -> Window -> IO ()
- setWindowBorder :: Display -> Window -> Pixel -> IO ()
- setWindowBorderPixmap :: Display -> Window -> Pixmap -> IO ()
- setWindowBorderWidth :: Display -> Window -> Dimension -> IO ()
- setWindowBackground :: Display -> Window -> Pixel -> IO ()
- setWindowBackgroundPixmap :: Display -> Window -> Pixmap -> IO ()
- setWindowColormap :: Display -> Window -> Colormap -> IO ()
- addToSaveSet :: Display -> Window -> IO ()
- removeFromSaveSet :: Display -> Window -> IO ()
- changeSaveSet :: Display -> Window -> ChangeSaveSetMode -> IO ()
- clearWindow :: Display -> Window -> IO ()
- clearArea :: Display -> Window -> Position -> Position -> Dimension -> Dimension -> Bool -> IO ()
- setTextProperty :: Display -> Window -> String -> Atom -> IO ()
- rotateBuffers :: Display -> CInt -> IO ()
- fetchBytes :: Display -> IO String
- fetchBuffer :: Display -> CInt -> IO String
- storeBytes :: Display -> String -> IO ()
- storeBuffer :: Display -> String -> CInt -> IO ()
- drawImageString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO ()
- drawString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO ()
- fillArcs :: Display -> Drawable -> GC -> [Arc] -> IO ()
- fillPolygon :: Display -> Drawable -> GC -> [Point] -> PolygonShape -> CoordinateMode -> IO ()
- fillRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO ()
- drawArcs :: Display -> Drawable -> GC -> [Arc] -> IO ()
- drawRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO ()
- drawSegments :: Display -> Drawable -> GC -> [Segment] -> IO ()
- drawLines :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO ()
- drawPoints :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO ()
- set_cursor :: Ptr SetWindowAttributes -> Cursor -> IO ()
- set_colormap :: Ptr SetWindowAttributes -> Colormap -> IO ()
- set_override_redirect :: Ptr SetWindowAttributes -> Bool -> IO ()
- set_do_not_propagate_mask :: Ptr SetWindowAttributes -> EventMask -> IO ()
- set_event_mask :: Ptr SetWindowAttributes -> EventMask -> IO ()
- set_save_under :: Ptr SetWindowAttributes -> Bool -> IO ()
- set_backing_pixel :: Ptr SetWindowAttributes -> Pixel -> IO ()
- set_backing_planes :: Ptr SetWindowAttributes -> Pixel -> IO ()
- set_backing_store :: Ptr SetWindowAttributes -> BackingStore -> IO ()
- set_win_gravity :: Ptr SetWindowAttributes -> WindowGravity -> IO ()
- set_bit_gravity :: Ptr SetWindowAttributes -> BitGravity -> IO ()
- set_border_pixel :: Ptr SetWindowAttributes -> Pixel -> IO ()
- set_border_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO ()
- set_background_pixel :: Ptr SetWindowAttributes -> Pixel -> IO ()
- set_background_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO ()
- allocaSetWindowAttributes :: (Ptr SetWindowAttributes -> IO a) -> IO a
- setWMProtocols :: Display -> Window -> [Atom] -> IO ()
- recolorCursor :: Display -> Cursor -> Color -> Color -> IO ()
- createGlyphCursor :: Display -> Font -> Font -> Glyph -> Glyph -> Color -> Color -> IO Cursor
- createPixmapCursor :: Display -> Pixmap -> Pixmap -> Color -> Color -> Dimension -> Dimension -> IO Cursor
- setIconName :: Display -> Window -> String -> IO ()
- getIconName :: Display -> Window -> IO String
- lookupString :: XKeyEventPtr -> IO (Maybe KeySym, String)
- noSymbol :: KeySym
- stringToKeysym :: String -> KeySym
- keysymToString :: KeySym -> String
- displayKeycodes :: Display -> (CInt, CInt)
- readBitmapFile :: Display -> Drawable -> String -> IO (Either String (Dimension, Dimension, Pixmap, Maybe CInt, Maybe CInt))
- matchVisualInfo :: Display -> ScreenNumber -> CInt -> CInt -> IO (Maybe VisualInfo)
- getVisualInfo :: Display -> VisualInfoMask -> VisualInfo -> IO [VisualInfo]
- visualAllMask :: VisualInfoMask
- visualBitsPerRGBMask :: VisualInfoMask
- visualColormapSizeMask :: VisualInfoMask
- visualBlueMaskMask :: VisualInfoMask
- visualGreenMaskMask :: VisualInfoMask
- visualRedMaskMask :: VisualInfoMask
- visualClassMask :: VisualInfoMask
- visualDepthMask :: VisualInfoMask
- visualScreenMask :: VisualInfoMask
- visualIDMask :: VisualInfoMask
- visualNoMask :: VisualInfoMask
- getPointerControl :: Display -> IO (CInt, CInt, CInt)
- getScreenSaver :: Display -> IO (CInt, CInt, PreferBlankingMode, AllowExposuresMode)
- screenSaverReset :: ScreenSaverMode
- screenSaverActive :: ScreenSaverMode
- defaultBlanking :: PreferBlankingMode
- preferBlanking :: PreferBlankingMode
- dontPreferBlanking :: PreferBlankingMode
- defaultExposures :: AllowExposuresMode
- allowExposures :: AllowExposuresMode
- dontAllowExposures :: AllowExposuresMode
- setLocaleModifiers :: String -> IO String
- getGeometry :: Display -> Drawable -> IO (Window, Position, Position, Dimension, Dimension, Dimension, CInt)
- geometry :: Display -> CInt -> String -> String -> Dimension -> Dimension -> Dimension -> CInt -> CInt -> IO (CInt, Position, Position, Dimension, Dimension)
- setDefaultErrorHandler :: IO ()
- displayName :: String -> String
- queryPointer :: Display -> Window -> IO (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier)
- queryBestSize :: Display -> QueryBestSizeClass -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension)
- queryBestCursor :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension)
- queryBestStipple :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension)
- queryBestTile :: Display -> Drawable -> Dimension -> Dimension -> IO (Dimension, Dimension)
- getInputFocus :: Display -> IO (Window, FocusMode)
- rmInitialize :: IO ()
- autoRepeatOff :: Display -> IO ()
- autoRepeatOn :: Display -> IO ()
- bell :: Display -> CInt -> IO ()
- setCloseDownMode :: Display -> CloseDownMode -> IO ()
- lastKnownRequestProcessed :: Display -> IO CInt
- 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 -> KeyMask -> Window -> Bool -> GrabMode -> GrabMode -> IO ()
- ungrabKey :: Display -> KeyCode -> KeyMask -> Window -> IO ()
- grabKeyboard :: Display -> Window -> Bool -> GrabMode -> GrabMode -> Time -> IO GrabStatus
- ungrabKeyboard :: Display -> Time -> IO ()
- grabServer :: Display -> IO ()
- ungrabServer :: Display -> IO ()
- supportsLocale :: IO Bool
- setScreenSaver :: Display -> CInt -> CInt -> PreferBlankingMode -> AllowExposuresMode -> IO ()
- activateScreenSaver :: Display -> IO ()
- resetScreenSaver :: Display -> IO ()
- forceScreenSaver :: Display -> ScreenSaverMode -> IO ()
- warpPointer :: Display -> Window -> Window -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> IO ()
- visualIDFromVisual :: Visual -> IO VisualID
- 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
- lookupKeysym :: XKeyEventPtr -> CInt -> IO KeySym
- keycodeToKeysym :: Display -> KeyCode -> CInt -> IO KeySym
- keysymToKeycode :: Display -> KeySym -> IO KeyCode
- defineCursor :: Display -> Window -> Cursor -> IO ()
- undefineCursor :: Display -> Window -> IO ()
- createFontCursor :: Display -> Glyph -> IO Cursor
- freeCursor :: Display -> Font -> IO ()
- drawPoint :: Display -> Drawable -> GC -> Position -> Position -> IO ()
- drawLine :: Display -> Drawable -> GC -> Position -> Position -> Position -> Position -> IO ()
- drawRectangle :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> IO ()
- drawArc :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> IO ()
- fillRectangle :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> IO ()
- fillArc :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Angle -> Angle -> 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 ()
- type AllowExposuresMode = CInt
- type PreferBlankingMode = CInt
- type ScreenSaverMode = CInt
- type VisualInfoMask = CLong
- lAST_PREDEFINED :: Atom
- wM_TRANSIENT_FOR :: Atom
- wM_CLASS :: Atom
- cAP_HEIGHT :: Atom
- fULL_NAME :: Atom
- fAMILY_NAME :: Atom
- fONT_NAME :: Atom
- nOTICE :: Atom
- cOPYRIGHT :: Atom
- rESOLUTION :: Atom
- pOINT_SIZE :: Atom
- wEIGHT :: Atom
- qUAD_WIDTH :: Atom
- x_HEIGHT :: Atom
- iTALIC_ANGLE :: Atom
- sTRIKEOUT_DESCENT :: Atom
- sTRIKEOUT_ASCENT :: Atom
- uNDERLINE_THICKNESS :: Atom
- uNDERLINE_POSITION :: Atom
- sUBSCRIPT_Y :: Atom
- sUBSCRIPT_X :: Atom
- sUPERSCRIPT_Y :: Atom
- sUPERSCRIPT_X :: Atom
- eND_SPACE :: Atom
- mAX_SPACE :: Atom
- nORM_SPACE :: Atom
- mIN_SPACE :: Atom
- wM_ZOOM_HINTS :: Atom
- wM_SIZE_HINTS :: Atom
- wM_NORMAL_HINTS :: Atom
- wM_NAME :: Atom
- wM_ICON_SIZE :: Atom
- wM_ICON_NAME :: Atom
- wM_CLIENT_MACHINE :: Atom
- wM_HINTS :: Atom
- wM_COMMAND :: Atom
- wINDOW :: Atom
- vISUALID :: Atom
- sTRING :: Atom
- rGB_RED_MAP :: Atom
- rGB_GREEN_MAP :: Atom
- rGB_GRAY_MAP :: Atom
- rGB_DEFAULT_MAP :: Atom
- rGB_BLUE_MAP :: Atom
- rGB_BEST_MAP :: Atom
- rGB_COLOR_MAP :: Atom
- rESOURCE_MANAGER :: Atom
- rECTANGLE :: Atom
- pOINT :: Atom
- pIXMAP :: Atom
- iNTEGER :: Atom
- fONT :: Atom
- dRAWABLE :: Atom
- cUT_BUFFER7 :: Atom
- cUT_BUFFER6 :: Atom
- cUT_BUFFER5 :: Atom
- cUT_BUFFER4 :: Atom
- cUT_BUFFER3 :: Atom
- cUT_BUFFER2 :: Atom
- cUT_BUFFER1 :: Atom
- cUT_BUFFER0 :: Atom
- cURSOR :: Atom
- cOLORMAP :: Atom
- cARDINAL :: Atom
- bITMAP :: Atom
- aTOM :: Atom
- aRC :: Atom
- sECONDARY :: Atom
- pRIMARY :: Atom
- getAtomNames :: Display -> [Atom] -> IO [String]
- getAtomName :: Display -> Atom -> IO (Maybe String)
- internAtom :: Display -> String -> Bool -> IO Atom
- queryColors :: Display -> Colormap -> [Color] -> IO [Color]
- queryColor :: Display -> Colormap -> Color -> IO Color
- storeColor :: Display -> Colormap -> Color -> IO ()
- freeColors :: Display -> Colormap -> [Pixel] -> Pixel -> IO ()
- parseColor :: Display -> Colormap -> String -> IO Color
- allocColor :: Display -> Colormap -> Color -> IO Color
- allocNamedColor :: Display -> Colormap -> String -> IO (Color, Color)
- lookupColor :: Display -> Colormap -> String -> IO (Color, Color)
- installColormap :: Display -> Colormap -> IO ()
- uninstallColormap :: Display -> Colormap -> IO ()
- copyColormapAndFree :: Display -> Colormap -> IO Colormap
- createColormap :: Display -> Window -> Visual -> ColormapAlloc -> IO Colormap
- freeColormap :: Display -> Colormap -> IO ()
- createGC :: Display -> Drawable -> IO GC
- setDashes :: Display -> GC -> CInt -> String -> CInt -> IO ()
- setArcMode :: Display -> GC -> ArcMode -> IO ()
- setBackground :: Display -> GC -> Pixel -> IO ()
- setForeground :: Display -> GC -> Pixel -> IO ()
- setFunction :: Display -> GC -> GXFunction -> IO ()
- setGraphicsExposures :: Display -> GC -> Bool -> IO ()
- setClipMask :: Display -> GC -> Pixmap -> IO ()
- setClipOrigin :: Display -> GC -> Position -> Position -> IO ()
- setFillRule :: Display -> GC -> FillRule -> IO ()
- setFillStyle :: Display -> GC -> FillStyle -> IO ()
- setFont :: Display -> GC -> Font -> IO ()
- setLineAttributes :: Display -> GC -> CInt -> LineStyle -> CapStyle -> JoinStyle -> IO ()
- setPlaneMask :: Display -> GC -> Pixel -> IO ()
- setState :: Display -> GC -> Pixel -> Pixel -> GXFunction -> Pixel -> IO ()
- setStipple :: Display -> GC -> Pixmap -> IO ()
- setSubwindowMode :: Display -> GC -> SubWindowMode -> IO ()
- setTSOrigin :: Display -> GC -> Position -> Position -> IO ()
- setTile :: Display -> GC -> Pixmap -> IO ()
- gContextFromGC :: GC -> GContext
- freeGC :: Display -> GC -> IO ()
- flushGC :: Display -> GC -> IO ()
- copyGC :: Display -> GC -> Mask -> GC -> IO ()
- sendEvent :: Display -> Window -> Bool -> EventMask -> XEventPtr -> IO ()
- gettimeofday_in_milliseconds :: IO Integer
- waitForEvent :: Display -> Word32 -> IO Bool
- get_ConfigureEvent :: XEventPtr -> IO XConfigureEvent
- get_ExposeEvent :: XEventPtr -> IO XExposeEvent
- get_MotionEvent :: XEventPtr -> IO XMotionEvent
- get_ButtonEvent :: XEventPtr -> IO XButtonEvent
- asKeyEvent :: XEventPtr -> XKeyEventPtr
- get_KeyEvent :: XEventPtr -> IO XKeyEvent
- get_Window :: XEventPtr -> IO Window
- get_EventType :: XEventPtr -> IO EventType
- allocaXEvent :: (XEventPtr -> IO a) -> IO a
- queuedAfterReading :: QueuedMode
- queuedAfterFlush :: QueuedMode
- queuedAlready :: QueuedMode
- flush :: Display -> IO ()
- sync :: Display -> Bool -> IO ()
- pending :: Display -> IO CInt
- eventsQueued :: Display -> QueuedMode -> IO CInt
- nextEvent :: Display -> XEventPtr -> IO ()
- allowEvents :: Display -> AllowEvents -> Time -> IO ()
- selectInput :: Display -> Window -> EventMask -> IO ()
- windowEvent :: Display -> Window -> EventMask -> XEventPtr -> IO ()
- checkWindowEvent :: Display -> Window -> EventMask -> XEventPtr -> IO Bool
- maskEvent :: Display -> EventMask -> XEventPtr -> IO ()
- checkMaskEvent :: Display -> EventMask -> XEventPtr -> IO Bool
- checkTypedEvent :: Display -> EventType -> XEventPtr -> IO Bool
- checkTypedWindowEvent :: Display -> Window -> EventType -> XEventPtr -> IO Bool
- putBackEvent :: Display -> XEventPtr -> IO ()
- peekEvent :: Display -> XEventPtr -> IO ()
- type QueuedMode = CInt
- newtype XEvent = XEvent XEventPtr
- type XEventPtr = Ptr XEvent
- type XKeyEvent = (Window, Window, Time, CInt, CInt, CInt, CInt, Modifier, KeyCode, Bool)
- type XKeyEventPtr = Ptr XKeyEvent
- type XButtonEvent = (Window, Window, Time, CInt, CInt, CInt, CInt, Modifier, Button, Bool)
- type XMotionEvent = (Window, Window, Time, CInt, CInt, CInt, CInt, Modifier, NotifyMode, Bool)
- type XExposeEvent = (Position, Position, Dimension, Dimension, CInt)
- type XMappingEvent = (MappingRequest, KeyCode, CInt)
- type XConfigureEvent = (Position, Position, Dimension, Dimension)
- openDisplay :: String -> IO Display
- serverVendor :: Display -> String
- displayString :: Display -> String
- screenResourceString :: Screen -> String
- resourceManagerString :: Display -> String
- allPlanes_aux :: Pixel
- blackPixel :: Display -> ScreenNumber -> Pixel
- whitePixel :: Display -> ScreenNumber -> Pixel
- connectionNumber :: Display -> CInt
- defaultColormap :: Display -> ScreenNumber -> Colormap
- defaultGC :: Display -> ScreenNumber -> GC
- defaultDepth :: Display -> ScreenNumber -> CInt
- defaultScreen :: Display -> ScreenNumber
- defaultScreenOfDisplay :: Display -> Screen
- displayHeight :: Display -> ScreenNumber -> CInt
- displayHeightMM :: Display -> ScreenNumber -> CInt
- displayWidth :: Display -> ScreenNumber -> CInt
- displayWidthMM :: Display -> ScreenNumber -> CInt
- maxRequestSize :: Display -> CInt
- displayMotionBufferSize :: Display -> CInt
- imageByteOrder :: Display -> CInt
- protocolRevision :: Display -> CInt
- protocolVersion :: Display -> CInt
- screenCount :: Display -> CInt
- defaultVisual :: Display -> ScreenNumber -> Visual
- displayCells :: Display -> ScreenNumber -> CInt
- displayPlanes :: Display -> ScreenNumber -> CInt
- screenOfDisplay :: Display -> ScreenNumber -> Screen
- defaultRootWindow :: Display -> Window
- rootWindow :: Display -> ScreenNumber -> IO Window
- qLength :: Display -> IO CInt
- noOp :: Display -> IO ()
- closeDisplay :: Display -> IO ()
- xC_xterm :: Glyph
- xC_watch :: Glyph
- xC_ur_angle :: Glyph
- xC_umbrella :: Glyph
- xC_ul_angle :: Glyph
- xC_trek :: Glyph
- xC_top_tee :: Glyph
- xC_top_side :: Glyph
- xC_top_right_corner :: Glyph
- xC_top_left_corner :: Glyph
- xC_top_left_arrow :: Glyph
- xC_tcross :: Glyph
- xC_target :: Glyph
- xC_star :: Glyph
- xC_spraycan :: Glyph
- xC_spider :: Glyph
- xC_sizing :: Glyph
- xC_shuttle :: Glyph
- xC_sb_v_double_arrow :: Glyph
- xC_sb_up_arrow :: Glyph
- xC_sb_right_arrow :: Glyph
- xC_sb_left_arrow :: Glyph
- xC_sb_h_double_arrow :: Glyph
- xC_sb_down_arrow :: Glyph
- xC_sailboat :: Glyph
- xC_rtl_logo :: Glyph
- xC_rightbutton :: Glyph
- xC_right_tee :: Glyph
- xC_right_side :: Glyph
- xC_right_ptr :: Glyph
- xC_question_arrow :: Glyph
- xC_plus :: Glyph
- xC_pirate :: Glyph
- xC_pencil :: Glyph
- xC_mouse :: Glyph
- xC_man :: Glyph
- xC_lr_angle :: Glyph
- xC_ll_angle :: Glyph
- xC_leftbutton :: Glyph
- xC_left_tee :: Glyph
- xC_left_side :: Glyph
- xC_left_ptr :: Glyph
- xC_iron_cross :: Glyph
- xC_icon :: Glyph
- xC_heart :: Glyph
- xC_hand2 :: Glyph
- xC_hand1 :: Glyph
- xC_gumby :: Glyph
- xC_gobbler :: Glyph
- xC_fleur :: Glyph
- xC_exchange :: Glyph
- xC_draped_box :: Glyph
- xC_draft_small :: Glyph
- xC_draft_large :: Glyph
- xC_double_arrow :: Glyph
- xC_dotbox :: Glyph
- xC_dot :: Glyph
- xC_diamond_cross :: Glyph
- xC_crosshair :: Glyph
- xC_cross_reverse :: Glyph
- xC_cross :: Glyph
- xC_coffee_mug :: Glyph
- xC_clock :: Glyph
- xC_circle :: Glyph
- xC_center_ptr :: Glyph
- xC_box_spiral :: Glyph
- xC_bottom_tee :: Glyph
- xC_bottom_side :: Glyph
- xC_bottom_right_corner :: Glyph
- xC_bottom_left_corner :: Glyph
- xC_bogosity :: Glyph
- xC_boat :: Glyph
- xC_based_arrow_up :: Glyph
- xC_based_arrow_down :: Glyph
- xC_arrow :: Glyph
- xC_X_cursor :: Glyph
- textWidth :: FontStruct -> String -> Int32
- textExtents :: FontStruct -> String -> (FontDirection, Int32, Int32, CharStruct)
- descentFromFontStruct :: FontStruct -> Int32
- ascentFromFontStruct :: FontStruct -> Int32
- fontFromFontStruct :: FontStruct -> Font
- loadQueryFont :: Display -> String -> IO FontStruct
- fontFromGC :: Display -> GC -> IO Font
- queryFont :: Display -> Font -> IO FontStruct
- freeFont :: Display -> FontStruct -> IO ()
- type Glyph = Word16
- data FontStruct
- type CharStruct = (CInt, CInt, CInt, CInt, CInt)
- getPixel :: Image -> CInt -> CInt -> CULong
- getImage :: Display -> Drawable -> CInt -> CInt -> CUInt -> CUInt -> CULong -> ImageFormat -> IO Image
- createImage :: Display -> Visual -> CInt -> ImageFormat -> CInt -> Ptr CChar -> Dimension -> Dimension -> CInt -> CInt -> IO Image
- putImage :: Display -> Drawable -> GC -> Image -> Position -> Position -> Position -> Position -> Dimension -> Dimension -> IO ()
- destroyImage :: Image -> IO ()
- xGetPixel :: Image -> CInt -> CInt -> IO CULong
- setRegion :: Display -> GC -> Region -> IO CInt
- shrinkRegion :: Region -> Point -> IO CInt
- offsetRegion :: Region -> Point -> IO CInt
- clipBox :: Region -> IO (Rectangle, CInt)
- rectInRegion :: Region -> Rectangle -> IO RectInRegionResult
- pointInRegion :: Region -> Point -> IO Bool
- equalRegion :: Region -> Region -> IO Bool
- emptyRegion :: Region -> IO Bool
- xorRegion :: Region -> Region -> Region -> IO CInt
- unionRegion :: Region -> Region -> Region -> IO CInt
- unionRectWithRegion :: Rectangle -> Region -> Region -> IO CInt
- subtractRegion :: Region -> Region -> Region -> IO CInt
- intersectRegion :: Region -> Region -> Region -> IO CInt
- polygonRegion :: [Point] -> FillRule -> IO Region
- createRegion :: IO Region
- rectanglePart :: RectInRegionResult
- rectangleIn :: RectInRegionResult
- rectangleOut :: RectInRegionResult
- data Region
- type RectInRegionResult = CInt
- blackPixelOfScreen :: Screen -> Pixel
- whitePixelOfScreen :: Screen -> Pixel
- cellsOfScreen :: Screen -> CInt
- defaultColormapOfScreen :: Screen -> Colormap
- defaultDepthOfScreen :: Screen -> CInt
- defaultGCOfScreen :: Screen -> GC
- defaultVisualOfScreen :: Screen -> Visual
- doesBackingStore :: Screen -> Bool
- doesSaveUnders :: Screen -> Bool
- displayOfScreen :: Screen -> Display
- eventMaskOfScreen :: Screen -> EventMask
- minCmapsOfScreen :: Screen -> CInt
- maxCmapsOfScreen :: Screen -> CInt
- rootWindowOfScreen :: Screen -> Window
- widthOfScreen :: Screen -> Dimension
- widthMMOfScreen :: Screen -> Dimension
- heightOfScreen :: Screen -> Dimension
- heightMMOfScreen :: Screen -> Dimension
- planesOfScreen :: Screen -> CInt
- screenNumberOfScreen :: Screen -> ScreenNumber
- newtype Display = Display (Ptr Display)
- data Screen
- data Visual
- data GC
- data SetWindowAttributes
- data VisualInfo = VisualInfo {}
- data Image
- type Pixel = Word64
- type Position = Int32
- type Dimension = Word32
- type Angle = CInt
- type ScreenNumber = Word32
- type Buffer = CInt
- data Point = Point {}
- data Rectangle = Rectangle {
- rect_x :: !Position
- rect_y :: !Position
- rect_width :: !Dimension
- rect_height :: !Dimension
- data Arc = Arc {
- arc_x :: Position
- arc_y :: Position
- arc_width :: Dimension
- arc_height :: Dimension
- arc_angle1 :: Angle
- arc_angle2 :: Angle
- data Segment = Segment {}
- data Color = Color {
- color_pixel :: Pixel
- color_red :: Word16
- color_green :: Word16
- color_blue :: Word16
- color_flags :: Word8
- xRR_UnknownConnection :: Connection
- xRR_Disconnected :: Connection
- xRR_Connected :: Connection
- xRR_Reflect_Y :: Reflection
- xRR_Reflect_X :: Reflection
- xRR_Rotate_270 :: Rotation
- xRR_Rotate_180 :: Rotation
- xRR_Rotate_90 :: Rotation
- xRR_Rotate_0 :: Rotation
- zPixmap :: ImageFormat
- xyPixmap :: ImageFormat
- xyBitmap :: ImageFormat
- fontRightToLeft :: FontDirection
- fontLeftToRight :: FontDirection
- doBlue :: Word8
- doGreen :: Word8
- doRed :: Word8
- always :: BackingStore
- whenMapped :: BackingStore
- notUseful :: BackingStore
- unmapGravity :: WindowGravity
- staticGravity :: BitGravity
- southEastGravity :: BitGravity
- southGravity :: BitGravity
- southWestGravity :: BitGravity
- eastGravity :: BitGravity
- centerGravity :: BitGravity
- westGravity :: BitGravity
- northEastGravity :: BitGravity
- northGravity :: BitGravity
- northWestGravity :: BitGravity
- forgetGravity :: BitGravity
- setModeDelete :: ChangeSaveSetMode
- setModeInsert :: ChangeSaveSetMode
- mappingPointer :: MappingRequest
- mappingKeyboard :: MappingRequest
- mappingModifier :: MappingRequest
- allocAll :: ColormapAlloc
- allocNone :: ColormapAlloc
- mSBFirst :: ByteOrder
- lSBFirst :: ByteOrder
- lowerHighest :: CirculationDirection
- raiseLowest :: CirculationDirection
- gCLastBit :: GCMask
- gCArcMode :: GCMask
- gCDashList :: GCMask
- gCDashOffset :: GCMask
- gCClipMask :: GCMask
- gCClipYOrigin :: GCMask
- gCClipXOrigin :: GCMask
- gCGraphicsExposures :: GCMask
- gCSubwindowMode :: GCMask
- gCFont :: GCMask
- gCTileStipYOrigin :: GCMask
- gCTileStipXOrigin :: GCMask
- gCStipple :: GCMask
- gCTile :: GCMask
- gCFillRule :: GCMask
- gCFillStyle :: GCMask
- gCJoinStyle :: GCMask
- gCCapStyle :: GCMask
- gCLineStyle :: GCMask
- gCLineWidth :: GCMask
- gCBackground :: GCMask
- gCForeground :: GCMask
- gCPlaneMask :: GCMask
- gCFunction :: GCMask
- arcPieSlice :: ArcMode
- arcChord :: ArcMode
- convex :: PolygonShape
- nonconvex :: PolygonShape
- complex :: PolygonShape
- coordModePrevious :: CoordinateMode
- coordModeOrigin :: CoordinateMode
- includeInferiors :: SubWindowMode
- clipByChildren :: SubWindowMode
- windingRule :: FillRule
- evenOddRule :: FillRule
- fillOpaqueStippled :: FillStyle
- fillStippled :: FillStyle
- fillTiled :: FillStyle
- fillSolid :: FillStyle
- joinBevel :: JoinStyle
- joinRound :: JoinStyle
- joinMiter :: JoinStyle
- capProjecting :: CapStyle
- capRound :: CapStyle
- capButt :: CapStyle
- capNotLast :: CapStyle
- lineDoubleDash :: LineStyle
- lineOnOffDash :: LineStyle
- lineSolid :: LineStyle
- gXset :: GXFunction
- gXnand :: GXFunction
- gXorInverted :: GXFunction
- gXcopyInverted :: GXFunction
- gXorReverse :: GXFunction
- gXinvert :: GXFunction
- gXequiv :: GXFunction
- gXnor :: GXFunction
- gXor :: GXFunction
- gXxor :: GXFunction
- gXnoop :: GXFunction
- gXandInverted :: GXFunction
- gXcopy :: GXFunction
- gXandReverse :: GXFunction
- gXand :: GXFunction
- gXclear :: GXFunction
- stippleShape :: QueryBestSizeClass
- tileShape :: QueryBestSizeClass
- cursorShape :: QueryBestSizeClass
- retainTemporary :: CloseDownMode
- retainPermanent :: CloseDownMode
- destroyAll :: CloseDownMode
- cWHeight :: AttributeMask
- cWWidth :: AttributeMask
- cWY :: AttributeMask
- cWX :: AttributeMask
- cWCursor :: AttributeMask
- cWColormap :: AttributeMask
- cWDontPropagate :: AttributeMask
- cWEventMask :: AttributeMask
- cWSaveUnder :: AttributeMask
- cWOverrideRedirect :: AttributeMask
- cWBackingPixel :: AttributeMask
- cWBackingPlanes :: AttributeMask
- cWBackingStore :: AttributeMask
- cWWinGravity :: AttributeMask
- cWBitGravity :: AttributeMask
- cWBorderPixel :: AttributeMask
- cWBorderPixmap :: AttributeMask
- cWBackPixel :: AttributeMask
- cWBackPixmap :: AttributeMask
- inputOnly :: WindowClass
- inputOutput :: WindowClass
- copyFromParent :: WindowClass
- throwIfZero :: String -> IO Status -> IO ()
- lastExtensionError :: ErrorCode
- firstExtensionError :: ErrorCode
- badImplementation :: ErrorCode
- badLength :: ErrorCode
- badName :: ErrorCode
- badIDChoice :: ErrorCode
- badGC :: ErrorCode
- badColor :: ErrorCode
- badAlloc :: ErrorCode
- badAccess :: ErrorCode
- badDrawable :: ErrorCode
- badMatch :: ErrorCode
- badFont :: ErrorCode
- badCursor :: ErrorCode
- badAtom :: ErrorCode
- badPixmap :: ErrorCode
- badWindow :: ErrorCode
- badValue :: ErrorCode
- badRequest :: ErrorCode
- success :: ErrorCode
- revertToParent :: FocusMode
- revertToPointerRoot :: FocusMode
- revertToNone :: FocusMode
- syncBoth :: AllowEvents
- asyncBoth :: AllowEvents
- replayKeyboard :: AllowEvents
- syncKeyboard :: AllowEvents
- asyncKeyboard :: AllowEvents
- replayPointer :: AllowEvents
- syncPointer :: AllowEvents
- asyncPointer :: AllowEvents
- grabFrozen :: GrabStatus
- grabNotViewable :: GrabStatus
- grabInvalidTime :: GrabStatus
- alreadyGrabbed :: GrabStatus
- grabSuccess :: GrabStatus
- grabModeAsync :: GrabMode
- grabModeSync :: GrabMode
- colormapInstalled :: ColormapNotification
- colormapUninstalled :: ColormapNotification
- propertyDelete :: PropertyNotification
- propertyNewValue :: PropertyNotification
- familyChaos :: Protocol
- familyDECnet :: Protocol
- familyInternet :: Protocol
- placeOnBottom :: Place
- placeOnTop :: Place
- visibilityFullyObscured :: Visibility
- visibilityPartiallyObscured :: Visibility
- visibilityUnobscured :: Visibility
- notifyDetailNone :: NotifyDetail
- notifyPointerRoot :: NotifyDetail
- notifyPointer :: NotifyDetail
- notifyNonlinearVirtual :: NotifyDetail
- notifyNonlinear :: NotifyDetail
- notifyInferior :: NotifyDetail
- notifyVirtual :: NotifyDetail
- notifyAncestor :: NotifyDetail
- notifyHint :: NotifyMode
- notifyWhileGrabbed :: NotifyMode
- notifyUngrab :: NotifyMode
- notifyGrab :: NotifyMode
- notifyNormal :: NotifyMode
- button5 :: Button
- button4 :: Button
- button3 :: Button
- button2 :: Button
- button1 :: Button
- button5Mask :: ButtonMask
- button4Mask :: ButtonMask
- button3Mask :: ButtonMask
- button2Mask :: ButtonMask
- button1Mask :: ButtonMask
- mod5Mask :: KeyMask
- mod4Mask :: KeyMask
- mod3Mask :: KeyMask
- mod2Mask :: KeyMask
- mod1Mask :: KeyMask
- controlMask :: KeyMask
- lockMask :: KeyMask
- shiftMask :: KeyMask
- noModMask :: KeyMask
- anyModifier :: Modifier
- mod5MapIndex :: Modifier
- mod4MapIndex :: Modifier
- mod3MapIndex :: Modifier
- mod2MapIndex :: Modifier
- mod1MapIndex :: Modifier
- controlMapIndex :: Modifier
- lockMapIndex :: Modifier
- shiftMapIndex :: Modifier
- screenSaverNotify :: EventType
- lASTEvent :: EventType
- rrNotifyOutputProperty :: EventType
- rrNotifyOutputChange :: EventType
- rrNotifyCrtcChange :: EventType
- rrNotify :: EventType
- rrScreenChangeNotify :: EventType
- mappingNotify :: EventType
- clientMessage :: EventType
- colormapNotify :: EventType
- selectionNotify :: EventType
- selectionRequest :: EventType
- selectionClear :: EventType
- propertyNotify :: EventType
- circulateRequest :: EventType
- circulateNotify :: EventType
- resizeRequest :: EventType
- gravityNotify :: EventType
- configureRequest :: EventType
- configureNotify :: EventType
- reparentNotify :: EventType
- mapRequest :: EventType
- mapNotify :: EventType
- unmapNotify :: EventType
- destroyNotify :: EventType
- createNotify :: EventType
- visibilityNotify :: EventType
- noExpose :: EventType
- graphicsExpose :: EventType
- expose :: EventType
- keymapNotify :: EventType
- focusOut :: EventType
- focusIn :: EventType
- leaveNotify :: EventType
- enterNotify :: EventType
- motionNotify :: EventType
- buttonRelease :: EventType
- buttonPress :: EventType
- keyRelease :: EventType
- keyPress :: EventType
- screenSaverNotifyMask :: EventMask
- screenSaverCycleMask :: EventMask
- rrOutputPropertyNotifyMask :: EventMask
- rrOutputChangeNotifyMask :: EventMask
- rrCrtcChangeNotifyMask :: EventMask
- rrScreenChangeNotifyMask :: EventMask
- ownerGrabButtonMask :: EventMask
- colormapChangeMask :: EventMask
- propertyChangeMask :: EventMask
- focusChangeMask :: EventMask
- substructureRedirectMask :: EventMask
- substructureNotifyMask :: EventMask
- resizeRedirectMask :: EventMask
- structureNotifyMask :: EventMask
- visibilityChangeMask :: EventMask
- exposureMask :: EventMask
- keymapStateMask :: EventMask
- buttonMotionMask :: EventMask
- button5MotionMask :: EventMask
- button4MotionMask :: EventMask
- button3MotionMask :: EventMask
- button2MotionMask :: EventMask
- button1MotionMask :: EventMask
- pointerMotionHintMask :: EventMask
- pointerMotionMask :: EventMask
- leaveWindowMask :: EventMask
- enterWindowMask :: EventMask
- buttonReleaseMask :: EventMask
- buttonPressMask :: EventMask
- keyReleaseMask :: EventMask
- keyPressMask :: EventMask
- noEventMask :: EventMask
- xK_ydiaeresis :: KeySym
- xK_thorn :: KeySym
- xK_yacute :: KeySym
- xK_udiaeresis :: KeySym
- xK_ucircumflex :: KeySym
- xK_uacute :: KeySym
- xK_ugrave :: KeySym
- xK_oslash :: KeySym
- xK_division :: KeySym
- xK_odiaeresis :: KeySym
- xK_otilde :: KeySym
- xK_ocircumflex :: KeySym
- xK_oacute :: KeySym
- xK_ograve :: KeySym
- xK_ntilde :: KeySym
- xK_eth :: KeySym
- xK_idiaeresis :: KeySym
- xK_icircumflex :: KeySym
- xK_iacute :: KeySym
- xK_igrave :: KeySym
- xK_ediaeresis :: KeySym
- xK_ecircumflex :: KeySym
- xK_eacute :: KeySym
- xK_egrave :: KeySym
- xK_ccedilla :: KeySym
- xK_ae :: KeySym
- xK_aring :: KeySym
- xK_adiaeresis :: KeySym
- xK_atilde :: KeySym
- xK_acircumflex :: KeySym
- xK_aacute :: KeySym
- xK_agrave :: KeySym
- xK_ssharp :: KeySym
- xK_Thorn :: KeySym
- xK_THORN :: KeySym
- xK_Yacute :: KeySym
- xK_Udiaeresis :: KeySym
- xK_Ucircumflex :: KeySym
- xK_Uacute :: KeySym
- xK_Ugrave :: KeySym
- xK_Ooblique :: KeySym
- xK_multiply :: KeySym
- xK_Odiaeresis :: KeySym
- xK_Otilde :: KeySym
- xK_Ocircumflex :: KeySym
- xK_Oacute :: KeySym
- xK_Ograve :: KeySym
- xK_Ntilde :: KeySym
- xK_Eth :: KeySym
- xK_ETH :: KeySym
- xK_Idiaeresis :: KeySym
- xK_Icircumflex :: KeySym
- xK_Iacute :: KeySym
- xK_Igrave :: KeySym
- xK_Ediaeresis :: KeySym
- xK_Ecircumflex :: KeySym
- xK_Eacute :: KeySym
- xK_Egrave :: KeySym
- xK_Ccedilla :: KeySym
- xK_AE :: KeySym
- xK_Aring :: KeySym
- xK_Adiaeresis :: KeySym
- xK_Atilde :: KeySym
- xK_Acircumflex :: KeySym
- xK_Aacute :: KeySym
- xK_Agrave :: KeySym
- xK_questiondown :: KeySym
- xK_threequarters :: KeySym
- xK_onehalf :: KeySym
- xK_onequarter :: KeySym
- xK_guillemotright :: KeySym
- xK_masculine :: KeySym
- xK_onesuperior :: KeySym
- xK_cedilla :: KeySym
- xK_periodcentered :: KeySym
- xK_paragraph :: KeySym
- xK_mu :: KeySym
- xK_acute :: KeySym
- xK_threesuperior :: KeySym
- xK_twosuperior :: KeySym
- xK_plusminus :: KeySym
- xK_degree :: KeySym
- xK_macron :: KeySym
- xK_registered :: KeySym
- xK_hyphen :: KeySym
- xK_notsign :: KeySym
- xK_guillemotleft :: KeySym
- xK_ordfeminine :: KeySym
- xK_copyright :: KeySym
- xK_diaeresis :: KeySym
- xK_section :: KeySym
- xK_brokenbar :: KeySym
- xK_yen :: KeySym
- xK_currency :: KeySym
- xK_sterling :: KeySym
- xK_cent :: KeySym
- xK_exclamdown :: KeySym
- xK_nobreakspace :: KeySym
- xK_asciitilde :: KeySym
- xK_braceright :: KeySym
- xK_bar :: KeySym
- xK_braceleft :: KeySym
- xK_z :: KeySym
- xK_y :: KeySym
- xK_x :: KeySym
- xK_w :: KeySym
- xK_v :: KeySym
- xK_u :: KeySym
- xK_t :: KeySym
- xK_s :: KeySym
- xK_r :: KeySym
- xK_q :: KeySym
- xK_p :: KeySym
- xK_o :: KeySym
- xK_n :: KeySym
- xK_m :: KeySym
- xK_l :: KeySym
- xK_k :: KeySym
- xK_j :: KeySym
- xK_i :: KeySym
- xK_h :: KeySym
- xK_g :: KeySym
- xK_f :: KeySym
- xK_e :: KeySym
- xK_d :: KeySym
- xK_c :: KeySym
- xK_b :: KeySym
- xK_a :: KeySym
- xK_quoteleft :: KeySym
- xK_grave :: KeySym
- xK_underscore :: KeySym
- xK_asciicircum :: KeySym
- xK_bracketright :: KeySym
- xK_backslash :: KeySym
- xK_bracketleft :: KeySym
- xK_Z :: KeySym
- xK_Y :: KeySym
- xK_X :: KeySym
- xK_W :: KeySym
- xK_V :: KeySym
- xK_U :: KeySym
- xK_T :: KeySym
- xK_S :: KeySym
- xK_R :: KeySym
- xK_Q :: KeySym
- xK_P :: KeySym
- xK_O :: KeySym
- xK_N :: KeySym
- xK_M :: KeySym
- xK_L :: KeySym
- xK_K :: KeySym
- xK_J :: KeySym
- xK_I :: KeySym
- xK_H :: KeySym
- xK_G :: KeySym
- xK_F :: KeySym
- xK_E :: KeySym
- xK_D :: KeySym
- xK_C :: KeySym
- xK_B :: KeySym
- xK_A :: KeySym
- xK_at :: KeySym
- xK_question :: KeySym
- xK_greater :: KeySym
- xK_equal :: KeySym
- xK_less :: KeySym
- xK_semicolon :: KeySym
- xK_colon :: KeySym
- xK_9 :: KeySym
- xK_8 :: KeySym
- xK_7 :: KeySym
- xK_6 :: KeySym
- xK_5 :: KeySym
- xK_4 :: KeySym
- xK_3 :: KeySym
- xK_2 :: KeySym
- xK_1 :: KeySym
- xK_0 :: KeySym
- xK_slash :: KeySym
- xK_period :: KeySym
- xK_minus :: KeySym
- xK_comma :: KeySym
- xK_plus :: KeySym
- xK_asterisk :: KeySym
- xK_parenright :: KeySym
- xK_parenleft :: KeySym
- xK_quoteright :: KeySym
- xK_apostrophe :: KeySym
- xK_ampersand :: KeySym
- xK_percent :: KeySym
- xK_dollar :: KeySym
- xK_numbersign :: KeySym
- xK_quotedbl :: KeySym
- xK_exclam :: KeySym
- xK_space :: KeySym
- xK_Hyper_R :: KeySym
- xK_Hyper_L :: KeySym
- xK_Super_R :: KeySym
- xK_Super_L :: KeySym
- xK_Alt_R :: KeySym
- xK_Alt_L :: KeySym
- xK_Meta_R :: KeySym
- xK_Meta_L :: KeySym
- xK_Shift_Lock :: KeySym
- xK_Caps_Lock :: KeySym
- xK_Control_R :: KeySym
- xK_Control_L :: KeySym
- xK_Shift_R :: KeySym
- xK_Shift_L :: KeySym
- xK_R15 :: KeySym
- xK_F35 :: KeySym
- xK_R14 :: KeySym
- xK_F34 :: KeySym
- xK_R13 :: KeySym
- xK_F33 :: KeySym
- xK_R12 :: KeySym
- xK_F32 :: KeySym
- xK_R11 :: KeySym
- xK_F31 :: KeySym
- xK_R10 :: KeySym
- xK_F30 :: KeySym
- xK_R9 :: KeySym
- xK_F29 :: KeySym
- xK_R8 :: KeySym
- xK_F28 :: KeySym
- xK_R7 :: KeySym
- xK_F27 :: KeySym
- xK_R6 :: KeySym
- xK_F26 :: KeySym
- xK_R5 :: KeySym
- xK_F25 :: KeySym
- xK_R4 :: KeySym
- xK_F24 :: KeySym
- xK_R3 :: KeySym
- xK_F23 :: KeySym
- xK_R2 :: KeySym
- xK_F22 :: KeySym
- xK_R1 :: KeySym
- xK_F21 :: KeySym
- xK_L10 :: KeySym
- xK_F20 :: KeySym
- xK_L9 :: KeySym
- xK_F19 :: KeySym
- xK_L8 :: KeySym
- xK_F18 :: KeySym
- xK_L7 :: KeySym
- xK_F17 :: KeySym
- xK_L6 :: KeySym
- xK_F16 :: KeySym
- xK_L5 :: KeySym
- xK_F15 :: KeySym
- xK_L4 :: KeySym
- xK_F14 :: KeySym
- xK_L3 :: KeySym
- xK_F13 :: KeySym
- xK_L2 :: KeySym
- xK_F12 :: KeySym
- xK_L1 :: KeySym
- xK_F11 :: KeySym
- xK_F10 :: KeySym
- xK_F9 :: KeySym
- xK_F8 :: KeySym
- xK_F7 :: KeySym
- xK_F6 :: KeySym
- xK_F5 :: KeySym
- xK_F4 :: KeySym
- xK_F3 :: KeySym
- xK_F2 :: KeySym
- xK_F1 :: KeySym
- xK_KP_9 :: KeySym
- xK_KP_8 :: KeySym
- xK_KP_7 :: KeySym
- xK_KP_6 :: KeySym
- xK_KP_5 :: KeySym
- xK_KP_4 :: KeySym
- xK_KP_3 :: KeySym
- xK_KP_2 :: KeySym
- xK_KP_1 :: KeySym
- xK_KP_0 :: KeySym
- xK_KP_Divide :: KeySym
- xK_KP_Decimal :: KeySym
- xK_KP_Subtract :: KeySym
- xK_KP_Separator :: KeySym
- xK_KP_Add :: KeySym
- xK_KP_Multiply :: KeySym
- xK_KP_Equal :: KeySym
- xK_KP_Delete :: KeySym
- xK_KP_Insert :: KeySym
- xK_KP_Begin :: KeySym
- xK_KP_End :: KeySym
- xK_KP_Page_Down :: KeySym
- xK_KP_Next :: KeySym
- xK_KP_Page_Up :: KeySym
- xK_KP_Prior :: KeySym
- xK_KP_Down :: KeySym
- xK_KP_Right :: KeySym
- xK_KP_Up :: KeySym
- xK_KP_Left :: KeySym
- xK_KP_Home :: KeySym
- xK_KP_F4 :: KeySym
- xK_KP_F3 :: KeySym
- xK_KP_F2 :: KeySym
- xK_KP_F1 :: KeySym
- xK_KP_Enter :: KeySym
- xK_KP_Tab :: KeySym
- xK_KP_Space :: KeySym
- xK_Num_Lock :: KeySym
- xK_script_switch :: KeySym
- xK_Mode_switch :: KeySym
- xK_Break :: KeySym
- xK_Help :: KeySym
- xK_Cancel :: KeySym
- xK_Find :: KeySym
- xK_Menu :: KeySym
- xK_Redo :: KeySym
- xK_Undo :: KeySym
- xK_Insert :: KeySym
- xK_Execute :: KeySym
- xK_Print :: KeySym
- xK_Select :: KeySym
- xK_Begin :: KeySym
- xK_End :: KeySym
- xK_Page_Down :: KeySym
- xK_Next :: KeySym
- xK_Page_Up :: KeySym
- xK_Prior :: KeySym
- xK_Down :: KeySym
- xK_Right :: KeySym
- xK_Up :: KeySym
- xK_Left :: KeySym
- xK_Home :: KeySym
- xK_PreviousCandidate :: KeySym
- xK_MultipleCandidate :: KeySym
- xK_SingleCandidate :: KeySym
- xK_Codeinput :: KeySym
- xK_Multi_key :: KeySym
- xK_Delete :: KeySym
- xK_Escape :: KeySym
- xK_Sys_Req :: KeySym
- xK_Scroll_Lock :: KeySym
- xK_Pause :: KeySym
- xK_Return :: KeySym
- xK_Clear :: KeySym
- xK_Linefeed :: KeySym
- xK_Tab :: KeySym
- xK_BackSpace :: KeySym
- xK_VoidSymbol :: KeySym
- type XID = Word64
- type Mask = Word64
- type Atom = Word64
- type VisualID = Word64
- type Time = Word64
- type Window = XID
- type Drawable = XID
- type Font = XID
- type Pixmap = XID
- type Cursor = XID
- type Colormap = XID
- type GContext = XID
- type KeyCode = Word8
- type KeySym = XID
- type EventMask = Mask
- type EventType = Word32
- type Modifier = CUInt
- type KeyMask = Modifier
- type ButtonMask = Modifier
- type Button = Word32
- type NotifyMode = CInt
- type NotifyDetail = CInt
- type Visibility = CInt
- type Place = CInt
- type Protocol = CInt
- type PropertyNotification = CInt
- type ColormapNotification = CInt
- type GrabMode = CInt
- type GrabStatus = CInt
- type AllowEvents = CInt
- type FocusMode = CInt
- type ErrorCode = CInt
- type Status = CInt
- type WindowClass = CInt
- type AttributeMask = Mask
- type CloseDownMode = CInt
- type QueryBestSizeClass = CInt
- type GXFunction = CInt
- type LineStyle = CInt
- type CapStyle = CInt
- type JoinStyle = CInt
- type FillStyle = CInt
- type FillRule = CInt
- type SubWindowMode = CInt
- type CoordinateMode = CInt
- type PolygonShape = CInt
- type ArcMode = CInt
- type GCMask = CInt
- type CirculationDirection = CInt
- type ByteOrder = CInt
- type ColormapAlloc = CInt
- type MappingRequest = CInt
- type ChangeSaveSetMode = CInt
- type BitGravity = CInt
- type WindowGravity = CInt
- type BackingStore = CInt
- type FontDirection = CInt
- type ImageFormat = CInt
- type Rotation = Word16
- type Reflection = Word16
- type SizeID = Word16
- type SubpixelOrder = Word16
- type Connection = Word16
- type RROutput = Word64
- type RRCrtc = Word64
- type RRMode = Word64
- type XRRModeFlags = Word64
- module Graphics.X11.Xlib.Extras
- (.|.) :: Bits a => a -> a -> a
- class Monad m => MonadState s (m :: Type -> Type) | m -> s where
- gets :: MonadState s m => (s -> a) -> m a
- modify :: MonadState s m => (s -> s) -> m ()
- class Monad m => MonadReader r (m :: Type -> Type) | m -> r where
- asks :: MonadReader r m => (r -> a) -> m a
- class Monad m => MonadIO (m :: Type -> Type) where
Documentation
module XMonad.Main
module XMonad.Core
module XMonad.Config
module XMonad.Layout
module XMonad.ManageHook
module XMonad.Operations
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()
.
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()
.
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()
.
set_cursor :: Ptr SetWindowAttributes -> Cursor -> IO () Source #
set_colormap :: Ptr SetWindowAttributes -> Colormap -> IO () Source #
set_override_redirect :: Ptr SetWindowAttributes -> Bool -> IO () Source #
set_do_not_propagate_mask :: Ptr SetWindowAttributes -> EventMask -> IO () Source #
set_event_mask :: Ptr SetWindowAttributes -> EventMask -> IO () Source #
set_save_under :: Ptr SetWindowAttributes -> Bool -> IO () Source #
set_backing_pixel :: Ptr SetWindowAttributes -> Pixel -> IO () Source #
set_backing_planes :: Ptr SetWindowAttributes -> Pixel -> IO () Source #
set_backing_store :: Ptr SetWindowAttributes -> BackingStore -> IO () Source #
set_win_gravity :: Ptr SetWindowAttributes -> WindowGravity -> IO () Source #
set_bit_gravity :: Ptr SetWindowAttributes -> BitGravity -> IO () Source #
set_border_pixel :: Ptr SetWindowAttributes -> Pixel -> IO () Source #
set_border_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO () Source #
set_background_pixel :: Ptr SetWindowAttributes -> Pixel -> IO () Source #
set_background_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO () Source #
allocaSetWindowAttributes :: (Ptr SetWindowAttributes -> IO a) -> IO a Source #
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()
getVisualInfo :: Display -> VisualInfoMask -> VisualInfo -> IO [VisualInfo] Source #
visualBlueMaskMask :: VisualInfoMask Source #
interface to the X11 library function XGetVisualInfo()
getPointerControl :: Display -> IO (CInt, CInt, CInt) Source #
interface to the X11 library function XGetPointerControl()
.
getScreenSaver :: Display -> IO (CInt, CInt, PreferBlankingMode, AllowExposuresMode) Source #
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()
.
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()
.
initThreads :: IO Status Source #
lockDisplay :: Display -> IO () Source #
unlockDisplay :: Display -> IO () Source #
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()
.
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()
.
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()
.
type AllowExposuresMode = CInt Source #
type PreferBlankingMode = CInt Source #
type ScreenSaverMode = CInt Source #
type VisualInfoMask = CLong Source #
cAP_HEIGHT :: Atom Source #
fAMILY_NAME :: Atom Source #
rESOLUTION :: Atom Source #
pOINT_SIZE :: Atom Source #
qUAD_WIDTH :: Atom Source #
iTALIC_ANGLE :: Atom Source #
sUBSCRIPT_Y :: Atom Source #
sUBSCRIPT_X :: Atom Source #
sUPERSCRIPT_Y :: Atom Source #
sUPERSCRIPT_X :: Atom Source #
nORM_SPACE :: Atom Source #
wM_ZOOM_HINTS :: Atom Source #
wM_SIZE_HINTS :: Atom Source #
wM_ICON_SIZE :: Atom Source #
wM_ICON_NAME :: Atom Source #
wM_COMMAND :: Atom Source #
rGB_RED_MAP :: Atom Source #
rGB_GREEN_MAP :: Atom Source #
rGB_GRAY_MAP :: Atom Source #
rGB_BLUE_MAP :: Atom Source #
rGB_BEST_MAP :: Atom Source #
rGB_COLOR_MAP :: Atom Source #
cUT_BUFFER7 :: Atom Source #
cUT_BUFFER6 :: Atom Source #
cUT_BUFFER5 :: Atom Source #
cUT_BUFFER4 :: Atom Source #
cUT_BUFFER3 :: Atom Source #
cUT_BUFFER2 :: Atom Source #
cUT_BUFFER1 :: Atom Source #
cUT_BUFFER0 :: Atom Source #
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()
.
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()
.
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.
asKeyEvent :: XEventPtr -> XKeyEventPtr Source #
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()
.
type QueuedMode = CInt Source #
Instances
Data XEvent | |
Defined in Graphics.X11.Xlib.Event 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 | |
Eq XEvent | |
Ord XEvent | |
Defined in Graphics.X11.Xlib.Event |
type XKeyEventPtr = Ptr XKeyEvent Source #
type XMotionEvent = (Window, Window, Time, CInt, CInt, CInt, CInt, Modifier, NotifyMode, Bool) Source #
type XMappingEvent = (MappingRequest, KeyCode, CInt) Source #
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()
.
closeDisplay :: Display -> IO () Source #
interface to the X11 library function XCloseDisplay()
.
xC_ur_angle :: Glyph Source #
xC_umbrella :: Glyph Source #
xC_ul_angle :: Glyph Source #
xC_top_tee :: Glyph Source #
xC_top_side :: Glyph Source #
xC_spraycan :: Glyph Source #
xC_shuttle :: Glyph Source #
xC_sailboat :: Glyph Source #
xC_rtl_logo :: Glyph Source #
xC_right_tee :: Glyph Source #
xC_right_ptr :: Glyph Source #
xC_lr_angle :: Glyph Source #
xC_ll_angle :: Glyph Source #
xC_left_tee :: Glyph Source #
xC_left_side :: Glyph Source #
xC_left_ptr :: Glyph Source #
xC_gobbler :: Glyph Source #
xC_exchange :: Glyph Source #
xC_crosshair :: Glyph Source #
xC_bogosity :: Glyph Source #
xC_X_cursor :: Glyph Source #
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()
.
fontFromFontStruct :: FontStruct -> Font Source #
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
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()
.
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()
.
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()
.
Instances
Data Region | |
Defined in Graphics.X11.Xlib.Region 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 | |
Eq Region | |
Ord Region | |
Defined in Graphics.X11.Xlib.Region |
type RectInRegionResult = CInt Source #
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()
.
pointer to an X11 Display
structure
Instances
Data Display | |
Defined in Graphics.X11.Xlib.Types 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 | |
Eq Display | |
Ord Display | |
Defined in Graphics.X11.Xlib.Types |
pointer to an X11 Screen
structure
Instances
Data Screen | |
Defined in Graphics.X11.Xlib.Types 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 | |
Eq Screen | |
Ord Screen | |
Defined in Graphics.X11.Xlib.Types |
pointer to an X11 Visual
structure
Instances
Data Visual | |
Defined in Graphics.X11.Xlib.Types 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 | |
Eq Visual | |
Ord Visual | |
Defined in Graphics.X11.Xlib.Types |
pointer to an X11 GC
structure
Instances
Data GC | |
Defined in Graphics.X11.Xlib.Types 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 | |
Eq GC | |
Ord GC | |
data SetWindowAttributes Source #
pointer to an X11 XSetWindowAttributes
structure
Instances
data VisualInfo Source #
counterpart of an X11 XVisualInfo
structure
Instances
Storable VisualInfo | |
Defined in Graphics.X11.Xlib.Types sizeOf :: VisualInfo -> Int Source # alignment :: VisualInfo -> Int Source # peekElemOff :: Ptr VisualInfo -> Int -> IO VisualInfo Source # pokeElemOff :: Ptr VisualInfo -> Int -> VisualInfo -> IO () Source # peekByteOff :: Ptr b -> Int -> IO VisualInfo Source # pokeByteOff :: Ptr b -> Int -> VisualInfo -> IO () Source # peek :: Ptr VisualInfo -> IO VisualInfo Source # poke :: Ptr VisualInfo -> VisualInfo -> IO () Source # | |
Show VisualInfo | |
Defined in Graphics.X11.Xlib.Types | |
Default VisualInfo | |
Defined in Graphics.X11.Xlib.Types def :: VisualInfo Source # | |
Eq VisualInfo | |
Defined in Graphics.X11.Xlib.Types (==) :: VisualInfo -> VisualInfo -> Bool Source # (/=) :: VisualInfo -> VisualInfo -> Bool Source # |
pointer to an X11 XImage
structure
Instances
Data Image | |
Defined in Graphics.X11.Xlib.Types 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 | |
Eq Image | |
Ord Image | |
Defined in Graphics.X11.Xlib.Types |
type ScreenNumber = Word32 Source #
counterpart of an X11 XPoint
structure
Instances
Data Point | |
Defined in Graphics.X11.Xlib.Types 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 | |
Defined in Graphics.X11.Xlib.Types sizeOf :: Point -> Int Source # alignment :: Point -> Int Source # peekElemOff :: Ptr Point -> Int -> IO Point Source # pokeElemOff :: Ptr Point -> Int -> Point -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Point Source # pokeByteOff :: Ptr b -> Int -> Point -> IO () Source # | |
Show Point | |
Eq Point | |
counterpart of an X11 XRectangle
structure
Rectangle | |
|
Instances
Data Rectangle | |
Defined in Graphics.X11.Xlib.Types 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 | |
Defined in Graphics.X11.Xlib.Types sizeOf :: Rectangle -> Int Source # alignment :: Rectangle -> Int Source # peekElemOff :: Ptr Rectangle -> Int -> IO Rectangle Source # pokeElemOff :: Ptr Rectangle -> Int -> Rectangle -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Rectangle Source # pokeByteOff :: Ptr b -> Int -> Rectangle -> IO () Source # | |
Read Rectangle | |
Show Rectangle | |
Eq Rectangle | |
counterpart of an X11 XArc
structure
Arc | |
|
Instances
Storable Arc | |
Defined in Graphics.X11.Xlib.Types | |
Show Arc | |
Eq Arc | |
counterpart of an X11 XSegment
structure
Instances
Data Segment | |
Defined in Graphics.X11.Xlib.Types 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 | |
Defined in Graphics.X11.Xlib.Types sizeOf :: Segment -> Int Source # alignment :: Segment -> Int Source # peekElemOff :: Ptr Segment -> Int -> IO Segment Source # pokeElemOff :: Ptr Segment -> Int -> Segment -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Segment Source # pokeByteOff :: Ptr b -> Int -> Segment -> IO () Source # | |
Show Segment | |
Eq Segment | |
counterpart of an X11 XColor
structure
Color | |
|
Instances
Data Color | |
Defined in Graphics.X11.Xlib.Types 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 | |
Defined in Graphics.X11.Xlib.Types sizeOf :: Color -> Int Source # alignment :: Color -> Int Source # peekElemOff :: Ptr Color -> Int -> IO Color Source # pokeElemOff :: Ptr Color -> Int -> Color -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Color Source # pokeByteOff :: Ptr b -> Int -> Color -> IO () Source # | |
Show Color | |
Eq Color | |
gCDashList :: GCMask Source #
gCClipMask :: GCMask Source #
gCFillRule :: GCMask Source #
gCFillStyle :: GCMask Source #
gCJoinStyle :: GCMask Source #
gCCapStyle :: GCMask Source #
gCLineStyle :: GCMask Source #
gCLineWidth :: GCMask Source #
gCPlaneMask :: GCMask Source #
gCFunction :: GCMask Source #
gXset :: GXFunction Source #
gXnand :: GXFunction Source #
gXequiv :: GXFunction Source #
gXnor :: GXFunction Source #
gXor :: GXFunction Source #
gXxor :: GXFunction Source #
gXnoop :: GXFunction Source #
gXcopy :: GXFunction Source #
gXand :: GXFunction Source #
gXclear :: GXFunction Source #
cWY :: AttributeMask Source #
cWX :: AttributeMask Source #
Xlib functions with return values of type Status
return zero on
failure and nonzero on success.
placeOnTop :: Place Source #
xK_division :: KeySym Source #
xK_ccedilla :: KeySym Source #
xK_Ooblique :: KeySym Source #
xK_multiply :: KeySym Source #
xK_Ccedilla :: KeySym Source #
xK_onehalf :: KeySym Source #
xK_cedilla :: KeySym Source #
xK_notsign :: KeySym Source #
xK_section :: KeySym Source #
xK_currency :: KeySym Source #
xK_sterling :: KeySym Source #
xK_question :: KeySym Source #
xK_greater :: KeySym Source #
xK_asterisk :: KeySym Source #
xK_percent :: KeySym Source #
xK_quotedbl :: KeySym Source #
xK_Hyper_R :: KeySym Source #
xK_Hyper_L :: KeySym Source #
xK_Super_R :: KeySym Source #
xK_Super_L :: KeySym Source #
xK_Shift_R :: KeySym Source #
xK_Shift_L :: KeySym Source #
xK_KP_Equal :: KeySym Source #
xK_KP_Begin :: KeySym Source #
xK_KP_Next :: KeySym Source #
xK_KP_Prior :: KeySym Source #
xK_KP_Down :: KeySym Source #
xK_KP_Right :: KeySym Source #
xK_KP_Left :: KeySym Source #
xK_KP_Home :: KeySym Source #
xK_KP_Enter :: KeySym Source #
xK_KP_Space :: KeySym Source #
xK_Num_Lock :: KeySym Source #
xK_Execute :: KeySym Source #
xK_Page_Up :: KeySym Source #
xK_Sys_Req :: KeySym Source #
xK_Linefeed :: KeySym Source #
type ButtonMask = Modifier Source #
type NotifyMode = CInt Source #
type NotifyDetail = CInt Source #
type Visibility = CInt Source #
Place of window relative to siblings (used in Circulation requests or events)
type PropertyNotification = CInt Source #
type ColormapNotification = CInt Source #
type GrabStatus = CInt Source #
type AllowEvents = CInt Source #
type WindowClass = CInt Source #
type AttributeMask = Mask Source #
type CloseDownMode = CInt Source #
type QueryBestSizeClass = CInt Source #
type GXFunction = CInt Source #
type SubWindowMode = CInt Source #
type CoordinateMode = CInt Source #
type PolygonShape = CInt Source #
type CirculationDirection = CInt Source #
type ColormapAlloc = CInt Source #
type MappingRequest = CInt Source #
type ChangeSaveSetMode = CInt Source #
type BitGravity = CInt Source #
type WindowGravity = CInt Source #
type BackingStore = CInt Source #
type FontDirection = CInt Source #
type ImageFormat = CInt Source #
type Reflection = Word16 Source #
type SubpixelOrder = Word16 Source #
type Connection = Word16 Source #
type XRRModeFlags = Word64 Source #
module Graphics.X11.Xlib.Extras
class Monad m => MonadState s (m :: Type -> Type) | m -> s where Source #
Minimal definition is either both of get
and put
or just state
Return the state from the internals of the monad.
Replace the state inside the monad.
state :: (s -> (a, s)) -> m a Source #
Embed a simple state action into the monad.
Instances
MonadState XState X Source # | |
MonadState s m => MonadState s (ListT m) | |
MonadState s m => MonadState s (MaybeT m) | |
(Error e, MonadState s m) => MonadState s (ErrorT e m) | |
MonadState s m => MonadState s (ExceptT e m) | Since: mtl-2.2 |
MonadState s m => MonadState s (IdentityT m) | |
MonadState s m => MonadState s (ReaderT r m) | |
Monad m => MonadState s (StateT s m) | |
Monad m => MonadState s (StateT s m) | |
(Monoid w, MonadState s m) => MonadState s (WriterT w m) | |
(Monoid w, MonadState s m) => MonadState s (WriterT w m) | |
MonadState s m => MonadState s (ContT r m) | |
(Monad m, Monoid w) => MonadState s (RWST r w s m) | |
(Monad m, Monoid w) => MonadState s (RWST r w s m) | |
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.
Retrieves the monad environment.
:: (r -> r) | The function to modify the environment. |
-> m a |
|
-> m a |
Executes a computation in a modified environment.
:: (r -> a) | The selector function to apply to the environment. |
-> m a |
Retrieves a function of the current environment.
Instances
MonadReader Window Query Source # | |
MonadReader XConf X Source # | |
MonadReader r m => MonadReader r (ListT m) | |
MonadReader r m => MonadReader r (MaybeT m) | |
(Error e, MonadReader r m) => MonadReader r (ErrorT e m) | |
MonadReader r m => MonadReader r (ExceptT e m) | Since: mtl-2.2 |
MonadReader r m => MonadReader r (IdentityT m) | |
Monad m => MonadReader r (ReaderT r m) | |
MonadReader r m => MonadReader r (StateT s m) | |
MonadReader r m => MonadReader r (StateT s m) | |
(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) | |
(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) | |
MonadReader r ((->) r) | |
MonadReader r' m => MonadReader r' (ContT r m) | |
(Monad m, Monoid w) => MonadReader r (RWST r w s m) | |
(Monad m, Monoid w) => MonadReader r (RWST r w s m) | |
:: 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:
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
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
, we would have ended up with this error:liftIO
• 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
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3