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 |
- deriveInstance :: Q Type -> Q [Dec]
- deriveInstanceWith :: Q Type -> Q [Dec] -> Q [Dec]
- class Algebra f a where
- algebraA :: (Applicative g, Class f b, AlgebraSignature f) => f (g b) -> g b
- type family Signature (c :: * -> Constraint) :: * -> *
- class Traversable f => AlgebraSignature f where
- type Class f :: * -> Constraint
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) |]
Classes
class Algebra f a where Source #
algebra :: AlgebraSignature f => f a -> a Source #
An algebra f a -> a
corresponds to an instance of a
of the class Class f
.
In some cases, for example for tuple types, you can give an algebra generically for every signature:
instance (Class f m, Class f n) => Algebra f (m, n) where algebra fmn = (evaluate (fmap fst fmn), evaluate (fmap snd fmn))
Algebra f () Source # | |
Class f b => Algebra f (STM b) Source # | |
Class f b => Algebra f (Maybe b) Source # | |
Class f b => Algebra f (IO b) Source # | |
Class f b => Algebra f (Either a b) Source # | |
Class f b => Algebra f (a -> b) Source # | |
(Class f m, Class f n) => Algebra f (m, n) Source # | |
(Monoid m, Class f b) => Algebra f (Const * m b) Source # | |
algebraA :: (Applicative g, Class f b, AlgebraSignature f) => f (g b) -> g b Source #
If you just want to applicatively lift existing instances, you can use this default implementation of algebra
.
type family Signature (c :: * -> Constraint) :: * -> * Source #
The signature datatype for the class c
.
class Traversable f => AlgebraSignature f where Source #
type Class f :: * -> Constraint Source #
The class for which f
is the signature.