{-# LINE 1 "Graphics/X11/Xlib/Event.hsc" #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Graphics.X11.Xlib.Event(
QueuedMode,
queuedAlready,
queuedAfterFlush,
queuedAfterReading,
XEvent(..),
XEventPtr,
allocaXEvent,
get_EventType,
get_Window,
XKeyEvent,
XKeyEventPtr,
asKeyEvent,
XButtonEvent,
get_KeyEvent,
get_ButtonEvent,
get_MotionEvent,
XMotionEvent,
XExposeEvent,
get_ExposeEvent,
XMappingEvent,
XConfigureEvent,
get_ConfigureEvent,
waitForEvent,
gettimeofday_in_milliseconds,
flush,
sync,
pending,
eventsQueued,
nextEvent,
allowEvents,
selectInput,
sendEvent,
windowEvent,
checkWindowEvent,
maskEvent,
checkMaskEvent,
checkTypedEvent,
checkTypedWindowEvent,
putBackEvent,
peekEvent,
refreshKeyboardMapping,
) where
import Graphics.X11.Types
import Graphics.X11.Xlib.Types
import Graphics.X11.Xlib.Display( connectionNumber )
import Foreign
import Foreign.C.Types
{-# LINE 70 "Graphics/X11/Xlib/Event.hsc" #-}
import Data.Data
{-# LINE 72 "Graphics/X11/Xlib/Event.hsc" #-}
{-# CFILES cbits/fdset.c #-}
type QueuedMode = CInt
queuedAlready :: QueuedMode
queuedAlready = 0
queuedAfterFlush :: QueuedMode
queuedAfterFlush = 2
queuedAfterReading :: QueuedMode
queuedAfterReading = 1
{-# LINE 87 "Graphics/X11/Xlib/Event.hsc" #-}
newtype XEvent = XEvent XEventPtr
{-# LINE 101 "Graphics/X11/Xlib/Event.hsc" #-}
deriving (Eq, Ord, Show, Typeable, Data)
{-# LINE 105 "Graphics/X11/Xlib/Event.hsc" #-}
type XEventPtr = Ptr XEvent
allocaXEvent :: (XEventPtr -> IO a) -> IO a
allocaXEvent = allocaBytes (192)
{-# LINE 109 "Graphics/X11/Xlib/Event.hsc" #-}
get_EventType :: XEventPtr -> IO EventType
get_EventType = (\hsc_ptr -> peekByteOff hsc_ptr 0)
{-# LINE 112 "Graphics/X11/Xlib/Event.hsc" #-}
get_Window :: XEventPtr -> IO Window
get_Window = (\hsc_ptr -> peekByteOff hsc_ptr 32)
{-# LINE 115 "Graphics/X11/Xlib/Event.hsc" #-}
type XKeyEvent =
( Window
, Window
, Time
, CInt
, CInt
, CInt
, CInt
, Modifier
, KeyCode
, Bool
)
peekXKeyEvent :: Ptr XKeyEvent -> IO XKeyEvent
peekXKeyEvent p = do
root <- (\hsc_ptr -> peekByteOff hsc_ptr 40) p
{-# LINE 138 "Graphics/X11/Xlib/Event.hsc" #-}
subwindow <- (\hsc_ptr -> peekByteOff hsc_ptr 48) p
{-# LINE 139 "Graphics/X11/Xlib/Event.hsc" #-}
time <- (\hsc_ptr -> peekByteOff hsc_ptr 56) p
{-# LINE 140 "Graphics/X11/Xlib/Event.hsc" #-}
x <- (\hsc_ptr -> peekByteOff hsc_ptr 64) p
{-# LINE 141 "Graphics/X11/Xlib/Event.hsc" #-}
y <- (\hsc_ptr -> peekByteOff hsc_ptr 68) p
{-# LINE 142 "Graphics/X11/Xlib/Event.hsc" #-}
x_root <- (\hsc_ptr -> peekByteOff hsc_ptr 72) p
{-# LINE 143 "Graphics/X11/Xlib/Event.hsc" #-}
y_root <- (\hsc_ptr -> peekByteOff hsc_ptr 76) p
{-# LINE 144 "Graphics/X11/Xlib/Event.hsc" #-}
state <- ((\hsc_ptr -> peekByteOff hsc_ptr 80) p) :: IO CUInt
{-# LINE 145 "Graphics/X11/Xlib/Event.hsc" #-}
keycode <- ((\hsc_ptr -> peekByteOff hsc_ptr 84) p) :: IO CUInt
{-# LINE 146 "Graphics/X11/Xlib/Event.hsc" #-}
same_screen <- (\hsc_ptr -> peekByteOff hsc_ptr 88) p
{-# LINE 147 "Graphics/X11/Xlib/Event.hsc" #-}
return (root, subwindow, time, x, y, x_root, y_root,
fromIntegral state, fromIntegral keycode, same_screen)
get_KeyEvent :: XEventPtr -> IO XKeyEvent
get_KeyEvent p = peekXKeyEvent (castPtr p)
type XKeyEventPtr = Ptr XKeyEvent
asKeyEvent :: XEventPtr -> XKeyEventPtr
asKeyEvent = castPtr
type XButtonEvent =
( Window
, Window
, Time
, CInt
, CInt
, CInt
, CInt
, Modifier
, Button
, Bool
)
peekXButtonEvent :: Ptr XButtonEvent -> IO XButtonEvent
peekXButtonEvent p = do
root <- (\hsc_ptr -> peekByteOff hsc_ptr 40) p
{-# LINE 174 "Graphics/X11/Xlib/Event.hsc" #-}
subwindow <- (\hsc_ptr -> peekByteOff hsc_ptr 48) p
{-# LINE 175 "Graphics/X11/Xlib/Event.hsc" #-}
time <- (\hsc_ptr -> peekByteOff hsc_ptr 56) p
{-# LINE 176 "Graphics/X11/Xlib/Event.hsc" #-}
x <- (\hsc_ptr -> peekByteOff hsc_ptr 64) p
{-# LINE 177 "Graphics/X11/Xlib/Event.hsc" #-}
y <- (\hsc_ptr -> peekByteOff hsc_ptr 68) p
{-# LINE 178 "Graphics/X11/Xlib/Event.hsc" #-}
x_root <- (\hsc_ptr -> peekByteOff hsc_ptr 72) p
{-# LINE 179 "Graphics/X11/Xlib/Event.hsc" #-}
y_root <- (\hsc_ptr -> peekByteOff hsc_ptr 76) p
{-# LINE 180 "Graphics/X11/Xlib/Event.hsc" #-}
state <- (\hsc_ptr -> peekByteOff hsc_ptr 80) p
{-# LINE 181 "Graphics/X11/Xlib/Event.hsc" #-}
button <- (\hsc_ptr -> peekByteOff hsc_ptr 84) p
{-# LINE 182 "Graphics/X11/Xlib/Event.hsc" #-}
same_screen <- (\hsc_ptr -> peekByteOff hsc_ptr 88) p
{-# LINE 183 "Graphics/X11/Xlib/Event.hsc" #-}
return (root, subwindow, time, x, y, x_root, y_root,
state, button, same_screen)
get_ButtonEvent :: XEventPtr -> IO XButtonEvent
get_ButtonEvent p = peekXButtonEvent (castPtr p)
type XMotionEvent =
( Window
, Window
, Time
, CInt
, CInt
, CInt
, CInt
, Modifier
, NotifyMode
, Bool
)
peekXMotionEvent :: Ptr XMotionEvent -> IO XMotionEvent
peekXMotionEvent p = do
root <- (\hsc_ptr -> peekByteOff hsc_ptr 40) p
{-# LINE 205 "Graphics/X11/Xlib/Event.hsc" #-}
subwindow <- (\hsc_ptr -> peekByteOff hsc_ptr 48) p
{-# LINE 206 "Graphics/X11/Xlib/Event.hsc" #-}
time <- (\hsc_ptr -> peekByteOff hsc_ptr 56) p
{-# LINE 207 "Graphics/X11/Xlib/Event.hsc" #-}
x <- (\hsc_ptr -> peekByteOff hsc_ptr 64) p
{-# LINE 208 "Graphics/X11/Xlib/Event.hsc" #-}
y <- (\hsc_ptr -> peekByteOff hsc_ptr 68) p
{-# LINE 209 "Graphics/X11/Xlib/Event.hsc" #-}
x_root <- (\hsc_ptr -> peekByteOff hsc_ptr 72) p
{-# LINE 210 "Graphics/X11/Xlib/Event.hsc" #-}
y_root <- (\hsc_ptr -> peekByteOff hsc_ptr 76) p
{-# LINE 211 "Graphics/X11/Xlib/Event.hsc" #-}
state <- (\hsc_ptr -> peekByteOff hsc_ptr 80) p
{-# LINE 212 "Graphics/X11/Xlib/Event.hsc" #-}
is_hint <- (\hsc_ptr -> peekByteOff hsc_ptr 84) p
{-# LINE 213 "Graphics/X11/Xlib/Event.hsc" #-}
same_screen <- (\hsc_ptr -> peekByteOff hsc_ptr 88) p
{-# LINE 214 "Graphics/X11/Xlib/Event.hsc" #-}
return (root, subwindow, time, x, y, x_root, y_root,
state, is_hint, same_screen)
get_MotionEvent :: XEventPtr -> IO XMotionEvent
get_MotionEvent p = peekXMotionEvent (castPtr p)
type XExposeEvent =
( Position
, Position
, Dimension
, Dimension
, CInt
)
peekXExposeEvent :: Ptr XExposeEvent -> IO XExposeEvent
peekXExposeEvent p = do
x <- (\hsc_ptr -> peekByteOff hsc_ptr 40) p
{-# LINE 256 "Graphics/X11/Xlib/Event.hsc" #-}
y <- (\hsc_ptr -> peekByteOff hsc_ptr 44) p
{-# LINE 257 "Graphics/X11/Xlib/Event.hsc" #-}
width <- (\hsc_ptr -> peekByteOff hsc_ptr 48) p
{-# LINE 258 "Graphics/X11/Xlib/Event.hsc" #-}
height <- (\hsc_ptr -> peekByteOff hsc_ptr 52) p
{-# LINE 259 "Graphics/X11/Xlib/Event.hsc" #-}
count <- (\hsc_ptr -> peekByteOff hsc_ptr 56) p
{-# LINE 260 "Graphics/X11/Xlib/Event.hsc" #-}
return (x, y, width, height, count)
get_ExposeEvent :: XEventPtr -> IO XExposeEvent
get_ExposeEvent p = peekXExposeEvent (castPtr p)
type XMappingEvent =
( MappingRequest
, KeyCode
, CInt
)
withXMappingEvent :: XMappingEvent -> (Ptr XMappingEvent -> IO a) -> IO a
withXMappingEvent event_map f =
allocaBytes (56) $ \ event_map_ptr -> do
{-# LINE 317 "Graphics/X11/Xlib/Event.hsc" #-}
pokeXMappingEvent event_map_ptr event_map
f event_map_ptr
pokeXMappingEvent :: Ptr XMappingEvent -> XMappingEvent -> IO ()
pokeXMappingEvent p (request, first_keycode, count) = do
(\hsc_ptr -> pokeByteOff hsc_ptr 40) p request
{-# LINE 323 "Graphics/X11/Xlib/Event.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 44) p first_keycode
{-# LINE 324 "Graphics/X11/Xlib/Event.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 48) p count
{-# LINE 325 "Graphics/X11/Xlib/Event.hsc" #-}
type XConfigureEvent =
( Position
, Position
, Dimension
, Dimension
)
peekXConfigureEvent :: Ptr XConfigureEvent -> IO XConfigureEvent
peekXConfigureEvent p = do
x <- (\hsc_ptr -> peekByteOff hsc_ptr 48) p
{-# LINE 336 "Graphics/X11/Xlib/Event.hsc" #-}
y <- (\hsc_ptr -> peekByteOff hsc_ptr 52) p
{-# LINE 337 "Graphics/X11/Xlib/Event.hsc" #-}
width <- (\hsc_ptr -> peekByteOff hsc_ptr 56) p
{-# LINE 338 "Graphics/X11/Xlib/Event.hsc" #-}
height <- (\hsc_ptr -> peekByteOff hsc_ptr 60) p
{-# LINE 339 "Graphics/X11/Xlib/Event.hsc" #-}
return (x, y, width, height)
get_ConfigureEvent :: XEventPtr -> IO XConfigureEvent
get_ConfigureEvent p = peekXConfigureEvent (castPtr p)
waitForEvent :: Display -> Word32 -> IO Bool
waitForEvent display usecs =
with (TimeVal (usecs `div` 1000000) (usecs `mod` 1000000)) $ \ tv_ptr ->
allocaBytes (128) $ \ readfds ->
{-# LINE 403 "Graphics/X11/Xlib/Event.hsc" #-}
allocaBytes (128) $ \ nofds -> do
{-# LINE 404 "Graphics/X11/Xlib/Event.hsc" #-}
let fd = connectionNumber display
fdZero readfds
fdZero nofds
fdSet (fromIntegral fd) readfds
n <- select ((fromIntegral fd)+1) readfds nofds nofds tv_ptr
return (n == 0)
newtype FdSet = FdSet (Ptr FdSet)
{-# LINE 413 "Graphics/X11/Xlib/Event.hsc" #-}
deriving (Eq, Ord, Show, Typeable, Data)
{-# LINE 417 "Graphics/X11/Xlib/Event.hsc" #-}
foreign import ccall unsafe "HsXlib.h" fdZero :: Ptr FdSet -> IO ()
foreign import ccall unsafe "HsXlib.h" fdSet :: CInt -> Ptr FdSet -> IO ()
foreign import ccall unsafe "HsXlib.h" select ::
CInt -> Ptr FdSet -> Ptr FdSet -> Ptr FdSet -> Ptr TimeVal -> IO CInt
gettimeofday_in_milliseconds :: IO Integer
gettimeofday_in_milliseconds =
alloca $ \ tv_ptr -> do
_rc <- gettimeofday tv_ptr nullPtr
TimeVal sec usec <- peek tv_ptr
return (toInteger sec * 1000 + toInteger usec `div` 1000)
data TimeVal = TimeVal Word32 Word32
instance Storable TimeVal where
alignment _ = (4)
{-# LINE 436 "Graphics/X11/Xlib/Event.hsc" #-}
sizeOf _ = (16)
{-# LINE 437 "Graphics/X11/Xlib/Event.hsc" #-}
peek p = do
sec <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 439 "Graphics/X11/Xlib/Event.hsc" #-}
usec <- (\hsc_ptr -> peekByteOff hsc_ptr 8) p
{-# LINE 440 "Graphics/X11/Xlib/Event.hsc" #-}
return (TimeVal sec usec)
poke p (TimeVal sec usec) = do
(\hsc_ptr -> pokeByteOff hsc_ptr 0) p sec
{-# LINE 443 "Graphics/X11/Xlib/Event.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) p usec
{-# LINE 444 "Graphics/X11/Xlib/Event.hsc" #-}
newtype TimeZone = TimeZone (Ptr TimeZone)
{-# LINE 447 "Graphics/X11/Xlib/Event.hsc" #-}
deriving (Eq, Ord, Show, Typeable, Data)
{-# LINE 451 "Graphics/X11/Xlib/Event.hsc" #-}
foreign import ccall unsafe "HsXlib.h"
gettimeofday :: Ptr TimeVal -> Ptr TimeZone -> IO ()
foreign import ccall unsafe "HsXlib.h XFlush"
flush :: Display -> IO ()
foreign import ccall safe "HsXlib.h XSync"
sync :: Display -> Bool -> IO ()
foreign import ccall unsafe "HsXlib.h XPending"
pending :: Display -> IO CInt
foreign import ccall unsafe "HsXlib.h XEventsQueued"
eventsQueued :: Display -> QueuedMode -> IO CInt
foreign import ccall safe "HsXlib.h XNextEvent"
nextEvent :: Display -> XEventPtr -> IO ()
foreign import ccall unsafe "HsXlib.h XAllowEvents"
allowEvents :: Display -> AllowEvents -> Time -> IO ()
foreign import ccall unsafe "HsXlib.h XSelectInput"
selectInput :: Display -> Window -> EventMask -> IO ()
sendEvent :: Display -> Window -> Bool -> EventMask -> XEventPtr -> IO ()
sendEvent display w propagate event_mask event_send =
throwIfZero "sendEvent" $
xSendEvent display w propagate event_mask event_send
foreign import ccall unsafe "HsXlib.h XSendEvent"
xSendEvent :: Display -> Window -> Bool -> EventMask ->
XEventPtr -> IO Status
foreign import ccall unsafe "HsXlib.h XWindowEvent"
windowEvent :: Display -> Window -> EventMask -> XEventPtr -> IO ()
foreign import ccall unsafe "HsXlib.h XCheckWindowEvent"
checkWindowEvent :: Display -> Window -> EventMask ->
XEventPtr -> IO Bool
foreign import ccall unsafe "HsXlib.h XMaskEvent"
maskEvent :: Display -> EventMask -> XEventPtr -> IO ()
foreign import ccall unsafe "HsXlib.h XCheckMaskEvent"
checkMaskEvent :: Display -> EventMask -> XEventPtr -> IO Bool
foreign import ccall unsafe "HsXlib.h XCheckTypedEvent"
checkTypedEvent :: Display -> EventType -> XEventPtr -> IO Bool
foreign import ccall unsafe "HsXlib.h XCheckTypedWindowEvent"
checkTypedWindowEvent :: Display -> Window -> EventType ->
XEventPtr -> IO Bool
foreign import ccall unsafe "HsXlib.h XPutBackEvent"
putBackEvent :: Display -> XEventPtr -> IO ()
foreign import ccall unsafe "HsXlib.h XPeekEvent"
peekEvent :: Display -> XEventPtr -> IO ()
refreshKeyboardMapping :: XMappingEvent -> IO ()
refreshKeyboardMapping event_map =
withXMappingEvent event_map $ \ event_map_ptr ->
xRefreshKeyboardMapping event_map_ptr
foreign import ccall unsafe "HsXlib.h XRefreshKeyboardMapping"
xRefreshKeyboardMapping :: Ptr XMappingEvent -> IO ()