| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
FCI.Internal.TH
Description
TH for dictionary representation generation. This module is internal and provides no guarantees about stability and safety of its interface.
Synopsis
- mkDict :: Name -> Q [Dec]
- setDictOptions :: DictOptions -> Q [a]
- data DictOptions
- dictOptions :: DictOptions
- instanceDict :: Q Exp -> Q [Dec]
- instanceDict_ :: Overlap -> Q Exp -> Q [Dec]
- instanceDictM :: Maybe Overlap -> Q Exp -> Q [Dec]
- data Overlap
- type ClassName = String
- type MethodName = String
- type FieldName = String
- type TypeName = String
- type ConstrName = String
Main API
mkDict :: Name -> Q [Dec] Source #
Declare the dictionary type associated with a given class.
The generated type is a record of class members with the following format
by default (it can be customized using setDictOptions):
- The type of the record is
Dictprepended to the name of the class. - The name of the constructor is the name of the class.
Superclass constraints are transformed into fields containing their dictionaries. The names of those fields are generated this way:
- Alphabetic names (e.g.,
Show,Applicative) are prefixed with_ - Operators (e.g.,
(~)) are prefixed with/ - Tuples are converted into
_Tuple2,_Tuple3, etc. - Multiple occurrences of the same superclass are suffixed with an index
starting from 1, or with an increasing number of
|s if its name is an operator.
- Alphabetic names (e.g.,
- Methods get their own fields; their names are the names of methods
prefixed with
_for alphabetic method names, or|for operators.
This behavior can be configured using setDictOptions from FCI.TH.
setDictOptions :: DictOptions -> Q [a] Source #
Set options for subsequent invocations of mkDict.
This setting only affects the current module.
Returns the empty list so it can be used as a top-level slice.
data DictOptions Source #
Options to configure mkDict. The constructor is hidden so you have to use
record update with dictOptions.
Example
setDictOptionsdictOptions{autoDoc= False }
dictOptions :: DictOptions Source #
Default DictOptions. To be modified with record updates.
dictOptions{methodName= _ ,superclassName= _ ,typeName= _ ,constructorName= _ ,autoDoc= _ }
instanceDict :: Q Exp -> Q [Dec] Source #
Implement an instance using a dictionary. The argument must be an expression quote with an explicit signature.
Example
This declaration
instanceDict[|viaFunctor@((->) e) ::Dict(Functor(Reader e)) |]
generates the following Functor instance for a user-defined type Reader e:
instanceFunctor(Reader e) where -- Methods obtained from the fields of the dictionary (viaFunctor@((->) e)).fmap=_fmap(viaFunctor@(((->) e))) (<$) = (|<$) (viaFunctor@(((->) e)))
The following syntaxes are supported to specify the instance head:
instanceDict[| e ::Dict(C (T a)) |] -- instance C (T a)instanceDict[| e :: D a =>Dict(C (T a)) |] -- instance D a => C (T a)instanceDict[| e :: forall a. D a =>Dict(C (T a)) |] -- instance forall a. D a => C (T a)
instanceDict_ :: Overlap -> Q Exp -> Q [Dec] Source #
Variant of instanceDict with an Overlap annotation:
{-# OVERLAPPABLE #-}, etc.
instanceDict_OverlappableinstanceDict_OverlappinginstanceDict_OverlapsinstanceDict_Incoherent
instanceDictM :: Maybe Overlap -> Q Exp -> Q [Dec] Source #
instanceDict and instanceDict_ as one function.
instanceDictMNothing=instanceDictinstanceDictM(Justoverlap) =instanceDict_overlap
Varieties of allowed instance overlap.
Constructors
| Overlappable | May be overlapped by more specific instances |
| Overlapping | May overlap a more general instance |
| Overlaps | Both |
| Incoherent | Both |
Instances
| Data Overlap | |||||
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Overlap -> c Overlap # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Overlap # toConstr :: Overlap -> Constr # dataTypeOf :: Overlap -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Overlap) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Overlap) # gmapT :: (forall b. Data b => b -> b) -> Overlap -> Overlap # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Overlap -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Overlap -> r # gmapQ :: (forall d. Data d => d -> u) -> Overlap -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Overlap -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Overlap -> m Overlap # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Overlap -> m Overlap # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Overlap -> m Overlap # | |||||
| Generic Overlap | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Show Overlap | |||||
| Eq Overlap | |||||
| Ord Overlap | |||||
Defined in Language.Haskell.TH.Syntax | |||||
| type Rep Overlap | |||||
Defined in Language.Haskell.TH.Syntax type Rep Overlap = D1 ('MetaData "Overlap" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "Overlappable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Overlapping" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Overlaps" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Incoherent" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
Synonyms
type MethodName = String Source #
type ConstrName = String Source #