Copyright | Will Thompson and Iñaki García Etxebarria |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type C_ClassDeletePropertyFunction = Ptr Class -> Ptr Context -> Ptr () -> CString -> IO CInt
- type ClassDeletePropertyFunction = Class -> Context -> Ptr () -> Text -> IO Bool
- dynamic_ClassDeletePropertyFunction :: (HasCallStack, MonadIO m, IsClass a, IsContext b) => FunPtr C_ClassDeletePropertyFunction -> a -> b -> Ptr () -> Text -> m Bool
- genClosure_ClassDeletePropertyFunction :: MonadIO m => ClassDeletePropertyFunction -> m (GClosure C_ClassDeletePropertyFunction)
- mk_ClassDeletePropertyFunction :: C_ClassDeletePropertyFunction -> IO (FunPtr C_ClassDeletePropertyFunction)
- noClassDeletePropertyFunction :: Maybe ClassDeletePropertyFunction
- wrap_ClassDeletePropertyFunction :: Maybe (Ptr (FunPtr C_ClassDeletePropertyFunction)) -> ClassDeletePropertyFunction -> C_ClassDeletePropertyFunction
- type C_ClassEnumeratePropertiesFunction = Ptr Class -> Ptr Context -> Ptr () -> IO (Ptr CString)
- type ClassEnumeratePropertiesFunction = Class -> Context -> Ptr () -> IO (Maybe [Text])
- dynamic_ClassEnumeratePropertiesFunction :: (HasCallStack, MonadIO m, IsClass a, IsContext b) => FunPtr C_ClassEnumeratePropertiesFunction -> a -> b -> Ptr () -> m (Maybe [Text])
- genClosure_ClassEnumeratePropertiesFunction :: MonadIO m => ClassEnumeratePropertiesFunction -> m (GClosure C_ClassEnumeratePropertiesFunction)
- mk_ClassEnumeratePropertiesFunction :: C_ClassEnumeratePropertiesFunction -> IO (FunPtr C_ClassEnumeratePropertiesFunction)
- noClassEnumeratePropertiesFunction :: Maybe ClassEnumeratePropertiesFunction
- wrap_ClassEnumeratePropertiesFunction :: Maybe (Ptr (FunPtr C_ClassEnumeratePropertiesFunction)) -> ClassEnumeratePropertiesFunction -> C_ClassEnumeratePropertiesFunction
- type C_ClassGetPropertyFunction = Ptr Class -> Ptr Context -> Ptr () -> CString -> IO (Ptr Value)
- type ClassGetPropertyFunction = Class -> Context -> Ptr () -> Text -> IO (Maybe Value)
- dynamic_ClassGetPropertyFunction :: (HasCallStack, MonadIO m, IsClass a, IsContext b) => FunPtr C_ClassGetPropertyFunction -> a -> b -> Ptr () -> Text -> m (Maybe Value)
- genClosure_ClassGetPropertyFunction :: MonadIO m => ClassGetPropertyFunction -> m (GClosure C_ClassGetPropertyFunction)
- mk_ClassGetPropertyFunction :: C_ClassGetPropertyFunction -> IO (FunPtr C_ClassGetPropertyFunction)
- noClassGetPropertyFunction :: Maybe ClassGetPropertyFunction
- wrap_ClassGetPropertyFunction :: Maybe (Ptr (FunPtr C_ClassGetPropertyFunction)) -> ClassGetPropertyFunction -> C_ClassGetPropertyFunction
- type C_ClassHasPropertyFunction = Ptr Class -> Ptr Context -> Ptr () -> CString -> IO CInt
- type ClassHasPropertyFunction = Class -> Context -> Ptr () -> Text -> IO Bool
- dynamic_ClassHasPropertyFunction :: (HasCallStack, MonadIO m, IsClass a, IsContext b) => FunPtr C_ClassHasPropertyFunction -> a -> b -> Ptr () -> Text -> m Bool
- genClosure_ClassHasPropertyFunction :: MonadIO m => ClassHasPropertyFunction -> m (GClosure C_ClassHasPropertyFunction)
- mk_ClassHasPropertyFunction :: C_ClassHasPropertyFunction -> IO (FunPtr C_ClassHasPropertyFunction)
- noClassHasPropertyFunction :: Maybe ClassHasPropertyFunction
- wrap_ClassHasPropertyFunction :: Maybe (Ptr (FunPtr C_ClassHasPropertyFunction)) -> ClassHasPropertyFunction -> C_ClassHasPropertyFunction
- type C_ClassSetPropertyFunction = Ptr Class -> Ptr Context -> Ptr () -> CString -> Ptr Value -> IO CInt
- type ClassSetPropertyFunction = Class -> Context -> Ptr () -> Text -> Value -> IO Bool
- dynamic_ClassSetPropertyFunction :: (HasCallStack, MonadIO m, IsClass a, IsContext b, IsValue c) => FunPtr C_ClassSetPropertyFunction -> a -> b -> Ptr () -> Text -> c -> m Bool
- genClosure_ClassSetPropertyFunction :: MonadIO m => ClassSetPropertyFunction -> m (GClosure C_ClassSetPropertyFunction)
- mk_ClassSetPropertyFunction :: C_ClassSetPropertyFunction -> IO (FunPtr C_ClassSetPropertyFunction)
- noClassSetPropertyFunction :: Maybe ClassSetPropertyFunction
- wrap_ClassSetPropertyFunction :: Maybe (Ptr (FunPtr C_ClassSetPropertyFunction)) -> ClassSetPropertyFunction -> C_ClassSetPropertyFunction
- type C_ExceptionHandler = Ptr Context -> Ptr Exception -> Ptr () -> IO ()
- type ExceptionHandler = Context -> Exception -> IO ()
- type ExceptionHandler_WithClosures = Context -> Exception -> Ptr () -> IO ()
- drop_closures_ExceptionHandler :: ExceptionHandler -> ExceptionHandler_WithClosures
- dynamic_ExceptionHandler :: (HasCallStack, MonadIO m, IsContext a, IsException b) => FunPtr C_ExceptionHandler -> a -> b -> Ptr () -> m ()
- genClosure_ExceptionHandler :: MonadIO m => ExceptionHandler -> m (GClosure C_ExceptionHandler)
- mk_ExceptionHandler :: C_ExceptionHandler -> IO (FunPtr C_ExceptionHandler)
- noExceptionHandler :: Maybe ExceptionHandler
- noExceptionHandler_WithClosures :: Maybe ExceptionHandler_WithClosures
- wrap_ExceptionHandler :: Maybe (Ptr (FunPtr C_ExceptionHandler)) -> ExceptionHandler_WithClosures -> C_ExceptionHandler
- type C_OptionsFunc = CString -> CUInt -> CString -> Ptr () -> IO CInt
- type OptionsFunc = Text -> OptionType -> Maybe Text -> IO Bool
- type OptionsFunc_WithClosures = Text -> OptionType -> Maybe Text -> Ptr () -> IO Bool
- drop_closures_OptionsFunc :: OptionsFunc -> OptionsFunc_WithClosures
- dynamic_OptionsFunc :: (HasCallStack, MonadIO m) => FunPtr C_OptionsFunc -> Text -> OptionType -> Maybe Text -> Ptr () -> m Bool
- genClosure_OptionsFunc :: MonadIO m => OptionsFunc -> m (GClosure C_OptionsFunc)
- mk_OptionsFunc :: C_OptionsFunc -> IO (FunPtr C_OptionsFunc)
- noOptionsFunc :: Maybe OptionsFunc
- noOptionsFunc_WithClosures :: Maybe OptionsFunc_WithClosures
- wrap_OptionsFunc :: Maybe (Ptr (FunPtr C_OptionsFunc)) -> OptionsFunc_WithClosures -> C_OptionsFunc
Signals
ClassDeletePropertyFunction
type C_ClassDeletePropertyFunction = Ptr Class -> Ptr Context -> Ptr () -> CString -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ClassDeletePropertyFunction Source #
= Class |
|
-> Context |
|
-> Ptr () |
|
-> Text |
|
-> IO Bool | Returns: |
The type of delete_property in ClassVTable
. This is only required when you need to handle
external properties not added to the prototype.
dynamic_ClassDeletePropertyFunction Source #
:: (HasCallStack, MonadIO m, IsClass a, IsContext b) | |
=> FunPtr C_ClassDeletePropertyFunction | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> Text |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ClassDeletePropertyFunction :: MonadIO m => ClassDeletePropertyFunction -> m (GClosure C_ClassDeletePropertyFunction) Source #
Wrap the callback into a GClosure
.
mk_ClassDeletePropertyFunction :: C_ClassDeletePropertyFunction -> IO (FunPtr C_ClassDeletePropertyFunction) Source #
Generate a function pointer callable from C code, from a C_ClassDeletePropertyFunction
.
noClassDeletePropertyFunction :: Maybe ClassDeletePropertyFunction Source #
A convenience synonym for
.Nothing
:: Maybe
ClassDeletePropertyFunction
wrap_ClassDeletePropertyFunction :: Maybe (Ptr (FunPtr C_ClassDeletePropertyFunction)) -> ClassDeletePropertyFunction -> C_ClassDeletePropertyFunction Source #
Wrap a ClassDeletePropertyFunction
into a C_ClassDeletePropertyFunction
.
ClassEnumeratePropertiesFunction
type C_ClassEnumeratePropertiesFunction = Ptr Class -> Ptr Context -> Ptr () -> IO (Ptr CString) Source #
Type for the callback on the (unwrapped) C side.
type ClassEnumeratePropertiesFunction Source #
= Class |
|
-> Context |
|
-> Ptr () |
|
-> IO (Maybe [Text]) | Returns: a |
The type of enumerate_properties in ClassVTable
. This is only required when you need to handle
external properties not added to the prototype.
dynamic_ClassEnumeratePropertiesFunction Source #
:: (HasCallStack, MonadIO m, IsClass a, IsContext b) | |
=> FunPtr C_ClassEnumeratePropertiesFunction | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m (Maybe [Text]) | Returns: a |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ClassEnumeratePropertiesFunction :: MonadIO m => ClassEnumeratePropertiesFunction -> m (GClosure C_ClassEnumeratePropertiesFunction) Source #
Wrap the callback into a GClosure
.
mk_ClassEnumeratePropertiesFunction :: C_ClassEnumeratePropertiesFunction -> IO (FunPtr C_ClassEnumeratePropertiesFunction) Source #
Generate a function pointer callable from C code, from a C_ClassEnumeratePropertiesFunction
.
noClassEnumeratePropertiesFunction :: Maybe ClassEnumeratePropertiesFunction Source #
A convenience synonym for
.Nothing
:: Maybe
ClassEnumeratePropertiesFunction
wrap_ClassEnumeratePropertiesFunction :: Maybe (Ptr (FunPtr C_ClassEnumeratePropertiesFunction)) -> ClassEnumeratePropertiesFunction -> C_ClassEnumeratePropertiesFunction Source #
ClassGetPropertyFunction
type C_ClassGetPropertyFunction = Ptr Class -> Ptr Context -> Ptr () -> CString -> IO (Ptr Value) Source #
Type for the callback on the (unwrapped) C side.
type ClassGetPropertyFunction Source #
= Class |
|
-> Context |
|
-> Ptr () |
|
-> Text |
|
-> IO (Maybe Value) | Returns: a |
The type of get_property in ClassVTable
. This is only required when you need to handle
external properties not added to the prototype.
dynamic_ClassGetPropertyFunction Source #
:: (HasCallStack, MonadIO m, IsClass a, IsContext b) | |
=> FunPtr C_ClassGetPropertyFunction | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> Text |
|
-> m (Maybe Value) | Returns: a |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ClassGetPropertyFunction :: MonadIO m => ClassGetPropertyFunction -> m (GClosure C_ClassGetPropertyFunction) Source #
Wrap the callback into a GClosure
.
mk_ClassGetPropertyFunction :: C_ClassGetPropertyFunction -> IO (FunPtr C_ClassGetPropertyFunction) Source #
Generate a function pointer callable from C code, from a C_ClassGetPropertyFunction
.
noClassGetPropertyFunction :: Maybe ClassGetPropertyFunction Source #
A convenience synonym for
.Nothing
:: Maybe
ClassGetPropertyFunction
wrap_ClassGetPropertyFunction :: Maybe (Ptr (FunPtr C_ClassGetPropertyFunction)) -> ClassGetPropertyFunction -> C_ClassGetPropertyFunction Source #
Wrap a ClassGetPropertyFunction
into a C_ClassGetPropertyFunction
.
ClassHasPropertyFunction
type C_ClassHasPropertyFunction = Ptr Class -> Ptr Context -> Ptr () -> CString -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ClassHasPropertyFunction Source #
= Class |
|
-> Context |
|
-> Ptr () |
|
-> Text |
|
-> IO Bool | Returns: |
The type of has_property in ClassVTable
. This is only required when you need to handle
external properties not added to the prototype.
dynamic_ClassHasPropertyFunction Source #
:: (HasCallStack, MonadIO m, IsClass a, IsContext b) | |
=> FunPtr C_ClassHasPropertyFunction | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> Text |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ClassHasPropertyFunction :: MonadIO m => ClassHasPropertyFunction -> m (GClosure C_ClassHasPropertyFunction) Source #
Wrap the callback into a GClosure
.
mk_ClassHasPropertyFunction :: C_ClassHasPropertyFunction -> IO (FunPtr C_ClassHasPropertyFunction) Source #
Generate a function pointer callable from C code, from a C_ClassHasPropertyFunction
.
noClassHasPropertyFunction :: Maybe ClassHasPropertyFunction Source #
A convenience synonym for
.Nothing
:: Maybe
ClassHasPropertyFunction
wrap_ClassHasPropertyFunction :: Maybe (Ptr (FunPtr C_ClassHasPropertyFunction)) -> ClassHasPropertyFunction -> C_ClassHasPropertyFunction Source #
Wrap a ClassHasPropertyFunction
into a C_ClassHasPropertyFunction
.
ClassSetPropertyFunction
type C_ClassSetPropertyFunction = Ptr Class -> Ptr Context -> Ptr () -> CString -> Ptr Value -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ClassSetPropertyFunction Source #
= Class |
|
-> Context |
|
-> Ptr () |
|
-> Text |
|
-> Value |
|
-> IO Bool | Returns: |
The type of set_property in ClassVTable
. This is only required when you need to handle
external properties not added to the prototype.
dynamic_ClassSetPropertyFunction Source #
:: (HasCallStack, MonadIO m, IsClass a, IsContext b, IsValue c) | |
=> FunPtr C_ClassSetPropertyFunction | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> Text |
|
-> c |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ClassSetPropertyFunction :: MonadIO m => ClassSetPropertyFunction -> m (GClosure C_ClassSetPropertyFunction) Source #
Wrap the callback into a GClosure
.
mk_ClassSetPropertyFunction :: C_ClassSetPropertyFunction -> IO (FunPtr C_ClassSetPropertyFunction) Source #
Generate a function pointer callable from C code, from a C_ClassSetPropertyFunction
.
noClassSetPropertyFunction :: Maybe ClassSetPropertyFunction Source #
A convenience synonym for
.Nothing
:: Maybe
ClassSetPropertyFunction
wrap_ClassSetPropertyFunction :: Maybe (Ptr (FunPtr C_ClassSetPropertyFunction)) -> ClassSetPropertyFunction -> C_ClassSetPropertyFunction Source #
Wrap a ClassSetPropertyFunction
into a C_ClassSetPropertyFunction
.
ExceptionHandler
type C_ExceptionHandler = Ptr Context -> Ptr Exception -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type ExceptionHandler Source #
Function used to handle JavaScript exceptions in a Context
.
type ExceptionHandler_WithClosures Source #
Function used to handle JavaScript exceptions in a Context
.
drop_closures_ExceptionHandler :: ExceptionHandler -> ExceptionHandler_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ExceptionHandler Source #
:: (HasCallStack, MonadIO m, IsContext a, IsException b) | |
=> FunPtr C_ExceptionHandler | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ExceptionHandler :: MonadIO m => ExceptionHandler -> m (GClosure C_ExceptionHandler) Source #
Wrap the callback into a GClosure
.
mk_ExceptionHandler :: C_ExceptionHandler -> IO (FunPtr C_ExceptionHandler) Source #
Generate a function pointer callable from C code, from a C_ExceptionHandler
.
noExceptionHandler :: Maybe ExceptionHandler Source #
A convenience synonym for
.Nothing
:: Maybe
ExceptionHandler
noExceptionHandler_WithClosures :: Maybe ExceptionHandler_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ExceptionHandler_WithClosures
wrap_ExceptionHandler :: Maybe (Ptr (FunPtr C_ExceptionHandler)) -> ExceptionHandler_WithClosures -> C_ExceptionHandler Source #
Wrap a ExceptionHandler
into a C_ExceptionHandler
.
OptionsFunc
type C_OptionsFunc = CString -> CUInt -> CString -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type OptionsFunc Source #
= Text |
|
-> OptionType |
|
-> Maybe Text |
|
-> IO Bool |
Function used to iterate options.
Not that description
string is not localized.
Since: 2.24
type OptionsFunc_WithClosures Source #
= Text |
|
-> OptionType |
|
-> Maybe Text |
|
-> Ptr () |
|
-> IO Bool |
Function used to iterate options.
Not that description
string is not localized.
Since: 2.24
drop_closures_OptionsFunc :: OptionsFunc -> OptionsFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_OptionsFunc | |
-> Text |
|
-> OptionType |
|
-> Maybe Text |
|
-> Ptr () |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_OptionsFunc :: MonadIO m => OptionsFunc -> m (GClosure C_OptionsFunc) Source #
Wrap the callback into a GClosure
.
mk_OptionsFunc :: C_OptionsFunc -> IO (FunPtr C_OptionsFunc) Source #
Generate a function pointer callable from C code, from a C_OptionsFunc
.
noOptionsFunc :: Maybe OptionsFunc Source #
A convenience synonym for
.Nothing
:: Maybe
OptionsFunc
noOptionsFunc_WithClosures :: Maybe OptionsFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
OptionsFunc_WithClosures
wrap_OptionsFunc :: Maybe (Ptr (FunPtr C_OptionsFunc)) -> OptionsFunc_WithClosures -> C_OptionsFunc Source #
Wrap a OptionsFunc
into a C_OptionsFunc
.