taffybar-2.1.1: A desktop bar similar to xmobar, but with more GUI

Copyright(c) Ivan A. Malison
LicenseBSD3-style (see LICENSE)
MaintainerIvan A. Malison
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell2010

System.Taffybar.Information.SafeX11

Contents

Description

 

Documentation

anyButton :: Button #

anyKey :: KeyCode #

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 () #

createFontSet :: Display -> String -> IO ([String], String, FontSet) #

currentTime :: Time #

deleteProperty :: Display -> Window -> Atom -> IO () #

eventTable :: [(EventType, String)] #

fetchName :: Display -> Window -> IO (Maybe String) #

freeFontSet :: Display -> FontSet -> IO () #

getClassHint :: Display -> Window -> IO ClassHint #

getCommand :: Display -> Window -> IO [String] #

getEvent :: XEventPtr -> IO Event #

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 #

isCursorKey :: KeySym -> Bool #

isFunctionKey :: KeySym -> Bool #

isKeypadKey :: KeySym -> Bool #

isMiscFunctionKey :: KeySym -> Bool #

isModifierKey :: KeySym -> Bool #

isPFKey :: KeySym -> Bool #

killClient :: Display -> Window -> IO CInt #

mapRaised :: Display -> Window -> IO CInt #

none :: XID #

queryTree :: Display -> Window -> IO (Window, Window, [Window]) #

setClientMessageEvent :: XEventPtr -> Window -> Atom -> CInt -> Atom -> Time -> IO () #

setConfigureEvent :: XEventPtr -> Window -> Window -> CInt -> CInt -> CInt -> CInt -> CInt -> Window -> Bool -> 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 #

unmapWindow :: Display -> Window -> IO () #

wcDrawImageString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO () #

wcDrawString :: Display -> Drawable -> FontSet -> GC -> Position -> Position -> String -> IO () #

wcTextExtents :: FontSet -> String -> (Rectangle, Rectangle) #

withServer :: Display -> IO () -> IO () #

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 () #

xDeleteProperty :: Display -> Window -> Atom -> IO Status #

xFetchName :: Display -> Window -> Ptr CString -> IO Status #

xGetClassHint :: Display -> Window -> Ptr ClassHint -> IO Status #

xGetCommand :: Display -> Window -> Ptr (Ptr CWString) -> Ptr CInt -> 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 #

xGetWMNormalHints :: Display -> Window -> Ptr SizeHints -> Ptr CLong -> IO Status #

xGetWMProtocols :: Display -> Window -> Ptr (Ptr Atom) -> Ptr CInt -> 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 #

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 () #

xwcTextExtents :: FontSet -> CWString -> CInt -> Ptr Rectangle -> Ptr Rectangle -> IO CInt #

xFree :: Ptr a -> IO CInt #

type CXErrorHandler = Display -> XErrorEventPtr -> IO CInt #

data ClassHint #

Constructors

ClassHint 

Fields

data Event #

Constructors

AnyEvent 

Fields

ConfigureRequestEvent 

Fields

ConfigureEvent 

Fields

MapRequestEvent 

Fields

KeyEvent 

Fields

ButtonEvent 

Fields

MotionEvent 

Fields

DestroyWindowEvent 

Fields

UnmapEvent 

Fields

MapNotifyEvent 

Fields

MappingNotifyEvent 

Fields

CrossingEvent 

Fields

SelectionRequest 

Fields

SelectionClear 

Fields

PropertyEvent 

Fields

ExposeEvent 

Fields

ClientMessageEvent 

Fields

RRScreenChangeNotifyEvent 

Fields

RRNotifyEvent 

Fields

RRCrtcChangeNotifyEvent 

Fields

RROutputChangeNotifyEvent 

Fields

RROutputPropertyNotifyEvent 

Fields

Instances
Show Event 
Instance details

Defined in Graphics.X11.Xlib.Extras

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Message Event 
Instance details

Defined in XMonad.Core

newtype FontSet #

Constructors

FontSet (Ptr FontSet) 
Instances
Eq FontSet 
Instance details

Defined in Graphics.X11.Xlib.Extras

Methods

(==) :: FontSet -> FontSet -> Bool #

(/=) :: FontSet -> FontSet -> Bool #

Ord FontSet 
Instance details

Defined in Graphics.X11.Xlib.Extras

Show FontSet 
Instance details

Defined in Graphics.X11.Xlib.Extras

data SizeHints #

Constructors

SizeHints 

Fields

data WMHints #

Constructors

WMHints 
Instances
Storable WMHints 
Instance details

Defined in Graphics.X11.Xlib.Extras

type XErrorEventPtr = Ptr () #

type XErrorHandler = Display -> XErrorEventPtr -> IO () #

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 #

safeXGetWMHints :: Display -> Window -> IO (Ptr WMHints) Source #

rawGetWindowPropertyBytes :: Storable a => Int -> Display -> Atom -> Window -> IO (Maybe (ForeignPtr a, Int)) Source #

rawGetWindowProperty :: Storable a => Int -> Display -> Atom -> Window -> IO (Maybe [a]) Source #

getWindowProperty8 :: Display -> Atom -> Window -> IO (Maybe [CChar]) Source #

getWindowProperty16 :: Display -> Atom -> Window -> IO (Maybe [CShort]) Source #

getWindowProperty32 :: Display -> Atom -> Window -> IO (Maybe [CLong]) 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 # 
Instance details