message-db-0.0.1.0: Client library for Message-DB installed in PostgreSQL.
Safe HaskellNone
LanguageHaskell2010

MessageDb.Handlers

Synopsis

Documentation

data HandleError Source #

An error that may occur from handling a message.

Instances

Instances details
Eq HandleError Source # 
Instance details

Defined in MessageDb.Handlers

Show HandleError Source # 
Instance details

Defined in MessageDb.Handlers

Generic HandleError Source # 
Instance details

Defined in MessageDb.Handlers

Associated Types

type Rep HandleError :: Type -> Type #

ToJSON HandleError Source # 
Instance details

Defined in MessageDb.Handlers

FromJSON HandleError Source # 
Instance details

Defined in MessageDb.Handlers

Exception HandleError Source # 
Instance details

Defined in MessageDb.Handlers

MonadError HandleError Handler Source # 
Instance details

Defined in MessageDb.Handlers

type Rep HandleError Source # 
Instance details

Defined in MessageDb.Handlers

type Rep HandleError = D1 ('MetaData "HandleError" "MessageDb.Handlers" "message-db-0.0.1.0-inplace" 'False) (C1 ('MetaCons "HandlerParseFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ParseMessageFailure)) :+: C1 ('MetaCons "HandlerNotFound" 'PrefixI 'False) (U1 :: Type -> Type))

newtype Handler output Source #

Constructors

Handler 

Instances

Instances details
Monad Handler Source # 
Instance details

Defined in MessageDb.Handlers

Methods

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

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

return :: a -> Handler a #

Functor Handler Source # 
Instance details

Defined in MessageDb.Handlers

Methods

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

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

Applicative Handler Source # 
Instance details

Defined in MessageDb.Handlers

Methods

pure :: a -> Handler a #

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

liftA2 :: (a -> b -> c) -> Handler a -> Handler b -> Handler c #

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

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

MonadReader Message Handler Source # 
Instance details

Defined in MessageDb.Handlers

Methods

ask :: Handler Message #

local :: (Message -> Message) -> Handler a -> Handler a #

reader :: (Message -> a) -> Handler a #

MonadError HandleError Handler Source # 
Instance details

Defined in MessageDb.Handlers

Semigroup output => Semigroup (Handler output) Source # 
Instance details

Defined in MessageDb.Handlers

Methods

(<>) :: Handler output -> Handler output -> Handler output #

sconcat :: NonEmpty (Handler output) -> Handler output #

stimes :: Integral b => b -> Handler output -> Handler output #

Monoid output => Monoid (Handler output) Source # 
Instance details

Defined in MessageDb.Handlers

Methods

mempty :: Handler output #

mappend :: Handler output -> Handler output -> Handler output #

mconcat :: [Handler output] -> Handler output #

getParsedMessage :: (FromJSON payload, FromJSON metadata) => Handler (ParsedMessage payload metadata) Source #

type Handlers output = Map MessageType (Handler output) Source #

addHandler :: MessageType -> Handler output -> Handlers output -> Handlers output Source #

type ProjectionHandler state = Handler (Endo state) Source #

projectionHandler :: forall payload metadata state. (FromJSON payload, FromJSON metadata) => (Message -> payload -> metadata -> state -> state) -> ProjectionHandler state Source #

type ProjectionHandlers state = Handlers (Endo state) Source #

addProjectionHandler :: forall payload metadata state. (FromJSON payload, FromJSON metadata) => MessageType -> (Message -> payload -> metadata -> state -> state) -> ProjectionHandlers state -> ProjectionHandlers state Source #

subscriptionHandler :: forall payload metadata. (FromJSON payload, FromJSON metadata) => (Message -> payload -> metadata -> IO ()) -> SubscriptionHandler Source #

addSubscriptionHandler :: forall payload metadata. (FromJSON payload, FromJSON metadata) => MessageType -> (Message -> payload -> metadata -> IO ()) -> SubscriptionHandlers -> SubscriptionHandlers Source #