Copyright | (c) Ivan A. Malison |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Ivan A. Malison |
Stability | unstable |
Portability | unportable |
Safe Haskell | None |
Language | Haskell2010 |
Documentation
anyPropertyType :: Atom #
changeProperty16 :: Display -> Window -> Atom -> Atom -> CInt -> [CShort] -> IO () #
changeProperty32 :: Display -> Window -> Atom -> Atom -> CInt -> [CLong] -> IO () #
changeProperty8 :: Display -> Window -> Atom -> Atom -> CInt -> [CChar] -> IO () #
changeWindowAttributes :: Display -> Window -> AttributeMask -> Ptr SetWindowAttributes -> IO () #
configureWindow :: Display -> Window -> CULong -> WindowChanges -> IO () #
currentTime :: Time #
deleteProperty :: Display -> Window -> Atom -> IO () #
eventTable :: [(EventType, String)] #
freeFontSet :: Display -> FontSet -> IO () #
freeStringList :: Ptr CString -> IO () #
getClassHint :: Display -> Window -> IO ClassHint #
getCommand :: Display -> Window -> IO [String] #
getErrorEvent :: XErrorEventPtr -> IO ErrorEvent #
getModifierMapping :: Display -> IO [(Modifier, [KeyCode])] #
getTextProperty :: Display -> Window -> Atom -> IO TextProperty #
getTransientForHint :: Display -> Window -> IO (Maybe Window) #
getWMNormalHints :: Display -> Window -> IO SizeHints #
getWMProtocols :: Display -> Window -> IO [Atom] #
getWindowAttributes :: Display -> Window -> IO WindowAttributes #
iconMaskHintBit :: Int #
iconicState :: Int #
inputHintBit :: Int #
isCursorKey :: KeySym -> Bool #
isFunctionKey :: KeySym -> Bool #
isKeypadKey :: KeySym -> Bool #
isMiscFunctionKey :: KeySym -> Bool #
isModifierKey :: KeySym -> Bool #
isPrivateKeypadKey :: KeySym -> Bool #
killClient :: Display -> Window -> IO CInt #
mkXErrorHandler :: CXErrorHandler -> IO (FunPtr CXErrorHandler) #
normalState :: Int #
pAspectBit :: Int #
pBaseSizeBit :: Int #
pMaxSizeBit :: Int #
pMinSizeBit :: Int #
pResizeIncBit :: Int #
pWinGravityBit :: Int #
propModeAppend :: CInt #
propModePrepend :: CInt #
propModeReplace :: CInt #
setClientMessageEvent :: XEventPtr -> Window -> Atom -> CInt -> Atom -> Time -> IO () #
setConfigureEvent :: XEventPtr -> Window -> Window -> CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> IO () #
setErrorHandler :: XErrorHandler -> IO () #
setEventType :: XEventPtr -> EventType -> IO () #
setKeyEvent :: XEventPtr -> Window -> Window -> Window -> KeyMask -> KeyCode -> Bool -> IO () #
setSelectionNotify :: XEventPtr -> Window -> Atom -> Atom -> Atom -> Time -> IO () #
setWMHints :: Display -> Window -> WMHints -> IO Status #
stateHintBit :: Int #
unmapWindow :: Display -> Window -> IO () #
urgencyHintBit :: Int #
waIsUnmapped :: CInt #
waIsUnviewable :: CInt #
waIsViewable :: CInt #
wcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO () #
wcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO () #
wcFreeStringList :: Ptr CWString -> IO () #
wcTextEscapement :: FontSet -> String -> Int32 #
wcTextExtents :: FontSet -> String -> (Rectangle, Rectangle) #
wcTextPropertyToTextList :: Display -> TextProperty -> IO [String] #
withServer :: Display -> IO () -> IO () #
withdrawnState :: Int #
xAllocWMHints :: IO (Ptr WMHints) #
xChangeProperty :: Display -> Window -> Atom -> Atom -> CInt -> CInt -> Ptr CUChar -> CInt -> IO Status #
xConfigureWindow :: Display -> Window -> CULong -> Ptr WindowChanges -> IO CInt #
xConvertSelection :: Display -> Atom -> Atom -> Atom -> Window -> Time -> IO () #
xCreateFontSet :: Display -> CString -> Ptr (Ptr CString) -> Ptr CInt -> Ptr CString -> IO (Ptr FontSet) #
xDeleteProperty :: Display -> Window -> Atom -> IO Status #
xFetchName :: Display -> Window -> Ptr CString -> IO Status #
xGetClassHint :: Display -> Window -> Ptr ClassHint -> IO Status #
xGetModifierMapping :: Display -> IO (Ptr ()) #
xGetSelectionOwner :: Display -> Atom -> IO Window #
xGetTextProperty :: Display -> Window -> Ptr TextProperty -> Atom -> IO Status #
xGetTransientForHint :: Display -> Window -> Ptr Window -> IO Status #
xGetWindowAttributes :: Display -> Window -> Ptr WindowAttributes -> IO Status #
xGetWindowProperty :: Display -> Window -> Atom -> CLong -> CLong -> Bool -> Atom -> Ptr Atom -> Ptr CInt -> Ptr CULong -> Ptr CULong -> Ptr (Ptr CUChar) -> IO Status #
xQueryTree :: Display -> Window -> Ptr Window -> Ptr Window -> Ptr (Ptr Window) -> Ptr CInt -> IO Status #
xRefreshKeyboardMapping :: Ptr () -> IO CInt #
xSetErrorHandler :: IO () #
xSetSelectionOwner :: Display -> Atom -> Window -> Time -> IO () #
xSetWMHints :: Display -> Window -> Ptr WMHints -> IO Status #
xUnmapWindow :: Display -> Window -> IO CInt #
xwcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO () #
xwcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> CWString -> CInt -> IO () #
xwcTextPropertyToTextList :: Display -> Ptr TextProperty -> Ptr (Ptr CWString) -> Ptr CInt -> IO CInt #
type CXErrorHandler = Display -> XErrorEventPtr -> IO CInt #
data ErrorEvent #
ErrorEvent | |
|
Instances
Show ErrorEvent # | |
Defined in System.Taffybar.Information.SafeX11 showsPrec :: Int -> ErrorEvent -> ShowS # show :: ErrorEvent -> String # showList :: [ErrorEvent] -> ShowS # |
SizeHints | |
|
Instances
Storable SizeHints | |
Defined in Graphics.X11.Xlib.Extras |
data TextProperty #
Instances
Storable TextProperty | |
Defined in Graphics.X11.Xlib.Extras 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 () # |
WMHints | |
|
data WindowAttributes #
WindowAttributes | |
|
Instances
Storable WindowAttributes | |
Defined in Graphics.X11.Xlib.Extras 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 #
WindowChanges | |
|
Instances
Storable WindowChanges | |
Defined in Graphics.X11.Xlib.Extras 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 () # |
type XErrorEventPtr = Ptr () #
type XErrorHandler = Display -> XErrorEventPtr -> IO () #
IORequest | |
|
data SafeX11Exception Source #
Instances
Eq SafeX11Exception Source # | |
Defined in System.Taffybar.Information.SafeX11 (==) :: SafeX11Exception -> SafeX11Exception -> Bool # (/=) :: SafeX11Exception -> SafeX11Exception -> Bool # | |
Show SafeX11Exception Source # | |
Defined in System.Taffybar.Information.SafeX11 showsPrec :: Int -> SafeX11Exception -> ShowS # show :: SafeX11Exception -> String # showList :: [SafeX11Exception] -> ShowS # | |
Exception SafeX11Exception Source # | |
xGetGeometry :: Display -> Drawable -> Ptr Window -> Ptr Position -> Ptr Position -> Ptr Dimension -> Ptr Dimension -> Ptr Dimension -> Ptr CInt -> IO Status Source #
safeXGetWindowProperty :: Display -> Window -> Atom -> CLong -> CLong -> Bool -> Atom -> Ptr Atom -> Ptr CInt -> Ptr CULong -> Ptr CULong -> Ptr (Ptr CUChar) -> IO Status Source #
rawGetWindowPropertyBytes :: Storable a => Int -> Display -> Atom -> Window -> IO (Maybe (ForeignPtr a, Int)) Source #
withErrorHandler :: XErrorHandler -> IO a -> IO a Source #
startHandlingX11Requests :: IO () Source #
handleX11Requests :: IO () Source #
postX11RequestSync :: IO a -> IO (Either SafeX11Exception a) Source #
postX11RequestSyncDef :: a -> IO a -> IO a Source #
getWMHints :: Display -> Window -> IO WMHints Source #
safeGetGeometry :: Display -> Drawable -> IO (Window, Position, Position, Dimension, Dimension, Dimension, CInt) Source #
outParameters7 :: (Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g) => (IO r -> IO ()) -> (Ptr a -> Ptr b -> Ptr c -> Ptr d -> Ptr e -> Ptr f -> Ptr g -> IO r) -> IO (a, b, c, d, e, f, g) Source #
Orphan instances
Show ErrorEvent Source # | |
showsPrec :: Int -> ErrorEvent -> ShowS # show :: ErrorEvent -> String # showList :: [ErrorEvent] -> ShowS # |