Copyright | (c) Ivan A. Malison |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Ivan A. Malison |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
System.Taffybar.Information.SafeX11
Contents
Description
Synopsis
- module Graphics.X11.Xlib
- 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
- type XErrorHandler = Display -> XErrorEventPtr -> IO ()
- type CXErrorHandler = Display -> XErrorEventPtr -> IO CInt
- type XErrorEventPtr = Ptr ()
- data WMHints = WMHints {}
- data ClassHint = ClassHint {}
- 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
- newtype FontSet = FontSet (Ptr FontSet)
- data TextProperty = TextProperty {}
- data WindowAttributes = WindowAttributes {}
- 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
- 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
- | SelectionClear {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_selection :: !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 { }
- | FocusChangeEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_mode :: !NotifyMode
- ev_detail :: !NotifyDetail
- | 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]
- | RRScreenChangeNotifyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_root :: !Window
- ev_timestamp :: !Time
- ev_config_timestamp :: !Time
- ev_size_index :: !SizeID
- ev_subpixel_order :: !SubpixelOrder
- ev_rotation :: !Rotation
- ev_width :: !CInt
- ev_height :: !CInt
- ev_mwidth :: !CInt
- ev_mheight :: !CInt
- | RRNotifyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_subtype :: !CInt
- | RRCrtcChangeNotifyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_subtype :: !CInt
- ev_crtc :: !RRCrtc
- ev_rr_mode :: !RRMode
- ev_rotation :: !Rotation
- ev_x :: !CInt
- ev_y :: !CInt
- ev_rr_width :: !CUInt
- ev_rr_height :: !CUInt
- | RROutputChangeNotifyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_subtype :: !CInt
- ev_output :: !RROutput
- ev_crtc :: !RRCrtc
- ev_rr_mode :: !RRMode
- ev_rotation :: !Rotation
- ev_connection :: !Connection
- ev_subpixel_order :: !SubpixelOrder
- | RROutputPropertyNotifyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_subtype :: !CInt
- ev_output :: !RROutput
- ev_property :: !Atom
- ev_timestamp :: !Time
- ev_rr_state :: !CInt
- | ScreenSaverNotifyEvent {
- ev_event_type :: !EventType
- ev_serial :: !CULong
- ev_send_event :: !Bool
- ev_event_display :: Display
- ev_window :: !Window
- ev_root :: !Window
- ev_ss_state :: !XScreenSaverState
- ev_ss_kind :: !XScreenSaverKind
- ev_forced :: !Bool
- ev_time :: !Time
- = AnyEvent {
- xFree :: Ptr a -> IO CInt
- xFreeModifiermap :: Ptr () -> IO (Ptr CInt)
- xGetModifierMapping :: Display -> IO (Ptr ())
- xGetCommand :: Display -> Window -> Ptr (Ptr CWString) -> Ptr CInt -> IO Status
- mapRaised :: Display -> Window -> IO CInt
- _xSetErrorHandler :: FunPtr CXErrorHandler -> IO (FunPtr CXErrorHandler)
- getXErrorHandler :: FunPtr CXErrorHandler -> CXErrorHandler
- mkXErrorHandler :: CXErrorHandler -> IO (FunPtr CXErrorHandler)
- xConvertSelection :: Display -> Atom -> Atom -> Atom -> Window -> Time -> IO ()
- xGetSelectionOwner :: Display -> Atom -> IO Window
- xSetSelectionOwner :: Display -> Atom -> Window -> Time -> IO ()
- isPrivateKeypadKey :: KeySym -> Bool
- isPFKey :: KeySym -> Bool
- isModifierKey :: KeySym -> Bool
- isMiscFunctionKey :: KeySym -> Bool
- isKeypadKey :: KeySym -> Bool
- isFunctionKey :: KeySym -> Bool
- isCursorKey :: KeySym -> Bool
- xSetWMHints :: Display -> Window -> Ptr WMHints -> IO Status
- xAllocWMHints :: IO (Ptr WMHints)
- xSetClassHint :: Display -> Window -> Ptr ClassHint -> IO ()
- xGetClassHint :: Display -> Window -> Ptr ClassHint -> IO Status
- xSetWMNormalHints :: Display -> Window -> Ptr SizeHints -> IO ()
- xAllocSizeHints :: IO (Ptr SizeHints)
- xGetWMNormalHints :: Display -> Window -> Ptr SizeHints -> Ptr CLong -> IO Status
- xUnmapWindow :: Display -> Window -> IO CInt
- xGetWindowProperty :: Display -> Window -> Atom -> CLong -> CLong -> Bool -> Atom -> Ptr Atom -> Ptr CInt -> Ptr CULong -> Ptr CULong -> Ptr (Ptr CUChar) -> IO Status
- xDeleteProperty :: Display -> Window -> Atom -> IO Status
- xChangeProperty :: Display -> Window -> Atom -> Atom -> CInt -> CInt -> Ptr CUChar -> CInt -> IO Status
- xRefreshKeyboardMapping :: Ptr () -> IO CInt
- xSetErrorHandler :: IO ()
- xGetWMProtocols :: Display -> Window -> Ptr (Ptr Atom) -> Ptr CInt -> IO Status
- xGetTransientForHint :: Display -> Window -> Ptr Window -> IO Status
- xFetchName :: Display -> Window -> Ptr CString -> IO Status
- xwcTextEscapement :: FontSet -> CWString -> CInt -> IO Int32
- xwcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO ()
- xwcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO ()
- xwcTextExtents :: FontSet -> CWString -> CInt -> Ptr Rectangle -> Ptr Rectangle -> IO CInt
- freeFontSet :: Display -> FontSet -> IO ()
- freeStringList :: Ptr CString -> IO ()
- xCreateFontSet :: Display -> CString -> Ptr (Ptr CString) -> Ptr CInt -> Ptr CString -> IO (Ptr FontSet)
- wcFreeStringList :: Ptr CWString -> IO ()
- xwcTextPropertyToTextList :: Display -> Ptr TextProperty -> Ptr (Ptr CWString) -> Ptr CInt -> IO CInt
- xGetTextProperty :: Display -> Window -> Ptr TextProperty -> Atom -> IO Status
- changeWindowAttributes :: Display -> Window -> AttributeMask -> Ptr SetWindowAttributes -> IO ()
- xGetWindowAttributes :: Display -> Window -> Ptr WindowAttributes -> IO Status
- xQueryTree :: Display -> Window -> Ptr Window -> Ptr Window -> Ptr (Ptr Window) -> Ptr CInt -> IO Status
- killClient :: Display -> Window -> IO CInt
- xConfigureWindow :: Display -> Window -> CULong -> Ptr WindowChanges -> IO CInt
- eventTable :: [(EventType, String)]
- eventName :: Event -> String
- getEvent :: XEventPtr -> IO Event
- none :: XID
- anyButton :: Button
- anyKey :: KeyCode
- currentTime :: Time
- configureWindow :: Display -> Window -> CULong -> WindowChanges -> IO ()
- queryTree :: Display -> Window -> IO (Window, Window, [Window])
- waIsUnmapped :: CInt
- waIsUnviewable :: CInt
- waIsViewable :: CInt
- getWindowAttributes :: Display -> Window -> IO WindowAttributes
- withServer :: Display -> IO () -> IO ()
- getTextProperty :: Display -> Window -> Atom -> IO TextProperty
- wcTextPropertyToTextList :: Display -> TextProperty -> IO [String]
- createFontSet :: Display -> String -> IO ([String], String, FontSet)
- wcTextExtents :: FontSet -> String -> (Rectangle, Rectangle)
- wcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO ()
- wcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO ()
- wcTextEscapement :: FontSet -> String -> Int32
- fetchName :: Display -> Window -> IO (Maybe String)
- getTransientForHint :: Display -> Window -> IO (Maybe Window)
- getWMProtocols :: Display -> Window -> IO [Atom]
- setEventType :: XEventPtr -> EventType -> IO ()
- setSelectionNotify :: XEventPtr -> Window -> Atom -> Atom -> Atom -> Time -> IO ()
- setClientMessageEvent :: XEventPtr -> Window -> Atom -> CInt -> Atom -> Time -> IO ()
- setClientMessageEvent' :: XEventPtr -> Window -> Atom -> CInt -> [CInt] -> IO ()
- setConfigureEvent :: XEventPtr -> Window -> Window -> CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> IO ()
- setKeyEvent :: XEventPtr -> Window -> Window -> Window -> KeyMask -> KeyCode -> Bool -> IO ()
- anyPropertyType :: Atom
- 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 :: CInt
- propModePrepend :: CInt
- propModeAppend :: CInt
- deleteProperty :: Display -> Window -> Atom -> IO ()
- unmapWindow :: Display -> Window -> IO ()
- pMinSizeBit :: Int
- pMaxSizeBit :: Int
- pResizeIncBit :: Int
- pAspectBit :: Int
- pBaseSizeBit :: Int
- pWinGravityBit :: Int
- getWMNormalHints :: Display -> Window -> IO SizeHints
- setWMNormalHints :: Display -> Window -> SizeHints -> IO ()
- getClassHint :: Display -> Window -> IO ClassHint
- setClassHint :: Display -> Window -> ClassHint -> IO ()
- withdrawnState :: Int
- normalState :: Int
- iconicState :: Int
- inputHintBit :: Int
- stateHintBit :: Int
- iconPixmapHintBit :: Int
- iconWindowHintBit :: Int
- iconPositionHintBit :: Int
- iconMaskHintBit :: Int
- windowGroupHintBit :: Int
- urgencyHintBit :: Int
- allHintsBitmask :: CLong
- setWMHints :: Display -> Window -> WMHints -> IO Status
- setErrorHandler :: XErrorHandler -> IO ()
- getErrorEvent :: XErrorEventPtr -> IO ErrorEvent
- getCommand :: Display -> Window -> IO [String]
- getModifierMapping :: Display -> IO [(Modifier, [KeyCode])]
- getWMHints :: Display -> Window -> IO WMHints
- getWindowProperty8 :: Display -> Atom -> Window -> IO (Maybe [CChar])
- getWindowProperty16 :: Display -> Atom -> Window -> IO (Maybe [CShort])
- getWindowProperty32 :: Display -> Atom -> Window -> IO (Maybe [CLong])
- postX11RequestSyncDef :: a -> IO a -> IO a
- rawGetWindowPropertyBytes :: Storable a => Int -> Display -> Atom -> Window -> IO (Maybe (ForeignPtr a, Int))
- safeGetGeometry :: Display -> Drawable -> IO (Window, Position, Position, Dimension, Dimension, Dimension, CInt)
Documentation
module Graphics.X11.Xlib
data ErrorEvent #
Constructors
ErrorEvent | |
Fields
|
Instances
Show ErrorEvent Source # | |
Defined in System.Taffybar.Information.SafeX11 Methods showsPrec :: Int -> ErrorEvent -> ShowS # show :: ErrorEvent -> String # showList :: [ErrorEvent] -> ShowS # |
type XErrorHandler = Display -> XErrorEventPtr -> IO () #
type CXErrorHandler = Display -> XErrorEventPtr -> IO CInt #
type XErrorEventPtr = Ptr () #
Constructors
WMHints | |
Fields
|
Instances
Constructors
SizeHints | |
Fields
|
Instances
Storable SizeHints | |
Defined in Graphics.X11.Xlib.Extras |
data TextProperty #
Constructors
TextProperty | |
Instances
Storable TextProperty | |
Defined in Graphics.X11.Xlib.Extras Methods sizeOf :: TextProperty -> Int # alignment :: TextProperty -> Int # peekElemOff :: Ptr TextProperty -> Int -> IO TextProperty # pokeElemOff :: Ptr TextProperty -> Int -> TextProperty -> IO () # peekByteOff :: Ptr b -> Int -> IO TextProperty # pokeByteOff :: Ptr b -> Int -> TextProperty -> IO () # peek :: Ptr TextProperty -> IO TextProperty # poke :: Ptr TextProperty -> TextProperty -> IO () # |
data WindowAttributes #
Constructors
WindowAttributes | |
Fields
|
Instances
Storable WindowAttributes | |
Defined in Graphics.X11.Xlib.Extras Methods sizeOf :: WindowAttributes -> Int # alignment :: WindowAttributes -> Int # peekElemOff :: Ptr WindowAttributes -> Int -> IO WindowAttributes # pokeElemOff :: Ptr WindowAttributes -> Int -> WindowAttributes -> IO () # peekByteOff :: Ptr b -> Int -> IO WindowAttributes # pokeByteOff :: Ptr b -> Int -> WindowAttributes -> IO () # peek :: Ptr WindowAttributes -> IO WindowAttributes # poke :: Ptr WindowAttributes -> WindowAttributes -> IO () # |
data WindowChanges #
Constructors
WindowChanges | |
Fields
|
Instances
Storable WindowChanges | |
Defined in Graphics.X11.Xlib.Extras Methods sizeOf :: WindowChanges -> Int # alignment :: WindowChanges -> Int # peekElemOff :: Ptr WindowChanges -> Int -> IO WindowChanges # pokeElemOff :: Ptr WindowChanges -> Int -> WindowChanges -> IO () # peekByteOff :: Ptr b -> Int -> IO WindowChanges # pokeByteOff :: Ptr b -> Int -> WindowChanges -> IO () # peek :: Ptr WindowChanges -> IO WindowChanges # poke :: Ptr WindowChanges -> WindowChanges -> IO () # |
Constructors
xGetModifierMapping :: Display -> IO (Ptr ()) #
mkXErrorHandler :: CXErrorHandler -> IO (FunPtr CXErrorHandler) #
isPrivateKeypadKey :: KeySym -> Bool #
isModifierKey :: KeySym -> Bool #
isMiscFunctionKey :: KeySym -> Bool #
isKeypadKey :: KeySym -> Bool #
isFunctionKey :: KeySym -> Bool #
isCursorKey :: KeySym -> Bool #
xAllocWMHints :: IO (Ptr WMHints) #
xAllocSizeHints :: IO (Ptr SizeHints) #
xGetWindowProperty :: Display -> Window -> Atom -> CLong -> CLong -> Bool -> Atom -> Ptr Atom -> Ptr CInt -> Ptr CULong -> Ptr CULong -> Ptr (Ptr CUChar) -> IO Status #
xChangeProperty :: Display -> Window -> Atom -> Atom -> CInt -> CInt -> Ptr CUChar -> CInt -> IO Status #
xRefreshKeyboardMapping :: Ptr () -> IO CInt #
xSetErrorHandler :: IO () #
xwcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO () #
xwcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO () #
freeFontSet :: Display -> FontSet -> IO () #
freeStringList :: Ptr CString -> IO () #
xCreateFontSet :: Display -> CString -> Ptr (Ptr CString) -> Ptr CInt -> Ptr CString -> IO (Ptr FontSet) #
wcFreeStringList :: Ptr CWString -> IO () #
xwcTextPropertyToTextList :: Display -> Ptr TextProperty -> Ptr (Ptr CWString) -> Ptr CInt -> IO CInt #
xGetTextProperty :: Display -> Window -> Ptr TextProperty -> Atom -> IO Status #
changeWindowAttributes :: Display -> Window -> AttributeMask -> Ptr SetWindowAttributes -> IO () #
interface to the X11 library function XChangeWindowAttributes()
.
xGetWindowAttributes :: Display -> Window -> Ptr WindowAttributes -> IO Status #
xQueryTree :: Display -> Window -> Ptr Window -> Ptr Window -> Ptr (Ptr Window) -> Ptr CInt -> IO Status #
xConfigureWindow :: Display -> Window -> CULong -> Ptr WindowChanges -> IO CInt #
eventTable :: [(EventType, String)] #
currentTime :: Time #
configureWindow :: Display -> Window -> CULong -> WindowChanges -> IO () #
waIsUnmapped :: CInt #
waIsUnviewable :: CInt #
waIsViewable :: CInt #
getWindowAttributes :: Display -> Window -> IO WindowAttributes #
withServer :: Display -> IO () -> IO () #
Run an action with the server
getTextProperty :: Display -> Window -> Atom -> IO TextProperty #
wcTextPropertyToTextList :: Display -> TextProperty -> IO [String] #
wcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO () #
wcTextEscapement :: FontSet -> String -> Int32 #
getWMProtocols :: Display -> Window -> IO [Atom] #
The XGetWMProtocols function returns the list of atoms stored in the WM_PROTOCOLS property on the specified window. These atoms describe window manager protocols in which the owner of this window is willing to participate. If the property exists, is of type ATOM, is of format 32, and the atom WM_PROTOCOLS can be interned, XGetWMProtocols sets the protocols_return argument to a list of atoms, sets the count_return argument to the number of elements in the list, and returns a nonzero status. Otherwise, it sets neither of the return arguments and returns a zero status. To release the list of atoms, use XFree.
setEventType :: XEventPtr -> EventType -> IO () #
setConfigureEvent :: XEventPtr -> Window -> Window -> CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> IO () #
anyPropertyType :: Atom #
propModeReplace :: CInt #
propModePrepend :: CInt #
propModeAppend :: CInt #
unmapWindow :: Display -> Window -> IO () #
pMinSizeBit :: Int #
pMaxSizeBit :: Int #
pResizeIncBit :: Int #
pAspectBit :: Int #
pBaseSizeBit :: Int #
pWinGravityBit :: Int #
setClassHint :: Display -> Window -> ClassHint -> IO () #
Set the WM_CLASS
property for the given window.
withdrawnState :: Int #
normalState :: Int #
iconicState :: Int #
inputHintBit :: Int #
stateHintBit :: Int #
iconMaskHintBit :: Int #
urgencyHintBit :: Int #
setErrorHandler :: XErrorHandler -> IO () #
A binding to XSetErrorHandler. NOTE: This is pretty experimental because of safe vs. unsafe calls. I changed sync to a safe call, but there *might* be other calls that cause a problem
getErrorEvent :: XErrorEventPtr -> IO ErrorEvent #
Retrieves error event data from a pointer to an XErrorEvent and puts it into an ErrorEvent.
postX11RequestSyncDef :: a -> IO a -> IO a Source #
rawGetWindowPropertyBytes :: Storable a => Int -> Display -> Atom -> Window -> IO (Maybe (ForeignPtr a, Int)) Source #
safeGetGeometry :: Display -> Drawable -> IO (Window, Position, Position, Dimension, Dimension, Dimension, CInt) Source #
Orphan instances
Show ErrorEvent Source # | |
Methods showsPrec :: Int -> ErrorEvent -> ShowS # show :: ErrorEvent -> String # showList :: [ErrorEvent] -> ShowS # |