module Marvin.Internal
(
defineScript
, hear, respond, topic, topicIn, enter, exit, enterIn, exitFrom, customTrigger
, send, reply, messageChannel, messageChannel'
, getData, getUser, getMatch, getMessage, getChannel, getTopic, getBotName, getChannelName, resolveChannel, getUsername, resolveUser
, getConfigVal, requireConfigVal
, getAppConfigVal, requireAppConfigVal, getConfig, getConfigInternal
, Topic
, extractAction, extractReaction
, defaultBotName
, runDefinitions
, BotActionState(BotActionState)
, BotReacting(..), Script(..), ScriptDefinition(..), ScriptInit(..), ScriptId(..), Handlers(..)
, HasActions(actions), HasHears(hears), HasResponds(responds), HasJoins(joins), HasCustoms(customs), HasJoinsIn(joinsIn), HasLeaves(leaves), HasLeavesFrom(leavesFrom), HasTopicChange(topicChange), HasTopicChangeIn(topicChangeIn)
, AccessAdapter(AdapterT, getAdapter), Get(getLens)
) where
import Control.Exception.Lifted
import Control.Lens hiding (cons)
import Control.Monad.Logger
import Control.Monad.Reader
import Control.Monad.State
import qualified Data.Configurator as C
import qualified Data.Configurator.Types as C
import qualified Data.HashMap.Strict as HM
import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
import qualified Data.Text as T
import qualified Data.Text.Lazy as L
import Data.Vector (Vector)
import qualified Data.Vector as V
import Marvin.Adapter (IsAdapter)
import qualified Marvin.Adapter as A
import Marvin.Internal.Types hiding (getChannelName, getUsername, messageChannel,
resolveChannel, resolveChannel, resolveUser)
import Marvin.Internal.Values
import Marvin.Interpolate.String
import Marvin.Interpolate.Text
import Marvin.Util.Regex (Match, Regex)
import Util
getSubConfFor :: HasConfigAccess m => ScriptId -> m C.Config
getSubConfFor (ScriptId name) = C.subconfig $(isT "#{scriptConfigKey}.#{name}") <$> getConfigInternal
getConfig :: HasConfigAccess m => m C.Config
getConfig = getScriptId >>= getSubConfFor
runBotAction :: ShowT t => ScriptId -> C.Config -> a -> Maybe t -> d -> BotReacting a d () -> RunnerM ()
runBotAction scriptId config adapter trigger data_ action = do
oldLogFn <- askLoggerIO
catch
(liftIO $ flip runLoggingT (loggingAddSourcePrefix $(isT "#{scriptConfigKey}.#{scriptId}") oldLogFn) $ flip runReaderT actionState $ runReaction action)
(onScriptExcept scriptId trigger)
where
actionState = BotActionState scriptId config adapter data_
prepareAction :: (MonadState (Script a) m, ShowT t) => Maybe t -> BotReacting a d () -> m (d -> RunnerM ())
prepareAction trigger reac = do
ada <- use adapter
cfg <- use config
sid <- use scriptId
return $ \d -> runBotAction sid cfg ada trigger d reac
onScriptExcept :: ShowT t => ScriptId -> Maybe t -> SomeException -> RunnerM ()
onScriptExcept id trigger e = do
case trigger of
Just t ->
err $(isT "Unhandled exception during execution of script \"#{id}\" with trigger \"#{t}\"")
Nothing ->
err $(isT "Unhandled exception during execution of script \"#{id}\"")
err $(isT "#{e}")
where
err = logErrorNS $(isT "#{applicationScriptId}.dispatch")
hear :: Regex -> BotReacting a (User' a, Channel' a, Match, Message, TimeStamp) () -> ScriptDefinition a ()
hear !re ac = ScriptDefinition $ do
pac <- prepareAction (Just re) ac
actions . hears %= V.cons (re, pac)
respond :: Regex -> BotReacting a (User' a, Channel' a, Match, Message, TimeStamp) () -> ScriptDefinition a ()
respond !re ac = ScriptDefinition $ do
pac <- prepareAction (Just re) ac
actions . responds %= V.cons (re, pac)
enter :: BotReacting a (User' a, Channel' a, TimeStamp) () -> ScriptDefinition a ()
enter ac = ScriptDefinition $ do
pac <- prepareAction (Just "enter event" :: Maybe T.Text) ac
actions . joins %= V.cons pac
exit :: BotReacting a (User' a, Channel' a, TimeStamp) () -> ScriptDefinition a ()
exit ac = ScriptDefinition $ do
pac <- prepareAction (Just "exit event" :: Maybe T.Text) ac
actions . leaves %= V.cons pac
alterHelper :: a -> Maybe (Vector a) -> Maybe (Vector a)
alterHelper v = return . maybe (return v) (V.cons v)
enterIn :: L.Text -> BotReacting a (User' a, Channel' a, TimeStamp) () -> ScriptDefinition a ()
enterIn !chanName ac = ScriptDefinition $ do
pac <- prepareAction (Just $(isT "enter event in #{chanName}")) ac
actions . joinsIn %= HM.alter (alterHelper pac) chanName
exitFrom :: L.Text -> BotReacting a (User' a, Channel' a, TimeStamp) () -> ScriptDefinition a ()
exitFrom !chanName ac = ScriptDefinition $ do
pac <- prepareAction (Just $(isT "exit event in #{chanName}")) ac
actions . leavesFrom %= HM.alter (alterHelper pac) chanName
topic :: BotReacting a (User' a, Channel' a, Topic, TimeStamp) () -> ScriptDefinition a ()
topic ac = ScriptDefinition $ do
pac <- prepareAction (Just "topic event" :: Maybe T.Text) ac
actions . topicChange %= V.cons pac
topicIn :: L.Text -> BotReacting a (User' a, Channel' a, Topic, TimeStamp) () -> ScriptDefinition a ()
topicIn !chanName ac = ScriptDefinition $ do
pac <- prepareAction (Just $(isT "topic event in #{chanName}")) ac
actions . topicChangeIn %= HM.alter (alterHelper pac) chanName
customTrigger :: (Event a -> Maybe d) -> BotReacting a d () -> ScriptDefinition a ()
customTrigger tr ac = ScriptDefinition $ do
pac <- prepareAction (Nothing :: Maybe T.Text) ac
actions . customs %= V.cons (maybe Nothing (return . pac) . tr)
send :: (IsAdapter a, Get d (Channel' a)) => L.Text -> BotReacting a d ()
send msg = do
o <- getChannel
messageChannel' o msg
getUsername :: (HasConfigAccess m, AccessAdapter m, IsAdapter a, MonadIO m, AdapterT m ~ a)
=> User a -> m L.Text
getUsername = A.liftAdapterAction . A.getUsername
resolveChannel :: (HasConfigAccess m, AccessAdapter m, IsAdapter a, MonadIO m, AdapterT m ~ a)
=> L.Text -> m (Maybe (Channel a))
resolveChannel = A.liftAdapterAction . A.resolveChannel
getChannelName :: (HasConfigAccess m, AccessAdapter m, IsAdapter a, MonadIO m, AdapterT m ~ a)
=> Channel a -> m L.Text
getChannelName = A.liftAdapterAction . A.getChannelName
resolveUser :: (HasConfigAccess m, AccessAdapter m, IsAdapter a, MonadIO m, AdapterT m ~ a)
=> L.Text -> m (Maybe (User a))
resolveUser = A.liftAdapterAction . A.resolveUser
reply :: (IsAdapter a, Get d (User' a), Get d (Channel' a)) => L.Text -> BotReacting a d ()
reply msg = do
chan <- getChannel
user <- getUser >>= getUsername
messageChannel' chan $ user <> " " <> msg
messageChannel :: (HasConfigAccess m, AccessAdapter m, IsAdapter (AdapterT m), MonadLoggerIO m) => L.Text -> L.Text -> m ()
messageChannel name msg = do
mchan <- resolveChannel name
maybe ($logError $(isT "No channel known with the name #{name}")) (`messageChannel'` msg) mchan
messageChannel' :: (HasConfigAccess m, AccessAdapter m, IsAdapter (AdapterT m), MonadIO m) => Channel (AdapterT m) -> L.Text -> m ()
messageChannel' chan = A.liftAdapterAction . A.messageChannel chan
defineScript :: ScriptId -> ScriptDefinition a () -> ScriptInit a
defineScript sid definitions =
ScriptInit (sid, runDefinitions sid definitions)
runDefinitions :: ScriptId -> ScriptDefinition a () -> a -> C.Config -> RunnerM (Script a)
runDefinitions sid definitions ada cfg = execStateT (runScript definitions) (Script mempty sid cfg ada)
getData :: BotReacting a d d
getData = view payload
getMatch :: Get m Match => BotReacting a m Match
getMatch = view (payload . getLens)
getMessage :: Get m Message => BotReacting a m Message
getMessage = view (payload . getLens)
getTopic :: Get m Topic => BotReacting a m Topic
getTopic = view (payload . getLens)
getChannel :: forall a m. Get m (Channel' a) => BotReacting a m (Channel a)
getChannel = (unwrapChannel' :: Channel' a -> Channel a) <$> view (payload . getLens)
getUser :: forall m a. Get m (User' a) => BotReacting a m (User a)
getUser = (unwrapUser' :: User' a -> User a) <$> view (payload . getLens)
getConfigVal :: (C.Configured a, HasConfigAccess m) => C.Name -> m (Maybe a)
getConfigVal name = do
cfg <- getConfig
liftIO $ C.lookup cfg name
requireConfigVal :: (C.Configured a, HasConfigAccess m) => C.Name -> m a
requireConfigVal name = do
cfg <- getConfig
l <- liftIO $ C.lookup cfg name
case l of
Just v -> return v
_ -> do
sid <- getScriptId
error $(isS "Could not find required config value \"#{name}\" in script \"#{sid}\"")
getAppConfig :: HasConfigAccess m => m C.Config
getAppConfig = getSubConfFor applicationScriptId
getAppConfigVal :: (C.Configured a, HasConfigAccess m) => C.Name -> m (Maybe a)
getAppConfigVal name = do
cfg <- getAppConfig
liftIO $ C.lookup cfg name
requireAppConfigVal :: (C.Configured a, HasConfigAccess m) => C.Name -> m a
requireAppConfigVal name = do
cfg <- getAppConfig
liftIO $ C.require cfg name
getBotName :: HasConfigAccess m => m L.Text
getBotName = fromMaybe defaultBotName <$> getAppConfigVal "name"
extractReaction :: BotReacting a s o -> BotReacting a s (IO o)
extractReaction reac = BotReacting $
runStderrLoggingT . runReaderT (runReaction reac) <$> ask
extractAction :: BotReacting a () o -> ScriptDefinition a (IO o)
extractAction ac = ScriptDefinition $
fmap (runStderrLoggingT . runReaderT (runReaction ac)) $
BotActionState <$> use scriptId <*> use config <*> use adapter <*> pure ()