Copyright | Will Thompson Iñaki García Etxebarria and Jonas Platte |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria (garetxe@gmail.com) |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type C_EventFunc = Ptr Event -> Ptr () -> IO ()
- type EventFunc = Event -> IO ()
- type EventFunc_WithClosures = Event -> Ptr () -> IO ()
- drop_closures_EventFunc :: EventFunc -> EventFunc_WithClosures
- dynamic_EventFunc :: (HasCallStack, MonadIO m) => FunPtr C_EventFunc -> Event -> Ptr () -> m ()
- genClosure_EventFunc :: EventFunc -> IO Closure
- mk_EventFunc :: C_EventFunc -> IO (FunPtr C_EventFunc)
- noEventFunc :: Maybe EventFunc
- noEventFunc_WithClosures :: Maybe EventFunc_WithClosures
- wrap_EventFunc :: Maybe (Ptr (FunPtr C_EventFunc)) -> EventFunc_WithClosures -> C_EventFunc
- type C_FilterFunc = Ptr () -> Ptr Event -> Ptr () -> IO CUInt
- type FilterFunc = Ptr () -> Event -> IO FilterReturn
- type FilterFunc_WithClosures = Ptr () -> Event -> Ptr () -> IO FilterReturn
- drop_closures_FilterFunc :: FilterFunc -> FilterFunc_WithClosures
- dynamic_FilterFunc :: (HasCallStack, MonadIO m) => FunPtr C_FilterFunc -> Ptr () -> Event -> Ptr () -> m FilterReturn
- genClosure_FilterFunc :: FilterFunc -> IO Closure
- mk_FilterFunc :: C_FilterFunc -> IO (FunPtr C_FilterFunc)
- noFilterFunc :: Maybe FilterFunc
- noFilterFunc_WithClosures :: Maybe FilterFunc_WithClosures
- wrap_FilterFunc :: Maybe (Ptr (FunPtr C_FilterFunc)) -> FilterFunc_WithClosures -> C_FilterFunc
- type C_SeatGrabPrepareFunc = Ptr Seat -> Ptr Window -> Ptr () -> IO ()
- type SeatGrabPrepareFunc = Seat -> Window -> IO ()
- type SeatGrabPrepareFunc_WithClosures = Seat -> Window -> Ptr () -> IO ()
- drop_closures_SeatGrabPrepareFunc :: SeatGrabPrepareFunc -> SeatGrabPrepareFunc_WithClosures
- dynamic_SeatGrabPrepareFunc :: (HasCallStack, MonadIO m, IsSeat a, IsWindow b) => FunPtr C_SeatGrabPrepareFunc -> a -> b -> Ptr () -> m ()
- genClosure_SeatGrabPrepareFunc :: SeatGrabPrepareFunc -> IO Closure
- mk_SeatGrabPrepareFunc :: C_SeatGrabPrepareFunc -> IO (FunPtr C_SeatGrabPrepareFunc)
- noSeatGrabPrepareFunc :: Maybe SeatGrabPrepareFunc
- noSeatGrabPrepareFunc_WithClosures :: Maybe SeatGrabPrepareFunc_WithClosures
- wrap_SeatGrabPrepareFunc :: Maybe (Ptr (FunPtr C_SeatGrabPrepareFunc)) -> SeatGrabPrepareFunc_WithClosures -> C_SeatGrabPrepareFunc
- type C_WindowChildFunc = Ptr Window -> Ptr () -> IO CInt
- type WindowChildFunc = Window -> IO Bool
- type WindowChildFunc_WithClosures = Window -> Ptr () -> IO Bool
- drop_closures_WindowChildFunc :: WindowChildFunc -> WindowChildFunc_WithClosures
- dynamic_WindowChildFunc :: (HasCallStack, MonadIO m, IsWindow a) => FunPtr C_WindowChildFunc -> a -> Ptr () -> m Bool
- genClosure_WindowChildFunc :: WindowChildFunc -> IO Closure
- mk_WindowChildFunc :: C_WindowChildFunc -> IO (FunPtr C_WindowChildFunc)
- noWindowChildFunc :: Maybe WindowChildFunc
- noWindowChildFunc_WithClosures :: Maybe WindowChildFunc_WithClosures
- wrap_WindowChildFunc :: Maybe (Ptr (FunPtr C_WindowChildFunc)) -> WindowChildFunc_WithClosures -> C_WindowChildFunc
- type C_WindowInvalidateHandlerFunc = Ptr Window -> Ptr Region -> IO ()
- type WindowInvalidateHandlerFunc = Window -> Region -> IO ()
- dynamic_WindowInvalidateHandlerFunc :: (HasCallStack, MonadIO m, IsWindow a) => FunPtr C_WindowInvalidateHandlerFunc -> a -> Region -> m ()
- genClosure_WindowInvalidateHandlerFunc :: WindowInvalidateHandlerFunc -> IO Closure
- mk_WindowInvalidateHandlerFunc :: C_WindowInvalidateHandlerFunc -> IO (FunPtr C_WindowInvalidateHandlerFunc)
- noWindowInvalidateHandlerFunc :: Maybe WindowInvalidateHandlerFunc
- wrap_WindowInvalidateHandlerFunc :: Maybe (Ptr (FunPtr C_WindowInvalidateHandlerFunc)) -> WindowInvalidateHandlerFunc -> C_WindowInvalidateHandlerFunc
Signals
EventFunc
type C_EventFunc = Ptr Event -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
Specifies the type of function passed to eventHandlerSet
to
handle all GDK events.
type EventFunc_WithClosures Source #
= Event |
|
-> Ptr () |
|
-> IO () |
Specifies the type of function passed to eventHandlerSet
to
handle all GDK events.
drop_closures_EventFunc :: EventFunc -> EventFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_EventFunc | |
-> Event |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_EventFunc :: C_EventFunc -> IO (FunPtr C_EventFunc) Source #
Generate a function pointer callable from C code, from a C_EventFunc
.
noEventFunc_WithClosures :: Maybe EventFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
EventFunc_WithClosures
wrap_EventFunc :: Maybe (Ptr (FunPtr C_EventFunc)) -> EventFunc_WithClosures -> C_EventFunc Source #
Wrap a EventFunc
into a C_EventFunc
.
FilterFunc
type C_FilterFunc = Ptr () -> Ptr Event -> Ptr () -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type FilterFunc Source #
= Ptr () |
|
-> Event |
|
-> IO FilterReturn | Returns: a |
Specifies the type of function used to filter native events before they are converted to GDK events.
When a filter is called, event
is unpopulated, except for
event->window
. The filter may translate the native
event to a GDK event and store the result in event
, or handle it without
translation. If the filter translates the event and processing should
continue, it should return FilterReturnTranslate
.
type FilterFunc_WithClosures Source #
= Ptr () |
|
-> Event |
|
-> Ptr () |
|
-> IO FilterReturn | Returns: a |
Specifies the type of function used to filter native events before they are converted to GDK events.
When a filter is called, event
is unpopulated, except for
event->window
. The filter may translate the native
event to a GDK event and store the result in event
, or handle it without
translation. If the filter translates the event and processing should
continue, it should return FilterReturnTranslate
.
drop_closures_FilterFunc :: FilterFunc -> FilterFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FilterFunc | |
-> Ptr () |
|
-> Event |
|
-> Ptr () |
|
-> m FilterReturn | Returns: a |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FilterFunc :: FilterFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_FilterFunc :: C_FilterFunc -> IO (FunPtr C_FilterFunc) Source #
Generate a function pointer callable from C code, from a C_FilterFunc
.
noFilterFunc :: Maybe FilterFunc Source #
A convenience synonym for
.Nothing
:: Maybe
FilterFunc
noFilterFunc_WithClosures :: Maybe FilterFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FilterFunc_WithClosures
wrap_FilterFunc :: Maybe (Ptr (FunPtr C_FilterFunc)) -> FilterFunc_WithClosures -> C_FilterFunc Source #
Wrap a FilterFunc
into a C_FilterFunc
.
SeatGrabPrepareFunc
type C_SeatGrabPrepareFunc = Ptr Seat -> Ptr Window -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type SeatGrabPrepareFunc Source #
Type of the callback used to set up window
so it can be
grabbed. A typical action would be ensuring the window is
visible, although there's room for other initialization
actions.
Since: 3.20
type SeatGrabPrepareFunc_WithClosures Source #
= Seat |
|
-> Window |
|
-> Ptr () |
|
-> IO () |
Type of the callback used to set up window
so it can be
grabbed. A typical action would be ensuring the window is
visible, although there's room for other initialization
actions.
Since: 3.20
drop_closures_SeatGrabPrepareFunc :: SeatGrabPrepareFunc -> SeatGrabPrepareFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SeatGrabPrepareFunc Source #
:: (HasCallStack, MonadIO m, IsSeat a, IsWindow b) | |
=> FunPtr C_SeatGrabPrepareFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SeatGrabPrepareFunc :: SeatGrabPrepareFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_SeatGrabPrepareFunc :: C_SeatGrabPrepareFunc -> IO (FunPtr C_SeatGrabPrepareFunc) Source #
Generate a function pointer callable from C code, from a C_SeatGrabPrepareFunc
.
noSeatGrabPrepareFunc :: Maybe SeatGrabPrepareFunc Source #
A convenience synonym for
.Nothing
:: Maybe
SeatGrabPrepareFunc
noSeatGrabPrepareFunc_WithClosures :: Maybe SeatGrabPrepareFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
SeatGrabPrepareFunc_WithClosures
wrap_SeatGrabPrepareFunc :: Maybe (Ptr (FunPtr C_SeatGrabPrepareFunc)) -> SeatGrabPrepareFunc_WithClosures -> C_SeatGrabPrepareFunc Source #
Wrap a SeatGrabPrepareFunc
into a C_SeatGrabPrepareFunc
.
WindowChildFunc
type C_WindowChildFunc = Ptr Window -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type WindowChildFunc Source #
A function of this type is passed to windowInvalidateMaybeRecurse
.
It gets called for each child of the window to determine whether to
recursively invalidate it or now.
type WindowChildFunc_WithClosures Source #
= Window |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function of this type is passed to windowInvalidateMaybeRecurse
.
It gets called for each child of the window to determine whether to
recursively invalidate it or now.
drop_closures_WindowChildFunc :: WindowChildFunc -> WindowChildFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_WindowChildFunc Source #
:: (HasCallStack, MonadIO m, IsWindow a) | |
=> FunPtr C_WindowChildFunc | |
-> a |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WindowChildFunc :: WindowChildFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_WindowChildFunc :: C_WindowChildFunc -> IO (FunPtr C_WindowChildFunc) Source #
Generate a function pointer callable from C code, from a C_WindowChildFunc
.
noWindowChildFunc :: Maybe WindowChildFunc Source #
A convenience synonym for
.Nothing
:: Maybe
WindowChildFunc
noWindowChildFunc_WithClosures :: Maybe WindowChildFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
WindowChildFunc_WithClosures
wrap_WindowChildFunc :: Maybe (Ptr (FunPtr C_WindowChildFunc)) -> WindowChildFunc_WithClosures -> C_WindowChildFunc Source #
Wrap a WindowChildFunc
into a C_WindowChildFunc
.
WindowInvalidateHandlerFunc
type C_WindowInvalidateHandlerFunc = Ptr Window -> Ptr Region -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WindowInvalidateHandlerFunc Source #
Whenever some area of the window is invalidated (directly in the
window or in a child window) this gets called with region
in
the coordinate space of window
. You can use region
to just
keep track of the dirty region, or you can actually change
region
in case you are doing display tricks like showing
a child in multiple places.
Since: 3.10
dynamic_WindowInvalidateHandlerFunc Source #
:: (HasCallStack, MonadIO m, IsWindow a) | |
=> FunPtr C_WindowInvalidateHandlerFunc | |
-> a |
|
-> Region |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WindowInvalidateHandlerFunc :: WindowInvalidateHandlerFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_WindowInvalidateHandlerFunc :: C_WindowInvalidateHandlerFunc -> IO (FunPtr C_WindowInvalidateHandlerFunc) Source #
Generate a function pointer callable from C code, from a C_WindowInvalidateHandlerFunc
.
noWindowInvalidateHandlerFunc :: Maybe WindowInvalidateHandlerFunc Source #
A convenience synonym for
.Nothing
:: Maybe
WindowInvalidateHandlerFunc