{-# Language GeneralizedNewtypeDeriving, RankNTypes, RecordWildCards #-}
module Client.CApi
(
ActiveExtension(..)
, extensionSymbol
, openExtension
, startExtension
, deactivateExtension
, notifyExtension
, commandExtension
, chatExtension
, popTimer
, pushTimer
, cancelTimer
, evalNestedIO
, withChat
, withRawIrcMsg
) where
import Client.Configuration
(ExtensionConfiguration,
extensionPath, extensionRtldFlags, extensionArgs)
import Client.CApi.Types
import Control.Lens (view)
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Codensity
import Data.IntPSQ (IntPSQ)
import qualified Data.IntPSQ as IntPSQ
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Time
import Foreign.C
import Foreign.Marshal
import Foreign.Ptr
import Foreign.Storable
import Irc.Identifier
import Irc.RawIrcMsg
import Irc.UserInfo
import System.Posix.DynamicLinker
extensionSymbol :: String
extensionSymbol = "extension"
data ActiveExtension = ActiveExtension
{ aeFgn :: !FgnExtension
, aeDL :: !DL
, aeSession :: !(Ptr ())
, aeName :: !Text
, aeMajorVersion, aeMinorVersion :: !Int
, aeTimers :: !(IntPSQ UTCTime TimerEntry)
, aeNextTimer :: !Int
}
data TimerEntry = TimerEntry !(FunPtr TimerCallback) !(Ptr ())
popTimer ::
ActiveExtension ->
Maybe (UTCTime, TimerId, FunPtr TimerCallback, Ptr (), ActiveExtension)
popTimer ae =
do let timers = aeTimers ae
(timerId, time, TimerEntry fun ptr, timers') <- IntPSQ.minView timers
let ae' = ae { aeTimers = timers' }
return (time, fromIntegral timerId, fun, ptr, ae')
pushTimer ::
UTCTime ->
FunPtr TimerCallback ->
Ptr () ->
ActiveExtension ->
(Int,ActiveExtension)
pushTimer time fun ptr ae = entry `seq` ae' `seq` (i, ae')
where
entry = TimerEntry fun ptr
i = aeNextTimer ae
ae' = ae { aeTimers = IntPSQ.insert i time entry (aeTimers ae)
, aeNextTimer = i + 1 }
cancelTimer ::
Int ->
ActiveExtension ->
Maybe (Ptr (), ActiveExtension)
cancelTimer timerId ae =
do (_, TimerEntry _ ptr) <- IntPSQ.lookup timerId (aeTimers ae)
return (ptr, ae { aeTimers = IntPSQ.delete timerId (aeTimers ae)})
openExtension ::
ExtensionConfiguration ->
IO ActiveExtension
openExtension config =
do dl <- dlopen (view extensionPath config)
(view extensionRtldFlags config)
p <- dlsym dl extensionSymbol
fgn <- peek (castFunPtrToPtr p)
name <- peekCString (fgnName fgn)
return $! ActiveExtension
{ aeFgn = fgn
, aeDL = dl
, aeSession = nullPtr
, aeName = Text.pack name
, aeTimers = IntPSQ.empty
, aeMajorVersion = fromIntegral (fgnMajorVersion fgn)
, aeMinorVersion = fromIntegral (fgnMinorVersion fgn)
, aeNextTimer = 1
}
startExtension ::
Ptr () ->
ExtensionConfiguration ->
ActiveExtension ->
IO (Ptr ())
startExtension stab config ae =
do let f = fgnStart (aeFgn ae)
if nullFunPtr == f
then return nullPtr
else evalNestedIO $
do extPath <- nest1 (withCString (view extensionPath config))
args <- traverse withText
$ view extensionArgs config
argsArray <- nest1 (withArray args)
let len = fromIntegral (length args)
liftIO (runStartExtension f stab extPath argsArray len)
deactivateExtension :: ActiveExtension -> IO ()
deactivateExtension ae =
do let f = fgnStop (aeFgn ae)
unless (nullFunPtr == f) $
runStopExtension f (aeSession ae)
dlclose (aeDL ae)
chatExtension ::
ActiveExtension ->
Ptr FgnChat ->
IO Bool
chatExtension ae chat =
do let f = fgnChat (aeFgn ae)
if f == nullFunPtr
then return True
else (passMessage ==) <$> runProcessChat f (aeSession ae) chat
notifyExtension ::
ActiveExtension ->
Ptr FgnMsg ->
IO Bool
notifyExtension ae msg =
do let f = fgnMessage (aeFgn ae)
if f == nullFunPtr
then return True
else (passMessage ==) <$> runProcessMessage f (aeSession ae) msg
commandExtension ::
Text ->
ActiveExtension ->
IO ()
commandExtension command ae = evalNestedIO $
do cmd <- withCommand command
let f = fgnCommand (aeFgn ae)
liftIO $ unless (f == nullFunPtr)
$ runProcessCommand f (aeSession ae) cmd
withRawIrcMsg ::
Text ->
RawIrcMsg ->
NestedIO (Ptr FgnMsg)
withRawIrcMsg network RawIrcMsg{..} =
do net <- withText network
pfxN <- withText $ maybe Text.empty (idText.userNick) _msgPrefix
pfxU <- withText $ maybe Text.empty userName _msgPrefix
pfxH <- withText $ maybe Text.empty userHost _msgPrefix
cmd <- withText _msgCommand
prms <- traverse withText _msgParams
tags <- traverse withTag _msgTags
let (keys,vals) = unzip tags
(tagN,keysPtr) <- nest2 $ withArrayLen keys
valsPtr <- nest1 $ withArray vals
(prmN,prmPtr) <- nest2 $ withArrayLen prms
nest1 $ with $ FgnMsg net pfxN pfxU pfxH cmd prmPtr (fromIntegral prmN)
keysPtr valsPtr (fromIntegral tagN)
withChat ::
Text ->
Text ->
Text ->
NestedIO (Ptr FgnChat)
withChat net tgt msg =
do net' <- withText net
tgt' <- withText tgt
msg' <- withText msg
nest1 $ with $ FgnChat net' tgt' msg'
withCommand ::
Text ->
NestedIO (Ptr FgnCmd)
withCommand command =
do cmd <- withText command
nest1 $ with $ FgnCmd cmd
withTag :: TagEntry -> NestedIO (FgnStringLen, FgnStringLen)
withTag (TagEntry k v) =
do pk <- withText k
pv <- withText v
return (pk,pv)
withText :: Text -> NestedIO FgnStringLen
withText txt =
do (ptr,len) <- nest1 $ withText0 txt
return $ FgnStringLen ptr $ fromIntegral len
newtype NestedIO a = NestedIO (Codensity IO a)
deriving (Functor, Applicative, Monad, MonadIO)
evalNestedIO :: NestedIO a -> IO a
evalNestedIO (NestedIO m) = lowerCodensity m
nest1 :: (forall r. (a -> IO r) -> IO r) -> NestedIO a
nest1 f = NestedIO (Codensity f)
nest2 :: (forall r. (a -> b -> IO r) -> IO r) -> NestedIO (a,b)
nest2 f = NestedIO (Codensity (f . curry))