Safe Haskell | None |
---|---|
Language | Haskell2010 |
Graphics.Wayland.Client
- data Result
- displayConnect :: IO (Maybe Display)
- displayConnectName :: String -> IO (Maybe Display)
- displayConnectFd :: Fd -> IO (Maybe Display)
- displayDisconnect :: Display -> IO ()
- displayGetFd :: Display -> IO Fd
- displayDispatch :: Display -> IO (Maybe Int)
- displayDispatchPending :: Display -> IO (Maybe Int)
- displayGetError :: Display -> IO (Maybe Int)
- displayFlush :: Display -> IO (Maybe Int)
- displayRoundtrip :: Display -> IO (Maybe Int)
- displayPrepareRead :: Display -> IO Result
- displayCancelRead :: Display -> IO ()
- displayReadEvents :: Display -> IO Result
- subsurfaceSetDesync :: Subsurface -> IO ()
- subsurfaceSetSync :: Subsurface -> IO ()
- subsurfacePlaceBelow :: Subsurface -> Surface -> IO ()
- subsurfacePlaceAbove :: Subsurface -> Surface -> IO ()
- subsurfaceSetPosition :: Subsurface -> Int -> Int -> IO ()
- subsurfaceDestroy :: Subsurface -> IO ()
- subcompositorGetSubsurface :: Subcompositor -> Surface -> Surface -> IO Subsurface
- subcompositorDestroy :: Subcompositor -> IO ()
- regionSubtract :: Region -> Int -> Int -> Int -> Int -> IO ()
- regionAdd :: Region -> Int -> Int -> Int -> Int -> IO ()
- regionDestroy :: Region -> IO ()
- outputDestroy :: Output -> IO ()
- touchRelease :: Touch -> IO ()
- keyboardRelease :: Keyboard -> IO ()
- pointerRelease :: Pointer -> IO ()
- pointerSetCursor :: Pointer -> Word -> Maybe Surface -> Int -> Int -> IO ()
- seatDestroy :: Seat -> IO ()
- seatGetTouch :: Seat -> IO Touch
- seatGetKeyboard :: Seat -> IO Keyboard
- seatGetPointer :: Seat -> IO Pointer
- surfaceSetBufferScale :: Surface -> Int -> IO ()
- surfaceSetBufferTransform :: Surface -> Int -> IO ()
- surfaceCommit :: Surface -> IO ()
- surfaceSetInputRegion :: Surface -> Maybe Region -> IO ()
- surfaceSetOpaqueRegion :: Surface -> Maybe Region -> IO ()
- surfaceFrame :: Surface -> IO Callback
- surfaceDamage :: Surface -> Int -> Int -> Int -> Int -> IO ()
- surfaceAttach :: Surface -> Maybe Buffer -> Int -> Int -> IO ()
- surfaceDestroy :: Surface -> IO ()
- shellSurfaceDestroy :: ShellSurface -> IO ()
- shellSurfaceSetClass :: ShellSurface -> String -> IO ()
- shellSurfaceSetTitle :: ShellSurface -> String -> IO ()
- shellSurfaceSetMaximized :: ShellSurface -> Maybe Output -> IO ()
- shellSurfaceSetPopup :: ShellSurface -> Seat -> Word -> Surface -> Int -> Int -> Word -> IO ()
- shellSurfaceSetFullscreen :: ShellSurface -> Word -> Word -> Maybe Output -> IO ()
- shellSurfaceSetTransient :: ShellSurface -> Surface -> Int -> Int -> Word -> IO ()
- shellSurfaceSetToplevel :: ShellSurface -> IO ()
- shellSurfaceResize :: ShellSurface -> Seat -> Word -> Word -> IO ()
- shellSurfaceMove :: ShellSurface -> Seat -> Word -> IO ()
- shellSurfacePong :: ShellSurface -> Word -> IO ()
- shellDestroy :: Shell -> IO ()
- shellGetShellSurface :: Shell -> Surface -> IO ShellSurface
- dataDeviceManagerDestroy :: DataDeviceManager -> IO ()
- dataDeviceManagerGetDataDevice :: DataDeviceManager -> Seat -> IO DataDevice
- dataDeviceManagerCreateDataSource :: DataDeviceManager -> IO DataSource
- dataDeviceDestroy :: DataDevice -> IO ()
- dataDeviceSetSelection :: DataDevice -> Maybe DataSource -> Word -> IO ()
- dataDeviceStartDrag :: DataDevice -> Maybe DataSource -> Surface -> Maybe Surface -> Word -> IO ()
- dataSourceDestroy :: DataSource -> IO ()
- dataSourceOffer :: DataSource -> String -> IO ()
- dataOfferDestroy :: DataOffer -> IO ()
- dataOfferReceive :: DataOffer -> String -> Fd -> IO ()
- dataOfferAccept :: DataOffer -> Word -> Maybe String -> IO ()
- bufferDestroy :: Buffer -> IO ()
- shmDestroy :: Shm -> IO ()
- shmCreatePool :: Shm -> Fd -> Int -> IO ShmPool
- shmPoolResize :: ShmPool -> Int -> IO ()
- shmPoolDestroy :: ShmPool -> IO ()
- shmPoolCreateBuffer :: ShmPool -> Int -> Int -> Int -> Int -> Word -> IO Buffer
- compositorDestroy :: Compositor -> IO ()
- compositorCreateRegion :: Compositor -> IO Region
- compositorCreateSurface :: Compositor -> IO Surface
- callbackDestroy :: Callback -> IO ()
- registryDestroy :: Registry -> IO ()
- displayGetRegistry :: Display -> IO Registry
- displaySync :: Display -> IO Callback
- data DisplayListener = DisplayListener {
- displayDeleteId :: Display -> Word -> IO ()
- data RegistryListener = RegistryListener {
- registryGlobal :: Registry -> Word -> String -> Word -> IO ()
- registryGlobalRemove :: Registry -> Word -> IO ()
- data CallbackListener = CallbackListener {
- callbackDone :: Callback -> Word -> IO ()
- data ShmListener = ShmListener {}
- data BufferListener = BufferListener {
- bufferRelease :: Buffer -> IO ()
- data DataOfferListener = DataOfferListener {
- dataOfferOffer :: DataOffer -> String -> IO ()
- data DataSourceListener = DataSourceListener {
- dataSourceTarget :: DataSource -> Maybe String -> IO ()
- dataSourceSend :: DataSource -> String -> Fd -> IO ()
- dataSourceCancelled :: DataSource -> IO ()
- data DataDeviceListener = DataDeviceListener {
- dataDeviceDataOffer :: DataDevice -> DataOffer -> IO ()
- dataDeviceEnter :: DataDevice -> Word -> Surface -> Fixed256 -> Fixed256 -> Maybe DataOffer -> IO ()
- dataDeviceLeave :: DataDevice -> IO ()
- dataDeviceMotion :: DataDevice -> Time -> Fixed256 -> Fixed256 -> IO ()
- dataDeviceDrop :: DataDevice -> IO ()
- dataDeviceSelection :: DataDevice -> Maybe DataOffer -> IO ()
- data ShellSurfaceListener = ShellSurfaceListener {
- shellSurfacePing :: ShellSurface -> Word -> IO ()
- shellSurfaceConfigure :: ShellSurface -> Word -> Int -> Int -> IO ()
- shellSurfacePopupDone :: ShellSurface -> IO ()
- data SurfaceListener = SurfaceListener {
- surfaceEnter :: Surface -> Output -> IO ()
- surfaceLeave :: Surface -> Output -> IO ()
- data SeatListener = SeatListener {}
- data PointerListener = PointerListener {
- pointerEnter :: Pointer -> Word -> Surface -> Fixed256 -> Fixed256 -> IO ()
- pointerLeave :: Pointer -> Word -> Surface -> IO ()
- pointerMotion :: Pointer -> Time -> Fixed256 -> Fixed256 -> IO ()
- pointerButton :: Pointer -> Word -> Time -> Word -> Word -> IO ()
- pointerAxis :: Pointer -> Time -> Word -> Fixed256 -> IO ()
- data KeyboardListener = KeyboardListener {
- keyboardKeymap :: Keyboard -> Word -> Fd -> Word -> IO ()
- keyboardEnter :: Keyboard -> Word -> Surface -> (Int, Ptr ()) -> IO ()
- keyboardLeave :: Keyboard -> Word -> Surface -> IO ()
- keyboardKey :: Keyboard -> Word -> Time -> Word -> Word -> IO ()
- keyboardModifiers :: Keyboard -> Word -> Word -> Word -> Word -> Word -> IO ()
- data TouchListener = TouchListener {}
- data OutputListener = OutputListener {}
- wl_output_c_add_listener_request_binding :: Output -> Ptr OutputListener -> Ptr () -> IO CInt
- wl_touch_c_add_listener_request_binding :: Touch -> Ptr TouchListener -> Ptr () -> IO CInt
- wl_keyboard_c_add_listener_request_binding :: Keyboard -> Ptr KeyboardListener -> Ptr () -> IO CInt
- wl_pointer_c_add_listener_request_binding :: Pointer -> Ptr PointerListener -> Ptr () -> IO CInt
- wl_seat_c_add_listener_request_binding :: Seat -> Ptr SeatListener -> Ptr () -> IO CInt
- wl_surface_c_add_listener_request_binding :: Surface -> Ptr SurfaceListener -> Ptr () -> IO CInt
- wl_shell_surface_c_add_listener_request_binding :: ShellSurface -> Ptr ShellSurfaceListener -> Ptr () -> IO CInt
- wl_data_device_c_add_listener_request_binding :: DataDevice -> Ptr DataDeviceListener -> Ptr () -> IO CInt
- wl_data_source_c_add_listener_request_binding :: DataSource -> Ptr DataSourceListener -> Ptr () -> IO CInt
- wl_data_offer_c_add_listener_request_binding :: DataOffer -> Ptr DataOfferListener -> Ptr () -> IO CInt
- wl_buffer_c_add_listener_request_binding :: Buffer -> Ptr BufferListener -> Ptr () -> IO CInt
- wl_shm_c_add_listener_request_binding :: Shm -> Ptr ShmListener -> Ptr () -> IO CInt
- wl_callback_c_add_listener_request_binding :: Callback -> Ptr CallbackListener -> Ptr () -> IO CInt
- wl_registry_c_add_listener_request_binding :: Registry -> Ptr RegistryListener -> Ptr () -> IO CInt
- wl_display_c_add_listener_request_binding :: Display -> Ptr DisplayListener -> Ptr () -> IO CInt
- outputSetListener :: Output -> OutputListener -> IO Result
- touchSetListener :: Touch -> TouchListener -> IO Result
- keyboardSetListener :: Keyboard -> KeyboardListener -> IO Result
- pointerSetListener :: Pointer -> PointerListener -> IO Result
- seatSetListener :: Seat -> SeatListener -> IO Result
- surfaceSetListener :: Surface -> SurfaceListener -> IO Result
- shellSurfaceSetListener :: ShellSurface -> ShellSurfaceListener -> IO Result
- dataDeviceSetListener :: DataDevice -> DataDeviceListener -> IO Result
- dataSourceSetListener :: DataSource -> DataSourceListener -> IO Result
- dataOfferSetListener :: DataOffer -> DataOfferListener -> IO Result
- bufferSetListener :: Buffer -> BufferListener -> IO Result
- shmSetListener :: Shm -> ShmListener -> IO Result
- callbackSetListener :: Callback -> CallbackListener -> IO Result
- registrySetListener :: Registry -> RegistryListener -> IO Result
- displaySetListener :: Display -> DisplayListener -> IO Result
- registryBindSubcompositor :: Registry -> Word -> String -> Word -> IO Subcompositor
- registryBindOutput :: Registry -> Word -> String -> Word -> IO Output
- registryBindSeat :: Registry -> Word -> String -> Word -> IO Seat
- registryBindShell :: Registry -> Word -> String -> Word -> IO Shell
- registryBindDataDeviceManager :: Registry -> Word -> String -> Word -> IO DataDeviceManager
- registryBindDataOffer :: Registry -> Word -> String -> Word -> IO DataOffer
- registryBindShm :: Registry -> Word -> String -> Word -> IO Shm
- registryBindCompositor :: Registry -> Word -> String -> Word -> IO Compositor
- 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
- data CursorTheme
- data CursorImage
- data Cursor
- cursorImageSize :: CursorImage -> (Word, Word)
- cursorImageHotspot :: CursorImage -> (Word, Word)
- cursorImageDelay :: CursorImage -> Word
- cursorName :: Cursor -> String
- cursorImages :: Cursor -> [CursorImage]
- cursorThemeLoad :: String -> Int -> Shm -> IO CursorTheme
- cursorThemeDestroy :: CursorTheme -> IO ()
- cursorThemeGetCursor :: CursorTheme -> String -> IO Cursor
- cursorImageGetBuffer :: CursorImage -> IO Buffer
- cursorFrame :: Cursor -> Int -> IO Int
- data EGLWindow
- eglWindowCreate :: Surface -> Int -> Int -> IO EGLWindow
- eglWindowDestroy :: EGLWindow -> IO ()
- eglWindowResize :: EGLWindow -> Int -> Int -> Int -> Int -> IO ()
- eglWindowGetAttachedSize :: EGLWindow -> IO (Int, Int)
Documentation
displayConnect :: IO (Maybe Display) Source
Connect to the default display by passing a null pointer
displayDisconnect :: Display -> IO () Source
displayGetFd :: Display -> IO Fd Source
displayDispatch :: Display -> IO (Maybe Int) Source
wl_display_dispatch. Returns Nothing
on failure or Just k
if k events were processed.
Strictly safe!!! This *will* call back into Haskell code!
displayDispatchPending :: Display -> IO (Maybe Int) Source
wl_display_dispatch_pending. Returns Nothing
on failure or Just k
if k events were processed.
Strictly safe!!! This *will* call back into Haskell code!
displayGetError :: Display -> IO (Maybe Int) Source
Nothing
if no error occurred or Just k
if the latest error had code k
Note (from the wayland documentation): errors are fatal. If this function returns a Just
value, the display can no longer be used.
displayFlush :: Display -> IO (Maybe Int) Source
Nothing
on failure or Just k
if k bytes were sent
It is not clear to me if this is can be unsafe (ie. can this call back into haskell code?).
displayRoundtrip :: Display -> IO (Maybe Int) Source
Nothing
on failure or Just k
if k events were dispatched.
It is not clear to me if this is can be unsafe (ie. can this call back into haskell code?).
displayPrepareRead :: Display -> IO Result Source
displayCancelRead :: Display -> IO () Source
displayReadEvents :: Display -> IO Result Source
This will read events from the file descriptor for the display. This function does not dispatch events, it only reads and queues events into their corresponding event queues.
Before calling this function, wl_display_prepare_read() must be called first.
subsurfaceSetDesync :: Subsurface -> IO () Source
subsurfaceSetSync :: Subsurface -> IO () Source
subsurfacePlaceBelow :: Subsurface -> Surface -> IO () Source
subsurfacePlaceAbove :: Subsurface -> Surface -> IO () Source
subsurfaceSetPosition :: Subsurface -> Int -> Int -> IO () Source
subsurfaceDestroy :: Subsurface -> IO () Source
subcompositorGetSubsurface :: Subcompositor -> Surface -> Surface -> IO Subsurface Source
subcompositorDestroy :: Subcompositor -> IO () Source
regionDestroy :: Region -> IO () Source
outputDestroy :: Output -> IO () Source
touchRelease :: Touch -> IO () Source
keyboardRelease :: Keyboard -> IO () Source
pointerRelease :: Pointer -> IO () Source
seatDestroy :: Seat -> IO () Source
seatGetTouch :: Seat -> IO Touch Source
seatGetKeyboard :: Seat -> IO Keyboard Source
seatGetPointer :: Seat -> IO Pointer Source
surfaceSetBufferScale :: Surface -> Int -> IO () Source
surfaceSetBufferTransform :: Surface -> Int -> IO () Source
surfaceCommit :: Surface -> IO () Source
surfaceFrame :: Surface -> IO Callback Source
surfaceDestroy :: Surface -> IO () Source
shellSurfaceDestroy :: ShellSurface -> IO () Source
shellSurfaceSetClass :: ShellSurface -> String -> IO () Source
shellSurfaceSetTitle :: ShellSurface -> String -> IO () Source
shellSurfaceSetMaximized :: ShellSurface -> Maybe Output -> IO () Source
shellSurfaceSetPopup :: ShellSurface -> Seat -> Word -> Surface -> Int -> Int -> Word -> IO () Source
shellSurfaceSetFullscreen :: ShellSurface -> Word -> Word -> Maybe Output -> IO () Source
shellSurfaceSetTransient :: ShellSurface -> Surface -> Int -> Int -> Word -> IO () Source
shellSurfaceSetToplevel :: ShellSurface -> IO () Source
shellSurfaceResize :: ShellSurface -> Seat -> Word -> Word -> IO () Source
shellSurfaceMove :: ShellSurface -> Seat -> Word -> IO () Source
shellSurfacePong :: ShellSurface -> Word -> IO () Source
shellDestroy :: Shell -> IO () Source
shellGetShellSurface :: Shell -> Surface -> IO ShellSurface Source
dataDeviceDestroy :: DataDevice -> IO () Source
dataDeviceSetSelection :: DataDevice -> Maybe DataSource -> Word -> IO () Source
dataDeviceStartDrag :: DataDevice -> Maybe DataSource -> Surface -> Maybe Surface -> Word -> IO () Source
dataSourceDestroy :: DataSource -> IO () Source
dataSourceOffer :: DataSource -> String -> IO () Source
dataOfferDestroy :: DataOffer -> IO () Source
bufferDestroy :: Buffer -> IO () Source
shmDestroy :: Shm -> IO () Source
shmPoolResize :: ShmPool -> Int -> IO () Source
shmPoolDestroy :: ShmPool -> IO () Source
compositorDestroy :: Compositor -> IO () Source
callbackDestroy :: Callback -> IO () Source
registryDestroy :: Registry -> IO () Source
displaySync :: Display -> IO Callback Source
data DisplayListener Source
Constructors
DisplayListener | |
Fields
|
Instances
data RegistryListener Source
Constructors
RegistryListener | |
Fields
|
Instances
data CallbackListener Source
Constructors
CallbackListener | |
Fields
|
Instances
data BufferListener Source
Constructors
BufferListener | |
Fields
|
Instances
data DataOfferListener Source
Constructors
DataOfferListener | |
Fields
|
Instances
data DataSourceListener Source
Constructors
DataSourceListener | |
Fields
|
Instances
data DataDeviceListener Source
Constructors
DataDeviceListener | |
Fields
|
Instances
data ShellSurfaceListener Source
Constructors
ShellSurfaceListener | |
Fields
|
Instances
data SurfaceListener Source
Constructors
SurfaceListener | |
Fields
|
Instances
data PointerListener Source
Constructors
PointerListener | |
Fields
|
Instances
data KeyboardListener Source
Constructors
KeyboardListener | |
Fields
|
Instances
wl_output_c_add_listener_request_binding :: Output -> Ptr OutputListener -> Ptr () -> IO CInt Source
wl_touch_c_add_listener_request_binding :: Touch -> Ptr TouchListener -> Ptr () -> IO CInt Source
wl_keyboard_c_add_listener_request_binding :: Keyboard -> Ptr KeyboardListener -> Ptr () -> IO CInt Source
wl_pointer_c_add_listener_request_binding :: Pointer -> Ptr PointerListener -> Ptr () -> IO CInt Source
wl_seat_c_add_listener_request_binding :: Seat -> Ptr SeatListener -> Ptr () -> IO CInt Source
wl_surface_c_add_listener_request_binding :: Surface -> Ptr SurfaceListener -> Ptr () -> IO CInt Source
wl_shell_surface_c_add_listener_request_binding :: ShellSurface -> Ptr ShellSurfaceListener -> Ptr () -> IO CInt Source
wl_data_device_c_add_listener_request_binding :: DataDevice -> Ptr DataDeviceListener -> Ptr () -> IO CInt Source
wl_data_source_c_add_listener_request_binding :: DataSource -> Ptr DataSourceListener -> Ptr () -> IO CInt Source
wl_data_offer_c_add_listener_request_binding :: DataOffer -> Ptr DataOfferListener -> Ptr () -> IO CInt Source
wl_buffer_c_add_listener_request_binding :: Buffer -> Ptr BufferListener -> Ptr () -> IO CInt Source
wl_shm_c_add_listener_request_binding :: Shm -> Ptr ShmListener -> Ptr () -> IO CInt Source
wl_callback_c_add_listener_request_binding :: Callback -> Ptr CallbackListener -> Ptr () -> IO CInt Source
wl_registry_c_add_listener_request_binding :: Registry -> Ptr RegistryListener -> Ptr () -> IO CInt Source
wl_display_c_add_listener_request_binding :: Display -> Ptr DisplayListener -> Ptr () -> IO CInt Source
outputSetListener :: Output -> OutputListener -> IO Result Source
touchSetListener :: Touch -> TouchListener -> IO Result Source
pointerSetListener :: Pointer -> PointerListener -> IO Result Source
seatSetListener :: Seat -> SeatListener -> IO Result Source
surfaceSetListener :: Surface -> SurfaceListener -> IO Result Source
bufferSetListener :: Buffer -> BufferListener -> IO Result Source
shmSetListener :: Shm -> ShmListener -> IO Result Source
displaySetListener :: Display -> DisplayListener -> IO Result Source
registryBindSubcompositor :: Registry -> Word -> String -> Word -> IO Subcompositor Source
registryBindDataDeviceManager :: Registry -> Word -> String -> Word -> IO DataDeviceManager Source
registryBindCompositor :: Registry -> Word -> String -> Word -> IO Compositor Source
newtype ShellSurfaceFullscreenMethod Source
Constructors
ShellSurfaceFullscreenMethod Int |
data CursorTheme Source
struct wl_cursor_theme;
data CursorImage Source
struct wl_cursor_image { uint32_t width; * actual width * uint32_t height; * actual height * uint32_t hotspot_x; * hot spot x (must be inside image) * uint32_t hotspot_y; * hot spot y (must be inside image) * uint32_t delay; * animation delay to next frame (ms) * };
struct wl_cursor { unsigned int image_count; struct wl_cursor_image **images; char *name; };
cursorImageSize :: CursorImage -> (Word, Word) Source
cursorImageHotspot :: CursorImage -> (Word, Word) Source
cursorName :: Cursor -> String Source
cursorImages :: Cursor -> [CursorImage] Source
cursorThemeLoad :: String -> Int -> Shm -> IO CursorTheme Source
struct wl_cursor_theme * wl_cursor_theme_load(const char *name, int size, struct wl_shm *shm);
cursorThemeDestroy :: CursorTheme -> IO () Source
void wl_cursor_theme_destroy(struct wl_cursor_theme *theme);
cursorThemeGetCursor :: CursorTheme -> String -> IO Cursor Source
struct wl_cursor * wl_cursor_theme_get_cursor(struct wl_cursor_theme *theme, const char *name);
cursorImageGetBuffer :: CursorImage -> IO Buffer Source
struct wl_buffer * wl_cursor_image_get_buffer(struct wl_cursor_image *image);
From the wayland docs: do not destroy the returned buffer.
cursorFrame :: Cursor -> Int -> IO Int Source
int wl_cursor_frame(struct wl_cursor *cursor, uint32_t time);
eglWindowDestroy :: EGLWindow -> IO () Source