happstack-state-6.1.3: Event-based distributed state.

Safe HaskellNone

Happstack.State

Contents

Synopsis

ACID monad

data Ev m t Source

Monad for ACID event handlers.

Instances

MonadReader st (Update st) 
MonadReader st (Query st) 
MonadState st (Update st) 
Monad m => Monad (Ev m) 
Monad m => Functor (Ev m) 
MonadPlus m => MonadPlus (Ev m) 
(Typeable state, Typeable t) => Typeable (Ev (ReaderT state STM) t) 
(Typeable state, Typeable t) => Typeable (Ev (StateT state STM) t) 

type AnyEv a = forall t. (Monad (t STM), MonadTrans t) => Ev (t STM) aSource

ACID computations that work with any state and event types.

query :: (MonadIO m, QueryEvent ev res) => ev -> m resSource

Emit a state query and wait for the result.

update :: (MonadIO m, UpdateEvent ev res) => ev -> m resSource

Schedule an update and wait for it to complete. When this function returns, you're guaranteed the update will be persistent.

type Update state = Ev (StateT state STM)Source

type Query state = Ev (ReaderT state STM)Source

Types

data Saver Source

Constructors

NullSaver

A saver that discards all output

FileSaver String

A saver that operates on files. The parameter is the prefix for the files.

Queue Saver

Enable queueing.

Memory (MVar Store) 

Misc utilities

setUpdateType :: Proxy t -> Update t ()Source

Use a proxy to force the type of an update action.

proxyUpdate :: Update t b -> Proxy t -> Update t bSource

Forces the type of the proxy and update to match

setQueryType :: Proxy t -> Query t ()Source

Use a proxy to force the type of a query action.

proxyQuery :: Query t b -> Proxy t -> Query t bSource

Forces the type of proxy and query to match

asUpdate :: Update t a -> Proxy t -> Update t aSource

Currying version of setUpdateType.

asQuery :: Query t a -> Proxy t -> Query t aSource

Currying version of setQueryType.

askState :: Query st stSource

Specialized version of ask

getState :: Update st stSource

Specialized version of get

putState :: st -> Update st ()Source

Specialized version of put.

liftSTM :: STM a -> AnyEv aSource

Lift an STM action into Ev.

class CatchEv m whereSource

Methods

catchEv :: Exception e => Ev m a -> (e -> a) -> Ev m aSource

Instances

sel :: (Env -> b) -> AnyEv bSource

Select a part of the environment.

localState :: (outer -> inner) -> (inner -> outer -> outer) -> Ev (StateT inner STM) a -> Ev (StateT outer STM) aSource

Run a computation with local state. Changes to state will be visible to outside.

localStateReader :: (outer -> inner) -> Ev (ReaderT inner STM) a -> Ev (ReaderT outer STM) aSource

Run a computation with local state.

runQuery :: Query st a -> Update st aSource

Execute a Query action in the Update monad.

getTime :: Integral epochTime => AnyEv epochTimeSource

data EventItem Source

Constructors

EventItem 

Fields

eventContext :: TxContext
 
eventData :: Dynamic
 

Random numbers

getRandom :: Random a => AnyEv aSource

Get a random number.

getRandomR :: Random a => (a, a) -> AnyEv aSource

Get a random number inside the range.

TH helpers

inferRecordUpdaters :: Name -> Q [Dec]Source

Infer updating functions for a record. Given a data declaration of data Foo = Foo {bar :: String, baz :: Int} then $(inferRecordUpdaters ''Foo) will define functions a_bar :: String -> Foo -> Foo, withBar :: Update String a -> Update Foo a, etc. that can be used as convenience updaters.

Serialization

runTxSystem :: (Methods st, Component st) => Saver -> Proxy st -> IO (MVar TxControl)Source

Run the MACID system without multimaster support and with the given Saver.

shutdownSystem :: MVar TxControl -> IO ()Source

Shuts down a transaction system

Unsafe things