Copyright | (c) Eric Mertens 2016 |
---|---|
License | ISC |
Maintainer | emertens@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Client.CApi
Description
Foreign interface to the IRC client via a simple C API and dynamically loaded modules.
Synopsis
- data ActiveExtension = ActiveExtension {
- aeFgn :: !FgnExtension
- aeDL :: !DL
- aeSession :: !(Ptr ())
- aeName :: !Text
- aeMajorVersion, aeMinorVersion :: !Int
- aeTimers :: !(IntPSQ UTCTime TimerEntry)
- aeNextTimer :: !Int
- aeThreads :: !Int
- aeLive :: !Bool
- extensionSymbol :: String
- openExtension :: ExtensionConfiguration -> IO ActiveExtension
- startExtension :: Ptr () -> ExtensionConfiguration -> ActiveExtension -> IO (Ptr ())
- stopExtension :: ActiveExtension -> IO ()
- notifyExtension :: ActiveExtension -> Ptr FgnMsg -> IO Bool
- commandExtension :: Text -> ActiveExtension -> IO ()
- chatExtension :: ActiveExtension -> Ptr FgnChat -> IO Bool
- data ThreadEntry = ThreadEntry !(FunPtr ThreadFinish) !(Ptr ())
- threadFinish :: ThreadEntry -> IO ()
- popTimer :: ActiveExtension -> Maybe (UTCTime, TimerId, FunPtr TimerCallback, Ptr (), ActiveExtension)
- pushTimer :: UTCTime -> FunPtr TimerCallback -> Ptr () -> ActiveExtension -> (Int, ActiveExtension)
- cancelTimer :: Int -> ActiveExtension -> Maybe (Ptr (), ActiveExtension)
- evalNestedIO :: NestedIO a -> IO a
- withChat :: Text -> Text -> Text -> NestedIO (Ptr FgnChat)
- withRawIrcMsg :: Text -> RawIrcMsg -> NestedIO (Ptr FgnMsg)
Extension type
data ActiveExtension Source #
Information about a loaded extension including the handle to the loaded shared object, and state value returned by the startup callback, and the loaded extension record.
Constructors
ActiveExtension | |
Fields
|
Extension callbacks
extensionSymbol :: String Source #
The symbol that is loaded from an extension object.
Extensions are expected to export:
struct galua_extension extension;
Arguments
:: ExtensionConfiguration | extension configuration |
-> IO ActiveExtension |
Load the extension from the given path and call the start callback. The result of the start callback is saved to be passed to any subsequent calls into the extension.
Arguments
:: Ptr () | client stable pointer |
-> ExtensionConfiguration | extension configuration |
-> ActiveExtension | active extension |
-> IO (Ptr ()) | extension state |
stopExtension :: ActiveExtension -> IO () Source #
Arguments
:: ActiveExtension | extension |
-> Ptr FgnMsg | serialized IRC message |
-> IO Bool | allow message |
Call all of the process message callbacks in the list of extensions. This operation marshals the IRC message once and shares that across all of the callbacks.
Returns True
to pass message to client. Returns 'False to drop message.
Arguments
:: Text | command |
-> ActiveExtension | extension to command |
-> IO () |
Notify an extension of a client command with the given parameters.
Arguments
:: ActiveExtension | extension |
-> Ptr FgnChat | serialized chat message |
-> IO Bool | allow message |
Call all of the process chat callbacks in the list of extensions. This operation marshals the IRC message once and shares that across all of the callbacks.
Returns True
to pass message to client. Returns 'False to drop message.
data ThreadEntry Source #
Constructors
ThreadEntry !(FunPtr ThreadFinish) !(Ptr ()) |
threadFinish :: ThreadEntry -> IO () Source #
Notify an extension that one of its threads has finished.
Arguments
:: ActiveExtension | extension |
-> Maybe (UTCTime, TimerId, FunPtr TimerCallback, Ptr (), ActiveExtension) | earlier time, callback, callback state, updated extension |
Find the earliest timer ready to run if any are available.
Arguments
:: UTCTime | activation time |
-> FunPtr TimerCallback | callback function |
-> Ptr () | callback state |
-> ActiveExtension | extension |
-> (Int, ActiveExtension) |
Schedue a new timer event for the given extension.
Arguments
:: Int | timer ID |
-> ActiveExtension | extension |
-> Maybe (Ptr (), ActiveExtension) |
Remove a timer from the schedule by ID
evalNestedIO :: NestedIO a -> IO a Source #
Return the bracket IO action.