Safe Haskell | None |
---|---|
Language | Haskell2010 |
Graphics.Wayland.Server
- newtype ClientState = ClientState CUInt
- clientStateReadable :: ClientState
- clientStateWritable :: ClientState
- clientStateHangup :: ClientState
- clientStateError :: ClientState
- data EventLoop
- data EventSource
- type EventLoopFdFunc = Int -> ClientState -> IO Bool
- type EventLoopTimerFunc = IO Bool
- type EventLoopSignalFunc = Int -> IO Bool
- type EventLoopIdleFunc = IO ()
- eventLoopCreate :: IO EventLoop
- eventLoopDestroy :: EventLoop -> IO ()
- eventLoopAddFd :: EventLoop -> Fd -> ClientState -> EventLoopFdFunc -> IO EventSource
- eventSourceFdUpdate :: EventSource -> ClientState -> IO Result
- eventLoopAddTimer :: EventLoop -> EventLoopTimerFunc -> IO EventSource
- eventLoopAddSignal :: EventLoop -> Int -> EventLoopSignalFunc -> IO EventSource
- eventSourceTimerUpdate :: EventSource -> Int -> IO Result
- eventSourceRemove :: EventSource -> IO ()
- eventSourceCheck :: EventSource -> IO ()
- eventLoopDispatch :: EventLoop -> Int -> IO Result
- eventLoopDispatchIdle :: EventLoop -> IO ()
- eventLoopAddIdle :: EventLoop -> EventLoopIdleFunc -> IO EventSource
- eventLoopGetFd :: EventLoop -> IO Fd
- data DisplayServer
- displayCreate :: IO DisplayServer
- displayDestroy :: DisplayServer -> IO ()
- displayGetEventLoop :: DisplayServer -> IO EventLoop
- displayAddSocket :: DisplayServer -> Maybe String -> IO Result
- displayTerminate :: DisplayServer -> IO ()
- displayRun :: DisplayServer -> IO ()
- displayFlushClients :: DisplayServer -> IO ()
- displayGetSerial :: DisplayServer -> IO Word
- displayNextSerial :: DisplayServer -> IO Word
- clientCreate :: DisplayServer -> Fd -> IO (Maybe Client)
- clientDestroy :: Client -> IO ()
- clientFlush :: Client -> IO ()
- clientGetCredentials :: Client -> IO (ProcessID, UserID, GroupID)
- clientPostNoMemory :: Client -> IO ()
- data ShmBuffer
- shmBufferBeginAccess :: ShmBuffer -> IO ()
- shmBufferEndAccess :: ShmBuffer -> IO ()
- shmBufferGet :: Buffer -> IO (Maybe ShmBuffer)
- shmBufferGetData :: ShmBuffer -> IO (Ptr ())
- shmBufferGetStride :: ShmBuffer -> IO Int
- shmBufferGetFormat :: ShmBuffer -> IO Word
- shmBufferGetWidth :: ShmBuffer -> IO Int
- shmBufferGetHeight :: ShmBuffer -> IO Int
- displayInitShm :: DisplayServer -> IO Result
- displayAddShmFormat :: DisplayServer -> Word -> IO ()
- shmBufferCreate :: Client -> Word -> Word -> Int -> Int -> Word -> IO (Maybe ShmBuffer)
- outputScale :: Output -> Int -> IO ()
- outputDone :: Output -> IO ()
- outputMode :: Output -> Word -> Int -> Int -> Int -> IO ()
- outputGeometry :: Output -> Int -> Int -> Int -> Int -> Int -> String -> String -> Int -> IO ()
- touchCancel :: Touch -> IO ()
- touchFrame :: Touch -> IO ()
- touchMotion :: Touch -> Time -> Int -> Fixed256 -> Fixed256 -> IO ()
- touchUp :: Touch -> Word -> Time -> Int -> IO ()
- touchDown :: Touch -> Word -> Time -> Surface -> Int -> Fixed256 -> Fixed256 -> IO ()
- keyboardModifiers :: Keyboard -> Word -> Word -> Word -> Word -> Word -> IO ()
- keyboardKey :: Keyboard -> Word -> Time -> Word -> Word -> IO ()
- keyboardLeave :: Keyboard -> Word -> Surface -> IO ()
- keyboardEnter :: Keyboard -> Word -> Surface -> (CULong, Ptr ()) -> IO ()
- keyboardKeymap :: Keyboard -> Word -> Fd -> Word -> IO ()
- pointerAxis :: Pointer -> Time -> Word -> Fixed256 -> IO ()
- pointerButton :: Pointer -> Word -> Time -> Word -> Word -> IO ()
- pointerMotion :: Pointer -> Time -> Fixed256 -> Fixed256 -> IO ()
- pointerLeave :: Pointer -> Word -> Surface -> IO ()
- pointerEnter :: Pointer -> Word -> Surface -> Fixed256 -> Fixed256 -> IO ()
- seatName :: Seat -> String -> IO ()
- seatCapabilities :: Seat -> Word -> IO ()
- surfaceLeave :: Surface -> Output -> IO ()
- surfaceEnter :: Surface -> Output -> IO ()
- shellSurfacePopupDone :: ShellSurface -> IO ()
- shellSurfaceConfigure :: ShellSurface -> Word -> Int -> Int -> IO ()
- shellSurfacePing :: ShellSurface -> Word -> IO ()
- dataDeviceSelection :: DataDevice -> Maybe DataOffer -> IO ()
- dataDeviceDrop :: DataDevice -> IO ()
- dataDeviceMotion :: DataDevice -> Time -> Fixed256 -> Fixed256 -> IO ()
- dataDeviceLeave :: DataDevice -> IO ()
- dataDeviceEnter :: DataDevice -> Word -> Surface -> Fixed256 -> Fixed256 -> Maybe DataOffer -> IO ()
- dataDeviceDataOffer :: DataDevice -> DataOffer -> IO ()
- dataSourceCancelled :: DataSource -> IO ()
- dataSourceSend :: DataSource -> String -> Fd -> IO ()
- dataSourceTarget :: DataSource -> Maybe String -> IO ()
- dataOfferOffer :: DataOffer -> String -> IO ()
- bufferRelease :: Buffer -> IO ()
- shmFormat :: Shm -> Word -> IO ()
- callbackDone :: Callback -> Word -> IO ()
- registryGlobalRemove :: Registry -> Word -> IO ()
- registryGlobal :: Registry -> Word -> String -> Word -> IO ()
- data DisplayImplementation = DisplayImplementation {
- displaySync :: Client -> Display -> Callback -> IO ()
- displayGetRegistry :: Client -> Display -> Registry -> IO ()
- data CompositorImplementation = CompositorImplementation {
- compositorCreateSurface :: Client -> Compositor -> Surface -> IO ()
- compositorCreateRegion :: Client -> Compositor -> Region -> IO ()
- data ShmPoolImplementation = ShmPoolImplementation {}
- data ShmImplementation = ShmImplementation {}
- data BufferImplementation = BufferImplementation {
- bufferDestroy :: Client -> Buffer -> IO ()
- data DataOfferImplementation = DataOfferImplementation {}
- data DataSourceImplementation = DataSourceImplementation {
- dataSourceOffer :: Client -> DataSource -> String -> IO ()
- dataSourceDestroy :: Client -> DataSource -> IO ()
- data DataDeviceImplementation = DataDeviceImplementation {
- dataDeviceStartDrag :: Client -> DataDevice -> Maybe DataSource -> Surface -> Maybe Surface -> Word -> IO ()
- dataDeviceSetSelection :: Client -> DataDevice -> Maybe DataSource -> Word -> IO ()
- data DataDeviceManagerImplementation = DataDeviceManagerImplementation {
- dataDeviceManagerCreateDataSource :: Client -> DataDeviceManager -> DataSource -> IO ()
- dataDeviceManagerGetDataDevice :: Client -> DataDeviceManager -> DataDevice -> Seat -> IO ()
- data ShellImplementation = ShellImplementation {
- shellGetShellSurface :: Client -> Shell -> ShellSurface -> Surface -> IO ()
- data ShellSurfaceImplementation = ShellSurfaceImplementation {
- shellSurfacePong :: Client -> ShellSurface -> Word -> IO ()
- shellSurfaceMove :: Client -> ShellSurface -> Seat -> Word -> IO ()
- shellSurfaceResize :: Client -> ShellSurface -> Seat -> Word -> Word -> IO ()
- shellSurfaceSetToplevel :: Client -> ShellSurface -> IO ()
- shellSurfaceSetTransient :: Client -> ShellSurface -> Surface -> Int -> Int -> Word -> IO ()
- shellSurfaceSetFullscreen :: Client -> ShellSurface -> Word -> Word -> Maybe Output -> IO ()
- shellSurfaceSetPopup :: Client -> ShellSurface -> Seat -> Word -> Surface -> Int -> Int -> Word -> IO ()
- shellSurfaceSetMaximized :: Client -> ShellSurface -> Maybe Output -> IO ()
- shellSurfaceSetTitle :: Client -> ShellSurface -> String -> IO ()
- shellSurfaceSetClass :: Client -> ShellSurface -> String -> IO ()
- data SurfaceImplementation = SurfaceImplementation {
- surfaceDestroy :: Client -> Surface -> IO ()
- surfaceAttach :: Client -> Surface -> Maybe Buffer -> Int -> Int -> IO ()
- surfaceDamage :: Client -> Surface -> Int -> Int -> Int -> Int -> IO ()
- surfaceFrame :: Client -> Surface -> Callback -> IO ()
- surfaceSetOpaqueRegion :: Client -> Surface -> Maybe Region -> IO ()
- surfaceSetInputRegion :: Client -> Surface -> Maybe Region -> IO ()
- surfaceCommit :: Client -> Surface -> IO ()
- surfaceSetBufferTransform :: Client -> Surface -> Int -> IO ()
- surfaceSetBufferScale :: Client -> Surface -> Int -> IO ()
- data SeatImplementation = SeatImplementation {
- seatGetPointer :: Client -> Seat -> Pointer -> IO ()
- seatGetKeyboard :: Client -> Seat -> Keyboard -> IO ()
- seatGetTouch :: Client -> Seat -> Touch -> IO ()
- data PointerImplementation = PointerImplementation {}
- data KeyboardImplementation = KeyboardImplementation {
- keyboardRelease :: Client -> Keyboard -> IO ()
- data TouchImplementation = TouchImplementation {
- touchRelease :: Client -> Touch -> IO ()
- data RegionImplementation = RegionImplementation {}
- data SubcompositorImplementation = SubcompositorImplementation {
- subcompositorDestroy :: Client -> Subcompositor -> IO ()
- subcompositorGetSubsurface :: Client -> Subcompositor -> Subsurface -> Surface -> Surface -> IO ()
- data SubsurfaceImplementation = SubsurfaceImplementation {
- subsurfaceDestroy :: Client -> Subsurface -> IO ()
- subsurfaceSetPosition :: Client -> Subsurface -> Int -> Int -> IO ()
- subsurfacePlaceAbove :: Client -> Subsurface -> Surface -> IO ()
- subsurfacePlaceBelow :: Client -> Subsurface -> Surface -> IO ()
- subsurfaceSetSync :: Client -> Subsurface -> IO ()
- subsurfaceSetDesync :: Client -> Subsurface -> IO ()
- wl_subsurface_c_add_listener_request_binding :: Subsurface -> Ptr SubsurfaceImplementation -> Ptr () -> FunPtr (Subsurface -> IO ()) -> IO ()
- wl_subcompositor_c_add_listener_request_binding :: Subcompositor -> Ptr SubcompositorImplementation -> Ptr () -> FunPtr (Subcompositor -> IO ()) -> IO ()
- wl_region_c_add_listener_request_binding :: Region -> Ptr RegionImplementation -> Ptr () -> FunPtr (Region -> IO ()) -> IO ()
- wl_touch_c_add_listener_request_binding :: Touch -> Ptr TouchImplementation -> Ptr () -> FunPtr (Touch -> IO ()) -> IO ()
- wl_keyboard_c_add_listener_request_binding :: Keyboard -> Ptr KeyboardImplementation -> Ptr () -> FunPtr (Keyboard -> IO ()) -> IO ()
- wl_pointer_c_add_listener_request_binding :: Pointer -> Ptr PointerImplementation -> Ptr () -> FunPtr (Pointer -> IO ()) -> IO ()
- wl_seat_c_add_listener_request_binding :: Seat -> Ptr SeatImplementation -> Ptr () -> FunPtr (Seat -> IO ()) -> IO ()
- wl_surface_c_add_listener_request_binding :: Surface -> Ptr SurfaceImplementation -> Ptr () -> FunPtr (Surface -> IO ()) -> IO ()
- wl_shell_surface_c_add_listener_request_binding :: ShellSurface -> Ptr ShellSurfaceImplementation -> Ptr () -> FunPtr (ShellSurface -> IO ()) -> IO ()
- wl_shell_c_add_listener_request_binding :: Shell -> Ptr ShellImplementation -> Ptr () -> FunPtr (Shell -> IO ()) -> IO ()
- wl_data_device_manager_c_add_listener_request_binding :: DataDeviceManager -> Ptr DataDeviceManagerImplementation -> Ptr () -> FunPtr (DataDeviceManager -> IO ()) -> IO ()
- wl_data_device_c_add_listener_request_binding :: DataDevice -> Ptr DataDeviceImplementation -> Ptr () -> FunPtr (DataDevice -> IO ()) -> IO ()
- wl_data_source_c_add_listener_request_binding :: DataSource -> Ptr DataSourceImplementation -> Ptr () -> FunPtr (DataSource -> IO ()) -> IO ()
- wl_data_offer_c_add_listener_request_binding :: DataOffer -> Ptr DataOfferImplementation -> Ptr () -> FunPtr (DataOffer -> IO ()) -> IO ()
- wl_buffer_c_add_listener_request_binding :: Buffer -> Ptr BufferImplementation -> Ptr () -> FunPtr (Buffer -> IO ()) -> IO ()
- wl_shm_c_add_listener_request_binding :: Shm -> Ptr ShmImplementation -> Ptr () -> FunPtr (Shm -> IO ()) -> IO ()
- wl_shm_pool_c_add_listener_request_binding :: ShmPool -> Ptr ShmPoolImplementation -> Ptr () -> FunPtr (ShmPool -> IO ()) -> IO ()
- wl_compositor_c_add_listener_request_binding :: Compositor -> Ptr CompositorImplementation -> Ptr () -> FunPtr (Compositor -> IO ()) -> IO ()
- wl_display_c_add_listener_request_binding :: Display -> Ptr DisplayImplementation -> Ptr () -> FunPtr (Display -> IO ()) -> IO ()
- subsurfaceSetListener :: Subsurface -> SubsurfaceImplementation -> IO ()
- subcompositorSetListener :: Subcompositor -> SubcompositorImplementation -> IO ()
- regionSetListener :: Region -> RegionImplementation -> IO ()
- touchSetListener :: Touch -> TouchImplementation -> IO ()
- keyboardSetListener :: Keyboard -> KeyboardImplementation -> IO ()
- pointerSetListener :: Pointer -> PointerImplementation -> IO ()
- seatSetListener :: Seat -> SeatImplementation -> IO ()
- surfaceSetListener :: Surface -> SurfaceImplementation -> IO ()
- shellSurfaceSetListener :: ShellSurface -> ShellSurfaceImplementation -> IO ()
- shellSetListener :: Shell -> ShellImplementation -> IO ()
- dataDeviceManagerSetListener :: DataDeviceManager -> DataDeviceManagerImplementation -> IO ()
- dataDeviceSetListener :: DataDevice -> DataDeviceImplementation -> IO ()
- dataSourceSetListener :: DataSource -> DataSourceImplementation -> IO ()
- dataOfferSetListener :: DataOffer -> DataOfferImplementation -> IO ()
- bufferSetListener :: Buffer -> BufferImplementation -> IO ()
- shmSetListener :: Shm -> ShmImplementation -> IO ()
- shmPoolSetListener :: ShmPool -> ShmPoolImplementation -> IO ()
- compositorSetListener :: Compositor -> CompositorImplementation -> IO ()
- displaySetListener :: Display -> DisplayImplementation -> IO ()
- newtype Display = Display (Ptr Display)
- newtype Registry = Registry (Ptr Registry)
- newtype Callback = Callback (Ptr Callback)
- newtype Compositor = Compositor (Ptr Compositor)
- newtype ShmPool = ShmPool (Ptr ShmPool)
- newtype Shm = Shm (Ptr Shm)
- newtype Buffer = Buffer (Ptr Buffer)
- newtype DataOffer = DataOffer (Ptr DataOffer)
- newtype DataSource = DataSource (Ptr DataSource)
- newtype DataDevice = DataDevice (Ptr DataDevice)
- newtype DataDeviceManager = DataDeviceManager (Ptr DataDeviceManager)
- newtype Shell = Shell (Ptr Shell)
- newtype ShellSurface = ShellSurface (Ptr ShellSurface)
- newtype Surface = Surface (Ptr Surface)
- newtype Seat = Seat (Ptr Seat)
- newtype Pointer = Pointer (Ptr Pointer)
- newtype Keyboard = Keyboard (Ptr Keyboard)
- newtype Touch = Touch (Ptr Touch)
- newtype Output = Output (Ptr Output)
- newtype Region = Region (Ptr Region)
- newtype Subcompositor = Subcompositor (Ptr Subcompositor)
- newtype Subsurface = Subsurface (Ptr Subsurface)
- wl_subsurface_c_interface :: CInterface
- wl_subcompositor_c_interface :: CInterface
- wl_region_c_interface :: CInterface
- wl_output_c_interface :: CInterface
- wl_touch_c_interface :: CInterface
- wl_keyboard_c_interface :: CInterface
- wl_pointer_c_interface :: CInterface
- wl_seat_c_interface :: CInterface
- wl_surface_c_interface :: CInterface
- wl_shell_surface_c_interface :: CInterface
- wl_shell_c_interface :: CInterface
- wl_data_device_manager_c_interface :: CInterface
- wl_data_device_c_interface :: CInterface
- wl_data_source_c_interface :: CInterface
- wl_data_offer_c_interface :: CInterface
- wl_buffer_c_interface :: CInterface
- wl_shm_c_interface :: CInterface
- wl_shm_pool_c_interface :: CInterface
- wl_compositor_c_interface :: CInterface
- wl_callback_c_interface :: CInterface
- wl_registry_c_interface :: CInterface
- wl_display_c_interface :: CInterface
- newtype DisplayError = DisplayError Int
- newtype ShmError = ShmError Int
- newtype ShmFormat = ShmFormat Int
- newtype ShellSurfaceResize = ShellSurfaceResize Int
- newtype ShellSurfaceTransient = ShellSurfaceTransient Int
- newtype ShellSurfaceFullscreenMethod = ShellSurfaceFullscreenMethod Int
- newtype SeatCapability = SeatCapability Int
- newtype PointerButtonState = PointerButtonState Int
- newtype PointerAxis = PointerAxis Int
- newtype KeyboardKeymapFormat = KeyboardKeymapFormat Int
- newtype KeyboardKeyState = KeyboardKeyState Int
- newtype OutputSubpixel = OutputSubpixel Int
- newtype OutputTransform = OutputTransform Int
- newtype OutputMode = OutputMode Int
- newtype SubcompositorError = SubcompositorError Int
- newtype SubsurfaceError = SubsurfaceError Int
- subsurfaceErrorBadSurface :: SubsurfaceError
- subcompositorErrorBadSurface :: SubcompositorError
- outputModePreferred :: OutputMode
- outputModeCurrent :: OutputMode
- outputTransformFlipped_270 :: OutputTransform
- outputTransformFlipped_180 :: OutputTransform
- outputTransformFlipped_90 :: OutputTransform
- outputTransformFlipped :: OutputTransform
- outputTransform270 :: OutputTransform
- outputTransform180 :: OutputTransform
- outputTransform90 :: OutputTransform
- outputTransformNormal :: OutputTransform
- outputSubpixelVerticalBgr :: OutputSubpixel
- outputSubpixelVerticalRgb :: OutputSubpixel
- outputSubpixelHorizontalBgr :: OutputSubpixel
- outputSubpixelHorizontalRgb :: OutputSubpixel
- outputSubpixelNone :: OutputSubpixel
- outputSubpixelUnknown :: OutputSubpixel
- keyboardKeyStatePressed :: KeyboardKeyState
- keyboardKeyStateReleased :: KeyboardKeyState
- keyboardKeymapFormatXkbV1 :: KeyboardKeymapFormat
- keyboardKeymapFormatNoKeymap :: KeyboardKeymapFormat
- pointerAxisHorizontalScroll :: PointerAxis
- pointerAxisVerticalScroll :: PointerAxis
- pointerButtonStatePressed :: PointerButtonState
- pointerButtonStateReleased :: PointerButtonState
- seatCapabilityTouch :: SeatCapability
- seatCapabilityKeyboard :: SeatCapability
- seatCapabilityPointer :: SeatCapability
- shellSurfaceFullscreenMethodFill :: ShellSurfaceFullscreenMethod
- shellSurfaceFullscreenMethodDriver :: ShellSurfaceFullscreenMethod
- shellSurfaceFullscreenMethodScale :: ShellSurfaceFullscreenMethod
- shellSurfaceFullscreenMethodDefault :: ShellSurfaceFullscreenMethod
- shellSurfaceTransientInactive :: ShellSurfaceTransient
- shellSurfaceResizeBottomRight :: ShellSurfaceResize
- shellSurfaceResizeTopRight :: ShellSurfaceResize
- shellSurfaceResizeRight :: ShellSurfaceResize
- shellSurfaceResizeBottomLeft :: ShellSurfaceResize
- shellSurfaceResizeTopLeft :: ShellSurfaceResize
- shellSurfaceResizeLeft :: ShellSurfaceResize
- shellSurfaceResizeBottom :: ShellSurfaceResize
- shellSurfaceResizeTop :: ShellSurfaceResize
- shellSurfaceResizeNone :: ShellSurfaceResize
- shmFormatYvu444 :: ShmFormat
- shmFormatYuv444 :: ShmFormat
- shmFormatYvu422 :: ShmFormat
- shmFormatYuv422 :: ShmFormat
- shmFormatYvu420 :: ShmFormat
- shmFormatYuv420 :: ShmFormat
- shmFormatYvu411 :: ShmFormat
- shmFormatYuv411 :: ShmFormat
- shmFormatYvu410 :: ShmFormat
- shmFormatYuv410 :: ShmFormat
- shmFormatNv61 :: ShmFormat
- shmFormatNv16 :: ShmFormat
- shmFormatNv21 :: ShmFormat
- shmFormatNv12 :: ShmFormat
- shmFormatAyuv :: ShmFormat
- shmFormatVyuy :: ShmFormat
- shmFormatUyvy :: ShmFormat
- shmFormatYvyu :: ShmFormat
- shmFormatYuyv :: ShmFormat
- shmFormatBgra1010102 :: ShmFormat
- shmFormatRgba1010102 :: ShmFormat
- shmFormatAbgr2101010 :: ShmFormat
- shmFormatArgb2101010 :: ShmFormat
- shmFormatBgrx1010102 :: ShmFormat
- shmFormatRgbx1010102 :: ShmFormat
- shmFormatXbgr2101010 :: ShmFormat
- shmFormatXrgb2101010 :: ShmFormat
- shmFormatBgra8888 :: ShmFormat
- shmFormatRgba8888 :: ShmFormat
- shmFormatAbgr8888 :: ShmFormat
- shmFormatBgrx8888 :: ShmFormat
- shmFormatRgbx8888 :: ShmFormat
- shmFormatXbgr8888 :: ShmFormat
- shmFormatBgr888 :: ShmFormat
- shmFormatRgb888 :: ShmFormat
- shmFormatBgr565 :: ShmFormat
- shmFormatRgb565 :: ShmFormat
- shmFormatBgra5551 :: ShmFormat
- shmFormatRgba5551 :: ShmFormat
- shmFormatAbgr1555 :: ShmFormat
- shmFormatArgb1555 :: ShmFormat
- shmFormatBgrx5551 :: ShmFormat
- shmFormatRgbx5551 :: ShmFormat
- shmFormatXbgr1555 :: ShmFormat
- shmFormatXrgb1555 :: ShmFormat
- shmFormatBgra4444 :: ShmFormat
- shmFormatRgba4444 :: ShmFormat
- shmFormatAbgr4444 :: ShmFormat
- shmFormatArgb4444 :: ShmFormat
- shmFormatBgrx4444 :: ShmFormat
- shmFormatRgbx4444 :: ShmFormat
- shmFormatXbgr4444 :: ShmFormat
- shmFormatXrgb4444 :: ShmFormat
- shmFormatBgr233 :: ShmFormat
- shmFormatRgb332 :: ShmFormat
- shmFormatC8 :: ShmFormat
- shmFormatXrgb8888 :: ShmFormat
- shmFormatArgb8888 :: ShmFormat
- shmErrorInvalidFd :: ShmError
- shmErrorInvalidStride :: ShmError
- shmErrorInvalidFormat :: ShmError
- displayErrorNoMemory :: DisplayError
- displayErrorInvalidMethod :: DisplayError
- displayErrorInvalidObject :: DisplayError
- newtype Client = Client (Ptr Client)
Documentation
newtype ClientState Source
enum { WL_EVENT_READABLE = 0x01, WL_EVENT_WRITABLE = 0x02, WL_EVENT_HANGUP = 0x04, WL_EVENT_ERROR = 0x08 };
The "uint32_t mask" argument passed to a variety of functions in this file is a bitmask detailing the state of the client.
Constructors
ClientState CUInt |
Instances
Enum ClientState | |
Eq ClientState | |
Integral ClientState | |
Num ClientState | |
Ord ClientState | |
Real ClientState | |
Show ClientState | |
Flags ClientState | |
BoundedFlags ClientState |
data EventSource Source
struct wl_event_source;
type EventLoopFdFunc = Int -> ClientState -> IO Bool Source
typedef int (*wl_event_loop_fd_func_t)(int fd, uint32_t mask, void *data);
type EventLoopTimerFunc = IO Bool Source
typedef int (*wl_event_loop_timer_func_t)(void *data);
type EventLoopSignalFunc = Int -> IO Bool Source
typedef int (*wl_event_loop_signal_func_t)(int signal_number, void *data);
type EventLoopIdleFunc = IO () Source
eventLoopCreate :: IO EventLoop Source
struct wl_event_loop *wl_event_loop_create(void);
eventLoopDestroy :: EventLoop -> IO () Source
void wl_event_loop_destroy(struct wl_event_loop *loop);
eventLoopAddFd :: EventLoop -> Fd -> ClientState -> EventLoopFdFunc -> IO EventSource Source
struct wl_event_source *wl_event_loop_add_fd(struct wl_event_loop *loop, int fd, uint32_t mask, wl_event_loop_fd_func_t func, void *data);
eventSourceFdUpdate :: EventSource -> ClientState -> IO Result Source
int wl_event_source_fd_update(struct wl_event_source *source, uint32_t mask);
eventLoopAddTimer :: EventLoop -> EventLoopTimerFunc -> IO EventSource Source
struct wl_event_source *wl_event_loop_add_timer(struct wl_event_loop *loop, wl_event_loop_timer_func_t func, void *data);
eventLoopAddSignal :: EventLoop -> Int -> EventLoopSignalFunc -> IO EventSource Source
struct wl_event_source * wl_event_loop_add_signal(struct wl_event_loop *loop, int signal_number, wl_event_loop_signal_func_t func, void *data);
eventSourceTimerUpdate :: EventSource -> Int -> IO Result Source
int wl_event_source_timer_update(struct wl_event_source *source, int ms_delay);
eventSourceRemove :: EventSource -> IO () Source
int wl_event_source_remove(struct wl_event_source *source);
eventSourceCheck :: EventSource -> IO () Source
void wl_event_source_check(struct wl_event_source *source);
eventLoopDispatch :: EventLoop -> Int -> IO Result Source
int wl_event_loop_dispatch(struct wl_event_loop *loop, int timeout);
SAFE!!
eventLoopDispatchIdle :: EventLoop -> IO () Source
void wl_event_loop_dispatch_idle(struct wl_event_loop *loop);
eventLoopAddIdle :: EventLoop -> EventLoopIdleFunc -> IO EventSource Source
struct wl_event_source *wl_event_loop_add_idle(struct wl_event_loop *loop, wl_event_loop_idle_func_t func, void *data);
eventLoopGetFd :: EventLoop -> IO Fd Source
int wl_event_loop_get_fd(struct wl_event_loop *loop);
data DisplayServer Source
struct wl_display;
this is called a Compositor in e.g weston, QtWayland
this is NOT an instance of a wl_resource or a wl_proxy! it is a global server status singleton listing e.g. connected clients.
displayCreate :: IO DisplayServer Source
struct wl_display *wl_display_create(void);
displayDestroy :: DisplayServer -> IO () Source
void wl_display_destroy(struct wl_display *display);
displayGetEventLoop :: DisplayServer -> IO EventLoop Source
struct wl_event_loop *wl_display_get_event_loop(struct wl_display *display);
displayAddSocket :: DisplayServer -> Maybe String -> IO Result Source
displayTerminate :: DisplayServer -> IO () Source
void wl_display_terminate(struct wl_display *display);
displayRun :: DisplayServer -> IO () Source
void wl_display_run(struct wl_display *display);
STRICTLY SAFE!!!
displayFlushClients :: DisplayServer -> IO () Source
void wl_display_flush_clients(struct wl_display *display);
displayGetSerial :: DisplayServer -> IO Word Source
uint32_t wl_display_get_serial(struct wl_display *display);
displayNextSerial :: DisplayServer -> IO Word Source
uint32_t wl_display_next_serial(struct wl_display *display);
clientCreate :: DisplayServer -> Fd -> IO (Maybe Client) Source
struct wl_client *wl_client_create(struct wl_display *display, int fd);
clientDestroy :: Client -> IO () Source
void wl_client_destroy(struct wl_client *client);
clientFlush :: Client -> IO () Source
void wl_client_flush(struct wl_client *client);
clientGetCredentials :: Client -> IO (ProcessID, UserID, GroupID) Source
void wl_client_get_credentials(struct wl_client *client, pid_t *pid, uid_t *uid, gid_t *gid);
clientPostNoMemory :: Client -> IO () Source
wl_client_post_no_memory(struct wl_client *client);
shmBufferBeginAccess :: ShmBuffer -> IO () Source
void wl_shm_buffer_begin_access(struct wl_shm_buffer *buffer);
Lock the memory for reading. Needed to protect the server against SIGBUS signals caused by the client resizing the buffer.
shmBufferEndAccess :: ShmBuffer -> IO () Source
void wl_shm_buffer_end_access(struct wl_shm_buffer *buffer);
Unlock the memory.
shmBufferGet :: Buffer -> IO (Maybe ShmBuffer) Source
struct wl_shm_buffer * wl_shm_buffer_get(struct wl_resource *resource);
shmBufferGetData :: ShmBuffer -> IO (Ptr ()) Source
void * wl_shm_buffer_get_data(struct wl_shm_buffer *buffer);
shmBufferGetStride :: ShmBuffer -> IO Int Source
int32_t wl_shm_buffer_get_stride(struct wl_shm_buffer *buffer);
shmBufferGetFormat :: ShmBuffer -> IO Word Source
uint32_t wl_shm_buffer_get_format(struct wl_shm_buffer *buffer);
shmBufferGetWidth :: ShmBuffer -> IO Int Source
int32_t wl_shm_buffer_get_width(struct wl_shm_buffer *buffer);
shmBufferGetHeight :: ShmBuffer -> IO Int Source
int32_t wl_shm_buffer_get_height(struct wl_shm_buffer *buffer);
displayInitShm :: DisplayServer -> IO Result Source
int wl_display_init_shm(struct wl_display *display);
displayAddShmFormat :: DisplayServer -> Word -> IO () Source
uint32_t * wl_display_add_shm_format(struct wl_display *display, uint32_t format);
shmBufferCreate :: Client -> Word -> Word -> Int -> Int -> Word -> IO (Maybe ShmBuffer) Source
struct wl_shm_buffer * wl_shm_buffer_create(struct wl_client *client, uint32_t id, int32_t width, int32_t height, int32_t stride, uint32_t format);
outputScale :: Output -> Int -> IO () Source
outputDone :: Output -> IO () Source
outputGeometry :: Output -> Int -> Int -> Int -> Int -> Int -> String -> String -> Int -> IO () Source
touchCancel :: Touch -> IO () Source
touchFrame :: Touch -> IO () Source
seatCapabilities :: Seat -> Word -> IO () Source
surfaceLeave :: Surface -> Output -> IO () Source
surfaceEnter :: Surface -> Output -> IO () Source
shellSurfacePopupDone :: ShellSurface -> IO () Source
shellSurfaceConfigure :: ShellSurface -> Word -> Int -> Int -> IO () Source
shellSurfacePing :: ShellSurface -> Word -> IO () Source
dataDeviceSelection :: DataDevice -> Maybe DataOffer -> IO () Source
dataDeviceDrop :: DataDevice -> IO () Source
dataDeviceMotion :: DataDevice -> Time -> Fixed256 -> Fixed256 -> IO () Source
dataDeviceLeave :: DataDevice -> IO () Source
dataDeviceEnter :: DataDevice -> Word -> Surface -> Fixed256 -> Fixed256 -> Maybe DataOffer -> IO () Source
dataDeviceDataOffer :: DataDevice -> DataOffer -> IO () Source
dataSourceCancelled :: DataSource -> IO () Source
dataSourceSend :: DataSource -> String -> Fd -> IO () Source
dataSourceTarget :: DataSource -> Maybe String -> IO () Source
dataOfferOffer :: DataOffer -> String -> IO () Source
bufferRelease :: Buffer -> IO () Source
callbackDone :: Callback -> Word -> IO () Source
registryGlobalRemove :: Registry -> Word -> IO () Source
data DisplayImplementation Source
Constructors
DisplayImplementation | |
Fields
|
Instances
data CompositorImplementation Source
Constructors
CompositorImplementation | |
Fields
|
Instances
data BufferImplementation Source
Constructors
BufferImplementation | |
Fields
|
Instances
data DataSourceImplementation Source
Constructors
DataSourceImplementation | |
Fields
|
Instances
data DataDeviceImplementation Source
Constructors
DataDeviceImplementation | |
Fields
|
Instances
data DataDeviceManagerImplementation Source
Constructors
DataDeviceManagerImplementation | |
Fields
|
Instances
data ShellImplementation Source
Constructors
ShellImplementation | |
Fields
|
Instances
data ShellSurfaceImplementation Source
Constructors
ShellSurfaceImplementation | |
Fields
|
Instances
data SurfaceImplementation Source
Constructors
SurfaceImplementation | |
Fields
|
Instances
data SeatImplementation Source
Constructors
SeatImplementation | |
Fields
|
Instances
data KeyboardImplementation Source
Constructors
KeyboardImplementation | |
Fields
|
Instances
data TouchImplementation Source
Constructors
TouchImplementation | |
Fields
|
Instances
data SubcompositorImplementation Source
Constructors
SubcompositorImplementation | |
Fields
|
Instances
data SubsurfaceImplementation Source
Constructors
SubsurfaceImplementation | |
Fields
|
Instances
wl_subsurface_c_add_listener_request_binding :: Subsurface -> Ptr SubsurfaceImplementation -> Ptr () -> FunPtr (Subsurface -> IO ()) -> IO () Source
wl_subcompositor_c_add_listener_request_binding :: Subcompositor -> Ptr SubcompositorImplementation -> Ptr () -> FunPtr (Subcompositor -> IO ()) -> IO () Source
wl_region_c_add_listener_request_binding :: Region -> Ptr RegionImplementation -> Ptr () -> FunPtr (Region -> IO ()) -> IO () Source
wl_touch_c_add_listener_request_binding :: Touch -> Ptr TouchImplementation -> Ptr () -> FunPtr (Touch -> IO ()) -> IO () Source
wl_keyboard_c_add_listener_request_binding :: Keyboard -> Ptr KeyboardImplementation -> Ptr () -> FunPtr (Keyboard -> IO ()) -> IO () Source
wl_pointer_c_add_listener_request_binding :: Pointer -> Ptr PointerImplementation -> Ptr () -> FunPtr (Pointer -> IO ()) -> IO () Source
wl_seat_c_add_listener_request_binding :: Seat -> Ptr SeatImplementation -> Ptr () -> FunPtr (Seat -> IO ()) -> IO () Source
wl_surface_c_add_listener_request_binding :: Surface -> Ptr SurfaceImplementation -> Ptr () -> FunPtr (Surface -> IO ()) -> IO () Source
wl_shell_surface_c_add_listener_request_binding :: ShellSurface -> Ptr ShellSurfaceImplementation -> Ptr () -> FunPtr (ShellSurface -> IO ()) -> IO () Source
wl_shell_c_add_listener_request_binding :: Shell -> Ptr ShellImplementation -> Ptr () -> FunPtr (Shell -> IO ()) -> IO () Source
wl_data_device_manager_c_add_listener_request_binding :: DataDeviceManager -> Ptr DataDeviceManagerImplementation -> Ptr () -> FunPtr (DataDeviceManager -> IO ()) -> IO () Source
wl_data_device_c_add_listener_request_binding :: DataDevice -> Ptr DataDeviceImplementation -> Ptr () -> FunPtr (DataDevice -> IO ()) -> IO () Source
wl_data_source_c_add_listener_request_binding :: DataSource -> Ptr DataSourceImplementation -> Ptr () -> FunPtr (DataSource -> IO ()) -> IO () Source
wl_data_offer_c_add_listener_request_binding :: DataOffer -> Ptr DataOfferImplementation -> Ptr () -> FunPtr (DataOffer -> IO ()) -> IO () Source
wl_buffer_c_add_listener_request_binding :: Buffer -> Ptr BufferImplementation -> Ptr () -> FunPtr (Buffer -> IO ()) -> IO () Source
wl_shm_c_add_listener_request_binding :: Shm -> Ptr ShmImplementation -> Ptr () -> FunPtr (Shm -> IO ()) -> IO () Source
wl_shm_pool_c_add_listener_request_binding :: ShmPool -> Ptr ShmPoolImplementation -> Ptr () -> FunPtr (ShmPool -> IO ()) -> IO () Source
wl_compositor_c_add_listener_request_binding :: Compositor -> Ptr CompositorImplementation -> Ptr () -> FunPtr (Compositor -> IO ()) -> IO () Source
wl_display_c_add_listener_request_binding :: Display -> Ptr DisplayImplementation -> Ptr () -> FunPtr (Display -> IO ()) -> IO () Source
subsurfaceSetListener :: Subsurface -> SubsurfaceImplementation -> IO () Source
regionSetListener :: Region -> RegionImplementation -> IO () Source
touchSetListener :: Touch -> TouchImplementation -> IO () Source
keyboardSetListener :: Keyboard -> KeyboardImplementation -> IO () Source
pointerSetListener :: Pointer -> PointerImplementation -> IO () Source
seatSetListener :: Seat -> SeatImplementation -> IO () Source
surfaceSetListener :: Surface -> SurfaceImplementation -> IO () Source
shellSetListener :: Shell -> ShellImplementation -> IO () Source
dataDeviceManagerSetListener :: DataDeviceManager -> DataDeviceManagerImplementation -> IO () Source
dataDeviceSetListener :: DataDevice -> DataDeviceImplementation -> IO () Source
dataSourceSetListener :: DataSource -> DataSourceImplementation -> IO () Source
dataOfferSetListener :: DataOffer -> DataOfferImplementation -> IO () Source
bufferSetListener :: Buffer -> BufferImplementation -> IO () Source
shmSetListener :: Shm -> ShmImplementation -> IO () Source
shmPoolSetListener :: ShmPool -> ShmPoolImplementation -> IO () Source
compositorSetListener :: Compositor -> CompositorImplementation -> IO () Source
displaySetListener :: Display -> DisplayImplementation -> IO () Source
newtype ShellSurfaceFullscreenMethod Source
Constructors
ShellSurfaceFullscreenMethod Int |