algebraic-classes-0.1: Conversions between algebraic classes and F-algebras.

Portabilitynon-portable
Stabilityexperimental
Maintainersjoerd@w3future.com
Safe HaskellNone

Data.Algebra

Contents

Description

 

Synopsis

Classes

class Traversable f => AlgebraSignature f whereSource

Associated Types

type Class f :: * -> ConstraintSource

The class for which f is the signature.

Methods

evaluate :: Class f b => f b -> bSource

Translate the operations of the signature to method calls of the class.

class Algebra f a whereSource

Methods

algebra :: AlgebraSignature f => f a -> aSource

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))

Instances

Algebra f () 
Class f b => Algebra f (a -> b) 
(Class f m, Class f n) => Algebra f (m, n) 

Template Haskell functions

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 Algebra f a, where f is the signature of c.

deriveInstance will generate a signature for the class if there is no signature in scope.

deriveSignature :: Name -> Q [Dec]Source

Derive a signature for an algebraic class. For exaple:

 deriveSignature ''Num

deriveSignature creates the signature data type and an instance for it of the AlgebraSignature class. DeriveFunctor is used the generate the Functor instance of the signature.

This will do nothing if there is already a signature for the class in scope.

Example signature

data MonoidSignature a Source

The Monoid signature has this AlgebraSignature instance:

 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

Constructors

Op_mempty 
Op_mappend a a 
Op_mconcat [a]