Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- makeAcidic :: Name -> [Name] -> Q [Dec]
- makeAcidic' :: [Name] -> Name -> [TyVarBndr] -> [Con] -> Q [Dec]
- makeEvent :: Name -> Q [Dec]
- getEventType :: Name -> Q Type
- makeIsAcidic :: [Name] -> Name -> [TyVarBndr] -> p -> Q Dec
- eventCxts :: Type -> [TyVarBndr] -> Name -> Type -> [Pred]
- renameState :: Type -> Type -> Cxt -> Cxt
- makeEventHandler :: Name -> Type -> ExpQ
- makeEventDataType :: Name -> Type -> DecQ
- makeSafeCopyInstance :: Name -> Type -> Q Dec
- mkCxtFromTyVars :: [Name] -> [TyVarBndr] -> [Pred] -> CxtQ
- makeMethodInstance :: Name -> Type -> DecQ
- makeEventInstance :: Name -> Type -> DecQ
- data TypeAnalysis = TypeAnalysis {}
- analyseType :: Name -> Type -> TypeAnalysis
- findTyVars :: Type -> [Name]
- tyVarBndrName :: TyVarBndr -> Name
- allTyVarBndrNames :: [TyVarBndr] -> [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
:: Type | State type |
-> [TyVarBndr] | 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
.
data TypeAnalysis Source #
Instances
Eq TypeAnalysis Source # | |
Defined in Data.Acid.TemplateHaskell (==) :: TypeAnalysis -> TypeAnalysis -> Bool # (/=) :: TypeAnalysis -> TypeAnalysis -> Bool # | |
Show TypeAnalysis Source # | |
Defined in Data.Acid.TemplateHaskell showsPrec :: Int -> TypeAnalysis -> ShowS # show :: TypeAnalysis -> String # showList :: [TypeAnalysis] -> ShowS # |
analyseType :: Name -> Type -> TypeAnalysis Source #
findTyVars :: Type -> [Name] Source #
find the type variables | e.g. State a b ==> [a,b]
allTyVarBndrNames :: [TyVarBndr] -> [Name] Source #