habit-0.2.2.0: Haskell message bot framework

CopyrightAlexander Krupenkin 2016
LicenseBSD3
Maintaineremail@something.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Web.Bot

Contents

Description

Text message bot framework for creating story like:

     helloStory :: BotConfig a => Story a
     helloStory _ = hello $ question "How your name?"
                          * question "How your surname?"
                          * question "How old are you?"

Synopsis

Story & message types

class ToMessage a where Source #

Convert any data to message

Minimal complete definition

toMessage

Methods

toMessage :: a -> Message Source #

class Answer a where Source #

User message reply parser.

Minimal complete definition

parse

Methods

parse :: MonadIO m => Message -> ExceptT Text m a Source #

type StoryT = Pipe Message Message Source #

Story transformer is based on Pipe with fixed Message in/out.

type Story a = User -> StoryT (Bot a) Message Source #

Story is a pipe from user message to bot message and result is a final bot message.

data User Source #

Instances

Show User Source # 

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

PersistFieldSql User Source # 

Methods

sqlType :: Proxy * User -> SqlType #

PersistEntity User Source # 
PersistField User Source # 
ToBackendKey SqlBackend User Source # 
Eq (Key User) Source # 

Methods

(==) :: Key User -> Key User -> Bool #

(/=) :: Key User -> Key User -> Bool #

Ord (Key User) Source # 

Methods

compare :: Key User -> Key User -> Ordering #

(<) :: Key User -> Key User -> Bool #

(<=) :: Key User -> Key User -> Bool #

(>) :: Key User -> Key User -> Bool #

(>=) :: Key User -> Key User -> Bool #

max :: Key User -> Key User -> Key User #

min :: Key User -> Key User -> Key User #

Read (Key User) Source # 
Show (Key User) Source # 

Methods

showsPrec :: Int -> Key User -> ShowS #

show :: Key User -> String #

showList :: [Key User] -> ShowS #

ToJSON (Key User) Source # 
FromJSON (Key User) Source # 
ToHttpApiData (Key User) Source # 
FromHttpApiData (Key User) Source # 
PathPiece (Key User) Source # 
PersistFieldSql (Key User) Source # 

Methods

sqlType :: Proxy * (Key User) -> SqlType #

PersistField (Key User) Source # 
data Unique User Source # 
data EntityField User Source # 
data Key User Source # 
type PersistEntityBackend User Source # 

Story makers

question :: (MonadIO m, Answer a) => Text -> StoryT m a Source #

Bot text question.

replica :: (ToMessage a, MonadIO m, Answer b) => a -> StoryT m b Source #

Generalized story maker. The replica send message to user, when answer isn't parsed the error be sended and wait for correct answer.

select :: (MonadIO m, Answer a) => Text -> [[Text]] -> StoryT m a Source #

Reply keyboard selection

Bot monad & configuration classes

data Bot a b Source #

Message bot monad

Instances

MonadBaseControl IO (Bot a) Source # 

Associated Types

type StM (Bot a :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (Bot a) IO -> IO a) -> Bot a a #

restoreM :: StM (Bot a) a -> Bot a a #

MonadBase IO (Bot a) Source # 

Methods

liftBase :: IO α -> Bot a α #

Monad (Bot a) Source # 

Methods

(>>=) :: Bot a a -> (a -> Bot a b) -> Bot a b #

(>>) :: Bot a a -> Bot a b -> Bot a b #

return :: a -> Bot a a #

fail :: String -> Bot a a #

Functor (Bot a) Source # 

Methods

fmap :: (a -> b) -> Bot a a -> Bot a b #

(<$) :: a -> Bot a b -> Bot a a #

Applicative (Bot a) Source # 

Methods

pure :: a -> Bot a a #

(<*>) :: Bot a (a -> b) -> Bot a a -> Bot a b #

(*>) :: Bot a a -> Bot a b -> Bot a b #

(<*) :: Bot a a -> Bot a b -> Bot a a #

MonadIO (Bot a) Source # 

Methods

liftIO :: IO a -> Bot a a #

MonadLogger (Bot a) Source # 

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> Bot a () #

type StM (Bot a) b Source # 
type StM (Bot a) b = b

class Platform a where Source #

Message bot platform. Different platforms provide message bot API, e.g. Telegram, Viber, Facebook Messenger etc. This is generalized interface to it.

Minimal complete definition

trySelf, sendMessage, messageHandler, platformName

Methods

trySelf :: APIToken a => Bot a () Source #

Try connection to platform API

sendMessage :: (ToMessage msg, APIToken a) => User -> msg -> Bot a () Source #

Send message to user by platform API

messageHandler :: APIToken a => (User -> Message -> Bot a b) -> Bot a c Source #

Get user updates by platform API

platformName :: a -> Text Source #

Short description of platform

class Platform a => APIToken a where Source #

Bot authentification in platform Instance of it should be writen by user

Minimal complete definition

apiToken

Methods

apiToken :: Bot a Text Source #

Platform API token

Bot platforms

Bot storage

class Platform a => Persist a where Source #

Connection info provider

Minimal complete definition

persist

Bot runners

storyBot :: (Persist a, APIToken a, ToMessage help) => help -> Map Message (Story a) -> Bot a () Source #

User story handler

forkBot :: APIToken a => Bot a () -> Bot a ThreadId Source #

Fork bot thread

runBot :: (APIToken a, MonadIO m) => Bot a b -> m b Source #

Run bot monad

Re-exports

yield :: Monad m => a -> Producer' a m () #

Produce a value

yield :: Monad m => a -> Pipe x a m ()

await :: Monad m => Consumer' a m a #

Consume a value

await :: Monad m => Pipe a y m a

lift :: MonadTrans t => forall m a. Monad m => m a -> t m a #

Lift a computation from the argument monad to the constructed monad.