Copyright | (c) Eric Mertens 2016 |
---|---|
License | ISC |
Maintainer | emertens@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
Marshaling types and functions for the C API
Synopsis
- data FgnExtension = FgnExtension {}
- type StartExtension = Ptr () -> CString -> Ptr FgnStringLen -> CSize -> IO (Ptr ())
- type StopExtension = Ptr () -> IO ()
- type ProcessMessage = Ptr () -> Ptr FgnMsg -> IO ProcessResult
- type ProcessCommand = Ptr () -> Ptr FgnCmd -> IO ()
- type ProcessChat = Ptr () -> Ptr FgnChat -> IO ProcessResult
- type TimerCallback = Ptr () -> TimerId -> IO ()
- type TimerId = Int64
- data FgnStringLen = FgnStringLen !CString !CSize
- data FgnMsg = FgnMsg {}
- data FgnCmd = FgnCmd {}
- data FgnChat = FgnChat {}
- type Dynamic a = FunPtr a -> a
- runStartExtension :: Dynamic StartExtension
- runStopExtension :: Dynamic StopExtension
- runProcessMessage :: Dynamic ProcessMessage
- runProcessCommand :: Dynamic ProcessCommand
- runProcessChat :: Dynamic ProcessChat
- runTimerCallback :: Dynamic TimerCallback
- newtype MessageCode = MessageCode Word32
- normalMessage :: MessageCode
- errorMessage :: MessageCode
- newtype ProcessResult = ProcessResult Word32
- passMessage :: ProcessResult
- dropMessage :: ProcessResult
- withText0 :: Text -> (CStringLen -> IO a) -> IO a
- exportText :: Ptr CString -> Ptr CSize -> Text -> IO ()
- poke' :: Storable a => Ptr a -> a -> IO ()
Extension record
data FgnExtension Source #
Information describing an extension's entry-points and metadata.
FgnExtension | |
|
Instances
Storable FgnExtension Source # | struct glirc_extension |
Defined in Client.CApi.Types sizeOf :: FgnExtension -> Int # alignment :: FgnExtension -> Int # peekElemOff :: Ptr FgnExtension -> Int -> IO FgnExtension # pokeElemOff :: Ptr FgnExtension -> Int -> FgnExtension -> IO () # peekByteOff :: Ptr b -> Int -> IO FgnExtension # pokeByteOff :: Ptr b -> Int -> FgnExtension -> IO () # peek :: Ptr FgnExtension -> IO FgnExtension # poke :: Ptr FgnExtension -> FgnExtension -> IO () # |
type StartExtension Source #
= Ptr () | api token |
-> CString | path to extension |
-> Ptr FgnStringLen | array of arguments |
-> CSize | number of arguments |
-> IO (Ptr ()) | initialized extension state |
typedef void *start(void *glirc, const char *path)
type StopExtension Source #
typedef void stop(void *glirc, void *S)
type ProcessMessage Source #
= Ptr () | extention state |
-> Ptr FgnMsg | message to send |
-> IO ProcessResult |
typedef enum process_result process_message(void *glirc, void *S, const struct glirc_message *)
type ProcessCommand Source #
typedef void process_command(void *glirc, void *S, const struct glirc_command *)
type ProcessChat Source #
= Ptr () | extension state |
-> Ptr FgnChat | chat info |
-> IO ProcessResult |
typedef void process_chat(void *glirc, void *S, const struct glirc_chat *)
type TimerCallback Source #
Callback function when timer triggers
Strings
data FgnStringLen Source #
Pointer to UTF-8 encoded string and as string length. Strings are null-terminated. The null-terminator is not counted in the length.
Instances
Storable FgnStringLen Source # | struct glirc_string |
Defined in Client.CApi.Types sizeOf :: FgnStringLen -> Int # alignment :: FgnStringLen -> Int # peekElemOff :: Ptr FgnStringLen -> Int -> IO FgnStringLen # pokeElemOff :: Ptr FgnStringLen -> Int -> FgnStringLen -> IO () # peekByteOff :: Ptr b -> Int -> IO FgnStringLen # pokeByteOff :: Ptr b -> Int -> FgnStringLen -> IO () # peek :: Ptr FgnStringLen -> IO FgnStringLen # poke :: Ptr FgnStringLen -> FgnStringLen -> IO () # |
Messages
struct glirc_message
FgnMsg | |
|
Commands
Used to pass arguments from /extension EXT_NAME
client command into
an extension.
Instances
Storable FgnCmd Source # | struct glirc_command |
Chat
Chat message data containing the source network, window target, and message body.
Instances
Storable FgnChat Source # | struct glirc_message |
Function pointer calling
type Dynamic a = FunPtr a -> a Source #
Type of dynamic function pointer wrappers. These convert C function-pointers into Haskell functions.
runStartExtension :: Dynamic StartExtension Source #
Dynamic import for StartExtension
.
runStopExtension :: Dynamic StopExtension Source #
Dynamic import for StopExtension
.
runProcessMessage :: Dynamic ProcessMessage Source #
Dynamic import for ProcessMessage
.
runProcessCommand :: Dynamic ProcessCommand Source #
Dynamic import for ProcessCommand
.
runProcessChat :: Dynamic ProcessChat Source #
Dynamic import for ProcessChat
.
runTimerCallback :: Dynamic TimerCallback Source #
Dynamic import for timer callback
report message codes
newtype MessageCode Source #
Tag for describing the kind of message to display in the client
as used in glirc_print
. See normalMessage
and errorMessage
.
enum message_code;
Instances
Eq MessageCode Source # | |
Defined in Client.CApi.Types (==) :: MessageCode -> MessageCode -> Bool # (/=) :: MessageCode -> MessageCode -> Bool # |
normalMessage :: MessageCode Source #
Normal client message. Unread counter increments, but no client bell or error status update.
errorMessage :: MessageCode Source #
Important client message. Unread counter increments, bell rings, and error status updates.
process message results
newtype ProcessResult Source #
Result used to determine what to do after processing a message with
the ProcessMessage
callback.
| enum process_result
Instances
Eq ProcessResult Source # | |
Defined in Client.CApi.Types (==) :: ProcessResult -> ProcessResult -> Bool # (/=) :: ProcessResult -> ProcessResult -> Bool # |
passMessage :: ProcessResult Source #
Allow the message to proceed through the client logic.
dropMessage :: ProcessResult Source #
Drop the message from further processing.
Marshaling helpers
withText0 :: Text -> (CStringLen -> IO a) -> IO a Source #
Marshal a text as a temporary null-terminated CStringLen