module Marvin.Internal.Types where
import Control.DeepSeq
import Control.Lens
import Control.Monad.Base
import Control.Monad.IO.Class
import Control.Monad.Logger
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.Trans.Control
import Data.Char (isAlphaNum, isLetter)
import qualified Data.Configurator.Types as C
import qualified Data.HashMap.Strict as HM
import Data.Monoid
import Data.String
import qualified Data.Text as T
import qualified Data.Text.Lazy as L
import Data.Time.Clock
import Data.Vector (Vector)
import GHC.Generics
import Marvin.Interpolate.String
import Marvin.Interpolate.Text
import Marvin.Util.Regex
type Topic = L.Text
type Message = L.Text
newtype TimeStamp = TimeStamp { unwrapTimeStamp :: UTCTime } deriving Show
data Event a
= MessageEvent (User a) (Channel a) Message TimeStamp
| CommandEvent (User a) (Channel a) Message TimeStamp
| ChannelJoinEvent (User a) (Channel a) TimeStamp
| ChannelLeaveEvent (User a) (Channel a) TimeStamp
| TopicChangeEvent (User a) (Channel a) Topic TimeStamp
type RunnerM = LoggingT IO
newtype AdapterM a r = AdapterM { runAdapterAction :: ReaderT (C.Config, a) RunnerM r } deriving (MonadIO, Monad, Applicative, Functor, MonadLogger, MonadLoggerIO, MonadBase IO)
type EventHandler a = Event a -> IO ()
type RunWithAdapter a = EventHandler a -> AdapterM a ()
class IsAdapter a where
type User a
type Channel a
adapterId :: AdapterId a
messageChannel :: Channel a -> L.Text -> AdapterM a ()
initAdapter :: RunnerM a
runWithAdapter :: RunWithAdapter a
getUsername :: User a -> AdapterM a L.Text
getChannelName :: Channel a -> AdapterM a L.Text
resolveChannel :: L.Text -> AdapterM a (Maybe (Channel a))
resolveUser :: L.Text -> AdapterM a (Maybe (User a))
newtype User' a = User' {unwrapUser' :: User a}
newtype Channel' a = Channel' {unwrapChannel' :: Channel a}
newtype ScriptId = ScriptId { unwrapScriptId :: T.Text } deriving (Show, Eq)
newtype AdapterId a = AdapterId { unwrapAdapterId :: T.Text } deriving (Show, Eq)
class HasScriptId s a | s -> a where
scriptId :: Lens' s a
declareFields [d|
data BotActionState a d = BotActionState
{ botActionStateScriptId :: ScriptId
, botActionStateConfig :: C.Config
, botActionStateAdapter :: a
, botActionStatePayload :: d
}
|]
declareFields [d|
data Handlers a = Handlers
{ handlersResponds :: Vector (Regex, (User' a, Channel' a, Match, Message, TimeStamp) -> RunnerM ())
, handlersHears :: Vector (Regex, (User' a, Channel' a, Match, Message, TimeStamp) -> RunnerM ())
, handlersCustoms :: Vector (Event a -> Maybe (RunnerM ()))
, handlersJoins :: Vector ((User' a, Channel' a, TimeStamp) -> RunnerM ())
, handlersLeaves :: Vector ((User' a, Channel' a, TimeStamp) -> RunnerM ())
, handlersTopicChange :: Vector ((User' a, Channel' a, Topic, TimeStamp) -> RunnerM ())
, handlersJoinsIn :: HM.HashMap L.Text (Vector ((User' a, Channel' a, TimeStamp) -> RunnerM ()))
, handlersLeavesFrom :: HM.HashMap L.Text (Vector ((User' a, Channel' a, TimeStamp) -> RunnerM ()))
, handlersTopicChangeIn :: HM.HashMap L.Text (Vector ((User' a, Channel' a, Topic, TimeStamp) -> RunnerM ()))
} deriving Generic
|]
instance NFData (Handlers a)
instance Monoid (Handlers a) where
mempty = Handlers mempty mempty mempty mempty mempty mempty mempty mempty mempty
mappend (Handlers r1 h1 c1 j1 l1 t1 ji1 li1 ti1)
(Handlers r2 h2 c2 j2 l2 t2 ji2 li2 ti2)
= Handlers (r1 <> r2) (h1 <> h2) (c1 <> c2) (j1 <> j2) (l1 <> l2) (t1 <> t2) (HM.unionWith mappend ji1 ji2) (HM.unionWith mappend li1 li2) (HM.unionWith mappend ti1 ti2)
newtype BotReacting a d r = BotReacting { runReaction :: ReaderT (BotActionState a d) RunnerM r } deriving (Monad, MonadIO, Applicative, Functor, MonadReader (BotActionState a d), MonadLogger, MonadLoggerIO, MonadBase IO)
declareFields [d|
data Script a = Script
{ scriptActions :: Handlers a
, scriptScriptId :: ScriptId
, scriptConfig :: C.Config
, scriptAdapter :: a
}
|]
newtype ScriptDefinition a r = ScriptDefinition { runScript :: StateT (Script a) RunnerM r } deriving (Monad, MonadIO, Applicative, Functor, MonadLogger, MonadBase IO)
newtype ScriptInit a = ScriptInit (ScriptId, a -> C.Config -> RunnerM (Script a))
instance MonadBaseControl IO (AdapterM a) where
type StM (AdapterM a) r = r
liftBaseWith f = AdapterM $ liftBaseWith $ \q -> f (q . runAdapterAction)
restoreM = AdapterM . restoreM
class Get a b where
getLens :: Lens' a b
instance Get (User' a, b, c) (User' a) where
getLens = _1
instance Get (User' a, b, c, d) (User' a) where
getLens = _1
instance Get (User' a, b, c, d, e) (User' a) where
getLens = _1
instance Get (a, Channel' b, c) (Channel' b) where
getLens = _2
instance Get (a, Channel' b, c, d) (Channel' b) where
getLens = _2
instance Get (a, Channel' b, c, d, e) (Channel' b) where
getLens = _2
instance Get (a, b, TimeStamp) TimeStamp where
getLens = _3
instance Get (a, b, c, TimeStamp) TimeStamp where
getLens = _4
instance Get (a, b, c, d, TimeStamp) TimeStamp where
getLens = _5
instance Get (a, b, Match, d, e) Match where
getLens = _3
instance Get (a, b, c, Message, e) Message where
getLens = _4
instance Get (a, b, Topic, d) Topic where
getLens = _3
instance HasConfigAccess (ScriptDefinition a) where
getConfigInternal = ScriptDefinition $ use config
instance HasConfigAccess (BotReacting a b) where
getConfigInternal = view config
class IsScript m where
getScriptId :: m ScriptId
instance IsScript (ScriptDefinition a) where
getScriptId = ScriptDefinition $ use scriptId
instance IsScript (BotReacting a b) where
getScriptId = view scriptId
class AccessAdapter m where
type AdapterT m
getAdapter :: m (AdapterT m)
instance AccessAdapter (ScriptDefinition a) where
type AdapterT (ScriptDefinition a) = a
getAdapter = ScriptDefinition $ use adapter
instance AccessAdapter (BotReacting a b) where
type AdapterT (BotReacting a b) = a
getAdapter = view adapter
instance AccessAdapter (AdapterM a) where
type AdapterT (AdapterM a) = a
getAdapter = AdapterM $ snd <$> ask
instance ShowT ScriptId where showT = unwrapScriptId
instance ShowT (AdapterId a) where showT = unwrapAdapterId
type LoggingFn = Loc -> LogSource -> LogLevel -> LogStr -> IO ()
verifyIdString :: String -> (T.Text -> a) -> T.Text -> Either String a
verifyIdString name _ "" = Left $(isS "#{name} must not be empty")
verifyIdString name f s
| isLetter x && T.all (\c -> isAlphaNum c || c == '-' || c == '_' ) xs = Right $ f s
| otherwise = Left $(isS "first character of #{name} must be a letter, all other characters can be alphanumeric, '-' or '_'")
where Just (x, xs) = T.uncons s
instance IsString ScriptId where
fromString = either error id . verifyIdString "script id" ScriptId . fromString
instance IsString (AdapterId a) where
fromString = either error id . verifyIdString "adapter id" AdapterId . fromString
mkScriptId :: T.Text -> Either String ScriptId
mkScriptId = verifyIdString "script id" ScriptId
mkAdapterId :: T.Text -> Either String (AdapterId a)
mkAdapterId = verifyIdString "adapter id" AdapterId
class (IsScript m, MonadIO m) => HasConfigAccess m where
getConfigInternal :: m C.Config
instance C.Configured LogLevel where
convert (C.String s) =
case T.strip $ T.toLower s of
"debug" -> Just LevelDebug
"warning" -> Just LevelWarn
"error" -> Just LevelError
"info" -> Just LevelInfo
_ -> Nothing
convert _ = Nothing