Copyright | (c) Sjoerd Visscher 2013 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | sjoerd@w3future.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell98 |
Synopsis
- deriveInstance :: Q Type -> Q [Dec]
- deriveInstanceWith :: Q Type -> Q [Dec] -> Q [Dec]
- deriveInstanceWith_skipSignature :: Q Type -> Q [Dec] -> Q [Dec]
- deriveSuperclassInstances :: Q Type -> Q [Dec]
- deriveSignature :: Name -> Q [Dec]
- data SignatureTH = SignatureTH {
- signatureName :: Name
- typeVarName :: Name
- operations :: [OperationTH]
- superclasses :: [SuperclassTH]
- data OperationTH = OperationTH {
- functionName :: Name
- operationName :: Name
- arity :: Int
- constructor :: Con
- fixity :: Fixity
- data SuperclassTH = SuperclassTH {}
- getSignatureInfo :: Name -> Q SignatureTH
- buildSignatureDataType :: SignatureTH -> [Dec]
- signatureInstances :: Name -> SignatureTH -> [Dec]
Documentation
deriveInstance :: Q Type -> Q [Dec] Source #
Derive an instance for an algebraic class. For example:
deriveInstance [t| (Num m, Num n) => Num (m, n) |]
To be able to derive an instance for a
of class c
, we need an instance of
,
where Algebra
f af
is the signature of c
.
deriveInstance
will generate a signature for the class if there is no signature in scope.
deriveInstanceWith :: Q Type -> Q [Dec] -> Q [Dec] Source #
Derive an instance for an algebraic class with a given partial implementation. For example:
deriveInstanceWith [t| Num n => Num (Integer -> n) |] [d| fromInteger x y = fromInteger (x + y) |]
deriveInstanceWith_skipSignature :: Q Type -> Q [Dec] -> Q [Dec] Source #
Derive an instance for an algebraic class with a given partial implementation,
but don't generate the signature. This is for when you want to derive several instances
of the same class, but can't splice the results directly. In that case deriveSignature
can't detect it has already generated the signature earlier.
deriveSuperclassInstances :: Q Type -> Q [Dec] Source #
Derive the instances for the superclasses too, all using the same context. Usually you'd want to do this manually since you can often give a stricter context, for example:
deriveSuperclassInstances [t| (Fractional m, Fractional n) => Fractional (m, n) |]
will derive an instance (Fractional m, Fractional n) => Num (m, n)
while the instance only
needs (Num m, Num n)
.
deriveSignature :: Name -> Q [Dec] Source #
Derive a signature for an algebraic class. For example:
deriveSignature ''Monoid
The above would generate the following:
data MonoidSignature a = Op_mempty | Op_mappend a a | Op_mconcat [a] deriving (Functor, Foldable, Traversable, Eq, Ord) type instance Signature Monoid = MonoidSignature instance AlgebraSignature MonoidSignature where type Class MonoidSignature = Monoid evaluate Op_mempty = mempty evaluate (Op_mappend a b) = mappend a b evaluate (Op_mconcat ms) = mconcat ms instance Show a => Show (MonoidSignature a) where showsPrec d Op_mempty = showParen (d > 10) $ showString "mempty" showsPrec d (Op_mappend a1 a2) = showParen (d > 10) $ showString "mappend" . showChar ' ' . showsPrec 11 a1 . showChar ' ' . showsPrec 11 a2 showsPrec d (Op_mconcat a1) = showParen (d > 10) $ showString "mconcat" . showChar ' ' . showsPrec 11 a1
deriveSignature
creates the signature data type and an instance for it of the
AlgebraSignature
class. DeriveTraversable
is used the generate the Traversable
instance of the signature.
This will do nothing if there is already a signature for the class in scope.
Possibly useful internals
data SignatureTH Source #
SignatureTH | |
|
data OperationTH Source #
OperationTH | |
|
data SuperclassTH Source #
getSignatureInfo :: Name -> Q SignatureTH Source #
buildSignatureDataType :: SignatureTH -> [Dec] Source #
signatureInstances :: Name -> SignatureTH -> [Dec] Source #