acid-state-0.15.0: Add ACID guarantees to any serializable Haskell data structure.

Safe HaskellNone
LanguageHaskell2010

Data.Acid.TemplateHaskell

Synopsis

Documentation

makeAcidic :: Name -> [Name] -> Q [Dec] Source #

Create the control structures required for acid states using Template Haskell.

This code:

myUpdate :: Argument -> Update State Result
myUpdate arg = ...

myQuery :: Argument -> Query State Result
myQuery arg = ...

$(makeAcidic ''State ['myUpdate, 'myQuery])

will make State an instance of IsAcidic and provide the following events:

data MyUpdate = MyUpdate Argument
data MyQuery  = MyQuery Argument

makeAcidic' :: [Name] -> Name -> [TyVarBndr] -> [Con] -> Q [Dec] Source #

makeIsAcidic :: [Name] -> Name -> [TyVarBndr] -> p -> Q Dec Source #

eventCxts Source #

Arguments

:: Type

State type

-> [TyVarBndr]

type variables that will be used for the State type in the IsAcidic instance

-> Name

Name of the event

-> Type

Type of the event

-> [Pred]

extra context to add to IsAcidic instance

This function analyses an event function and extracts any additional class contexts which need to be added to the IsAcidic instance.

For example, if we have:

data State a = ...
setState :: (Ord a) => a -> UpdateEvent (State a) ()

Then we need to generate an IsAcidic instance like:

instance (SafeCopy a, Typeable a, Ord a) => IsAcidic (State a)

Note that we can only add constraints for type variables which appear in the State type. If we tried to do this:

setState :: (Ord a, Ord b) => a -> b -> UpdateEvent (State a) ()

We will get an ambigious type variable when trying to create the IsAcidic instance, because there is no way to figure out what type b should be.

The tricky part of this code is that we need to unify the type variables.

Let's say the user writes their code using b instead of a:

setState :: (Ord b) => b -> UpdateEvent (State b) ()

In the IsAcidic instance, we are still going to use a. So we need to rename the variables in the context to match.

The contexts returned by this function will have the variables renamed.

Additionally, if the event uses MonadReader or MonadState it might look like this:

setState :: (MonadState x m, IsFoo x) => m ()

In this case we have to rename x to the actual state we're going to use. This is done by renameState.

renameState :: Type -> Type -> Cxt -> Cxt Source #

See the end of comment for eventCxts.

findTyVars :: Type -> [Name] Source #

find the type variables | e.g. State a b ==> [a,b]