Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- makeAcidic :: Name -> [Name] -> Q [Dec]
- data SerialiserSpec = SerialiserSpec {}
- safeCopySerialiserSpec :: SerialiserSpec
- makeAcidicWithSerialiser :: SerialiserSpec -> Name -> [Name] -> Q [Dec]
- makeAcidic' :: SerialiserSpec -> [Name] -> Name -> [TyVarBndrUnit] -> [Con] -> Q [Dec]
- makeEvent :: SerialiserSpec -> Name -> Q [Dec]
- getEventType :: Name -> Q Type
- makeIsAcidic :: SerialiserSpec -> [Name] -> Name -> [TyVarBndr ()] -> p -> Q Dec
- eventCxts :: Type -> [TyVarBndrUnit] -> Name -> Type -> [Pred]
- renameState :: Type -> Type -> Cxt -> Cxt
- makeEventHandler :: SerialiserSpec -> Name -> Type -> ExpQ
- makeEventDataType :: Name -> Type -> DecQ
- makeSafeCopyInstance :: Name -> Type -> DecQ
- mkCxtFromTyVars :: Quote m => [Name] -> [TyVarBndr a] -> [Pred] -> m Cxt
- makeMethodInstance :: Name -> Type -> DecQ
- makeEventInstance :: Name -> Type -> DecQ
- data TypeAnalysis = TypeAnalysis {
- tyvars :: [TyVarBndrUnit]
- context :: Cxt
- argumentTypes :: [Type]
- stateType :: Type
- resultType :: Type
- isUpdate :: Bool
- analyseType :: Name -> Type -> TypeAnalysis
- findTyVars :: Type -> [Name]
- tyVarBndrName :: TyVarBndr a -> Name
- allTyVarBndrNames :: [TyVarBndr a] -> [Name]
- toStructName :: Name -> Name
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
data SerialiserSpec Source #
Specifies how to customise the IsAcidic
instance and event data
type serialisation instances for a particular serialisation layer.
SerialiserSpec | |
|
safeCopySerialiserSpec :: SerialiserSpec Source #
Default implementation of SerialiserSpec
that uses SafeCopy
for serialising events.
makeAcidicWithSerialiser :: SerialiserSpec -> Name -> [Name] -> Q [Dec] Source #
A variant on makeAcidic
that makes it possible to explicitly choose the
serialisation implementation to be used for methods.
makeAcidic' :: SerialiserSpec -> [Name] -> Name -> [TyVarBndrUnit] -> [Con] -> Q [Dec] Source #
makeEvent :: SerialiserSpec -> Name -> Q [Dec] Source #
Given an event name (e.g. 'myUpdate
), produce a data type like
data MyUpdate = MyUpdate Argument
along with the Method
class instance, Event
class instance and
the instance of the appropriate serialisation class.
However, if the event data type already exists, this will generate
the serialisation instance only. This makes it possible to call
makeAcidicWithSerialiser
multiple times on the same events but
with different SerialiserSpec
s, to support multiple serialisation
backends.
makeIsAcidic :: SerialiserSpec -> [Name] -> Name -> [TyVarBndr ()] -> p -> Q Dec Source #
:: Type | State type |
-> [TyVarBndrUnit] | type variables that will be used for the State type in the IsAcidic instance |
-> Name |
|
-> Type |
|
-> [Pred] | extra context to add to |
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
.
makeEventHandler :: SerialiserSpec -> Name -> Type -> ExpQ Source #
data TypeAnalysis Source #
TypeAnalysis | |
|
Instances
Show TypeAnalysis Source # | |
Defined in Data.Acid.TemplateHaskell showsPrec :: Int -> TypeAnalysis -> ShowS # show :: TypeAnalysis -> String # showList :: [TypeAnalysis] -> ShowS # | |
Eq TypeAnalysis Source # | |
Defined in Data.Acid.TemplateHaskell (==) :: TypeAnalysis -> TypeAnalysis -> Bool # (/=) :: TypeAnalysis -> TypeAnalysis -> Bool # |
analyseType :: Name -> Type -> TypeAnalysis Source #
findTyVars :: Type -> [Name] Source #
find the type variables | e.g. State a b ==> [a,b]
allTyVarBndrNames :: [TyVarBndr a] -> [Name] Source #