Stability | experimental |
---|
- data Event
- = AnyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- | ConfigureRequestEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_parent :: !Window
- ev_window :: !Window
- ev_x :: !CInt
- ev_y :: !CInt
- ev_width :: !CInt
- ev_height :: !CInt
- ev_border_width :: !CInt
- ev_above :: !Window
- ev_detail :: !NotifyDetail
- ev_value_mask :: !CULong
- | ConfigureEvent { }
- | MapRequestEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_parent :: !Window
- ev_window :: !Window
- | KeyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_root :: !Window
- ev_subwindow :: !Window
- ev_time :: !Time
- ev_x :: !CInt
- ev_y :: !CInt
- ev_x_root :: !CInt
- ev_y_root :: !CInt
- ev_state :: !KeyMask
- ev_keycode :: !KeyCode
- ev_same_screen :: !Bool
- | ButtonEvent { }
- | MotionEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_x :: !CInt
- ev_y :: !CInt
- ev_window :: !Window
- | DestroyWindowEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_event :: !Window
- ev_window :: !Window
- | UnmapEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_event :: !Window
- ev_window :: !Window
- ev_from_configure :: !Bool
- | MapNotifyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_event :: !Window
- ev_window :: !Window
- ev_override_redirect :: !Bool
- | MappingNotifyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_request :: !MappingRequest
- ev_first_keycode :: !KeyCode
- ev_count :: !CInt
- | CrossingEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_root :: !Window
- ev_subwindow :: !Window
- ev_time :: !Time
- ev_x :: !CInt
- ev_y :: !CInt
- ev_x_root :: !CInt
- ev_y_root :: !CInt
- ev_mode :: !NotifyMode
- ev_detail :: !NotifyDetail
- ev_same_screen :: !Bool
- ev_focus :: !Bool
- ev_state :: !Modifier
- | SelectionRequest {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_owner :: !Window
- ev_requestor :: !Window
- ev_selection :: !Atom
- ev_target :: !Atom
- ev_property :: !Atom
- ev_time :: !Time
- | PropertyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_atom :: !Atom
- ev_time :: !Time
- ev_propstate :: !CInt
- | ExposeEvent { }
- | ClientMessageEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_message_type :: !Atom
- ev_data :: ![CInt]
- = AnyEvent {
- eventTable :: [(EventType, String)]
- eventName :: Event -> String
- getEvent :: XEventPtr -> IO Event
- data WindowChanges = WindowChanges {
- wc_x :: CInt
- wc_y :: CInt
- wc_width :: CInt
- wc_height :: CInt
- wc_border_width :: CInt
- wc_sibling :: Window
- wc_stack_mode :: CInt
- none :: XID
- anyButton :: Button
- anyKey :: KeyCode
- currentTime :: Time
- xConfigureWindow :: Display -> Window -> CULong -> Ptr WindowChanges -> IO CInt
- killClient :: Display -> Window -> IO CInt
- configureWindow :: Display -> Window -> CULong -> WindowChanges -> IO ()
- xFree :: Ptr a -> IO CInt
- xQueryTree :: Display -> Window -> Ptr Window -> Ptr Window -> Ptr (Ptr Window) -> Ptr CInt -> IO Status
- queryTree :: Display -> Window -> IO (Window, Window, [Window])
- data WindowAttributes = WindowAttributes {
- wa_x :: CInt
- wa_y :: CInt
- wa_width :: CInt
- wa_height :: CInt
- wa_border_width :: CInt
- wa_map_state :: CInt
- wa_override_redirect :: Bool
- waIsUnmapped, waIsViewable, waIsUnviewable :: CInt
- xGetWindowAttributes :: Display -> Window -> Ptr WindowAttributes -> IO Status
- getWindowAttributes :: Display -> Window -> IO WindowAttributes
- changeWindowAttributes :: Display -> Window -> AttributeMask -> Ptr SetWindowAttributes -> IO ()
- withServer :: Display -> IO () -> IO ()
- data TextProperty = TextProperty {}
- xGetTextProperty :: Display -> Window -> Ptr TextProperty -> Atom -> IO Status
- getTextProperty :: Display -> Window -> Atom -> IO TextProperty
- xwcTextPropertyToTextList :: Display -> Ptr TextProperty -> Ptr (Ptr CWString) -> Ptr CInt -> IO CInt
- wcTextPropertyToTextList :: Display -> TextProperty -> IO [String]
- wcFreeStringList :: Ptr CWString -> IO ()
- newtype FontSet = FontSet (Ptr FontSet)
- xCreateFontSet :: Display -> CString -> Ptr (Ptr CString) -> Ptr CInt -> Ptr CString -> IO (Ptr FontSet)
- createFontSet :: Display -> String -> IO ([String], String, FontSet)
- freeStringList :: Ptr CString -> IO ()
- freeFontSet :: Display -> FontSet -> IO ()
- xwcTextExtents :: FontSet -> CWString -> CInt -> Ptr Rectangle -> Ptr Rectangle -> IO CInt
- wcTextExtents :: FontSet -> String -> (Rectangle, Rectangle)
- xwcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO ()
- wcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO ()
- xwcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO ()
- wcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO ()
- xwcTextEscapement :: FontSet -> CWString -> CInt -> IO Int32
- wcTextEscapement :: FontSet -> String -> Int32
- xFetchName :: Display -> Window -> Ptr CString -> IO Status
- fetchName :: Display -> Window -> IO (Maybe String)
- xGetTransientForHint :: Display -> Window -> Ptr Window -> IO Status
- getTransientForHint :: Display -> Window -> IO (Maybe Window)
- getWMProtocols :: Display -> Window -> IO [Atom]
- xGetWMProtocols :: Display -> Window -> Ptr (Ptr Atom) -> Ptr CInt -> IO Status
- setEventType :: XEventPtr -> EventType -> IO ()
- setSelectionNotify :: XEventPtr -> Window -> Atom -> Atom -> Atom -> Time -> IO ()
- setClientMessageEvent :: XEventPtr -> Window -> Atom -> CInt -> Atom -> Time -> IO ()
- setConfigureEvent :: XEventPtr -> Window -> Window -> CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> IO ()
- setKeyEvent :: XEventPtr -> Window -> Window -> Window -> KeyMask -> KeyCode -> Bool -> IO ()
- xSetErrorHandler :: IO ()
- refreshKeyboardMapping :: Event -> IO ()
- xRefreshKeyboardMapping :: Ptr () -> IO CInt
- anyPropertyType :: Atom
- xChangeProperty :: Display -> Window -> Atom -> Atom -> CInt -> CInt -> Ptr CUChar -> CInt -> IO Status
- xGetWindowProperty :: Display -> Window -> Atom -> CLong -> CLong -> Bool -> Atom -> Ptr Atom -> Ptr CInt -> Ptr CULong -> Ptr CULong -> Ptr (Ptr CUChar) -> IO Status
- rawGetWindowProperty :: Storable a => Int -> Display -> Atom -> Window -> IO (Maybe [a])
- getWindowProperty8 :: Display -> Atom -> Window -> IO (Maybe [CChar])
- getWindowProperty16 :: Display -> Atom -> Window -> IO (Maybe [CShort])
- getWindowProperty32 :: Display -> Atom -> Window -> IO (Maybe [CLong])
- changeProperty8 :: Display -> Window -> Atom -> Atom -> CInt -> [CChar] -> IO ()
- changeProperty16 :: Display -> Window -> Atom -> Atom -> CInt -> [CShort] -> IO ()
- changeProperty32 :: Display -> Window -> Atom -> Atom -> CInt -> [CLong] -> IO ()
- propModeReplace, propModeAppend, propModePrepend :: CInt
- xUnmapWindow :: Display -> Window -> IO CInt
- unmapWindow :: Display -> Window -> IO ()
- data SizeHints = SizeHints {
- sh_min_size :: Maybe (Dimension, Dimension)
- sh_max_size :: Maybe (Dimension, Dimension)
- sh_resize_inc :: Maybe (Dimension, Dimension)
- sh_aspect :: Maybe ((Dimension, Dimension), (Dimension, Dimension))
- sh_base_size :: Maybe (Dimension, Dimension)
- sh_win_gravity :: Maybe BitGravity
- pMinSizeBit, pWinGravityBit, pBaseSizeBit, pAspectBit, pResizeIncBit, pMaxSizeBit :: Int
- xGetWMNormalHints :: Display -> Window -> Ptr SizeHints -> Ptr CLong -> IO Status
- getWMNormalHints :: Display -> Window -> IO SizeHints
- data ClassHint = ClassHint {}
- getClassHint :: Display -> Window -> IO ClassHint
- xGetClassHint :: Display -> Window -> Ptr ClassHint -> IO Status
- withdrawnState, iconicState, normalState :: Int
- inputHintBit, urgencyHintBit, windowGroupHintBit, iconMaskHintBit, iconPositionHintBit, iconWindowHintBit, iconPixmapHintBit, stateHintBit :: Int
- allHintsBitmask :: CLong
- data WMHints = WMHints {}
- xGetWMHints :: Display -> Window -> IO (Ptr WMHints)
- getWMHints :: Display -> Window -> IO WMHints
- xAllocWMHints :: IO (Ptr WMHints)
- xSetWMHints :: Display -> Window -> Ptr WMHints -> IO Status
- setWMHints :: Display -> Window -> WMHints -> IO Status
- isCursorKey :: KeySym -> Bool
- isFunctionKey :: KeySym -> Bool
- isKeypadKey :: KeySym -> Bool
- isMiscFunctionKey :: KeySym -> Bool
- isModifierKey :: KeySym -> Bool
- isPFKey :: KeySym -> Bool
- isPrivateKeypadKey :: KeySym -> Bool
- xSetSelectionOwner :: Display -> Atom -> Window -> Time -> IO ()
- xGetSelectionOwner :: Display -> Atom -> IO Window
- xConvertSelection :: Display -> Atom -> Atom -> Atom -> Window -> Time -> IO ()
- type XErrorEventPtr = Ptr ()
- type CXErrorHandler = Display -> XErrorEventPtr -> IO CInt
- type XErrorHandler = Display -> XErrorEventPtr -> IO ()
- data ErrorEvent = ErrorEvent {
- ev_type :: !CInt
- ev_display :: Display
- ev_serialnum :: !CULong
- ev_error_code :: !CUChar
- ev_request_code :: !CUChar
- ev_minor_code :: !CUChar
- ev_resourceid :: !XID
- mkXErrorHandler :: CXErrorHandler -> IO (FunPtr CXErrorHandler)
- getXErrorHandler :: FunPtr CXErrorHandler -> CXErrorHandler
- _xSetErrorHandler :: FunPtr CXErrorHandler -> IO (FunPtr CXErrorHandler)
- setErrorHandler :: XErrorHandler -> IO ()
- getErrorEvent :: XErrorEventPtr -> IO ErrorEvent
- mapRaised :: Display -> Window -> IO CInt
- xGetCommand :: Display -> Window -> Ptr (Ptr CWString) -> Ptr CInt -> IO Status
- getCommand :: Display -> Window -> IO [String]
- xGetModifierMapping :: Display -> IO (Ptr ())
- xFreeModifiermap :: Ptr () -> IO (Ptr CInt)
- getModifierMapping :: Display -> IO [(Modifier, [KeyCode])]
Documentation
eventTable :: [(EventType, String)]Source
data WindowChanges Source
WindowChanges | |
|
xConfigureWindow :: Display -> Window -> CULong -> Ptr WindowChanges -> IO CIntSource
configureWindow :: Display -> Window -> CULong -> WindowChanges -> IO ()Source
xQueryTree :: Display -> Window -> Ptr Window -> Ptr Window -> Ptr (Ptr Window) -> Ptr CInt -> IO StatusSource
data WindowAttributes Source
WindowAttributes | |
|
xGetWindowAttributes :: Display -> Window -> Ptr WindowAttributes -> IO StatusSource
changeWindowAttributes :: Display -> Window -> AttributeMask -> Ptr SetWindowAttributes -> IO ()Source
interface to the X11 library function XChangeWindowAttributes()
.
xGetTextProperty :: Display -> Window -> Ptr TextProperty -> Atom -> IO StatusSource
getTextProperty :: Display -> Window -> Atom -> IO TextPropertySource
xwcTextPropertyToTextList :: Display -> Ptr TextProperty -> Ptr (Ptr CWString) -> Ptr CInt -> IO CIntSource
wcTextPropertyToTextList :: Display -> TextProperty -> IO [String]Source
xCreateFontSet :: Display -> CString -> Ptr (Ptr CString) -> Ptr CInt -> Ptr CString -> IO (Ptr FontSet)Source
xwcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO ()Source
wcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO ()Source
xwcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO ()Source
wcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO ()Source
wcTextEscapement :: FontSet -> String -> Int32Source
getWMProtocols :: Display -> Window -> IO [Atom]Source
The XGetWMProtocols function returns the list of atoms stored in the WM_PROTOCOLS property on the specified window. These atoms describe window manager protocols in which the owner of this window is willing to participate. If the property exists, is of type ATOM, is of format 32, and the atom WM_PROTOCOLS can be interned, XGetWMProtocols sets the protocols_return argument to a list of atoms, sets the count_return argument to the number of elements in the list, and returns a nonzero status. Otherwise, it sets neither of the return arguments and returns a zero status. To release the list of atoms, use XFree.
setConfigureEvent :: XEventPtr -> Window -> Window -> CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> IO ()Source
refreshKeyboardMapping :: Event -> IO ()Source
refreshKeyboardMapping. TODO Remove this binding when the fix has been commited to X11
xChangeProperty :: Display -> Window -> Atom -> Atom -> CInt -> CInt -> Ptr CUChar -> CInt -> IO StatusSource
xGetWindowProperty :: Display -> Window -> Atom -> CLong -> CLong -> Bool -> Atom -> Ptr Atom -> Ptr CInt -> Ptr CULong -> Ptr CULong -> Ptr (Ptr CUChar) -> IO StatusSource
SizeHints | |
|
inputHintBit, urgencyHintBit, windowGroupHintBit, iconMaskHintBit, iconPositionHintBit, iconWindowHintBit, iconPixmapHintBit, stateHintBit :: IntSource
WMHints | |
|
xAllocWMHints :: IO (Ptr WMHints)Source
isCursorKey :: KeySym -> BoolSource
isFunctionKey :: KeySym -> BoolSource
isKeypadKey :: KeySym -> BoolSource
isModifierKey :: KeySym -> BoolSource
type XErrorEventPtr = Ptr ()Source
type CXErrorHandler = Display -> XErrorEventPtr -> IO CIntSource
type XErrorHandler = Display -> XErrorEventPtr -> IO ()Source
data ErrorEvent Source
ErrorEvent | |
|
setErrorHandler :: XErrorHandler -> IO ()Source
A binding to XSetErrorHandler. NOTE: This is pretty experimental because of safe vs. unsafe calls. I changed sync to a safe call, but there *might* be other calls that cause a problem
getErrorEvent :: XErrorEventPtr -> IO ErrorEventSource
Retrieves error event data from a pointer to an XErrorEvent and puts it into an ErrorEvent.