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

Copyright(c) Sjoerd Visscher 2013
LicenseBSD-style (see the file LICENSE)
Maintainersjoerd@w3future.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Data.Algebra

Contents

Description

 

Synopsis

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

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

Methods

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

Instances

Algebra f () 
Class f b => Algebra f (STM b) 
Class f b => Algebra f (Maybe b) 
Class f b => Algebra f (IO b) 
(Monoid m, Class f b) => Algebra f (Const m b) 
Class f b => Algebra f (Either a b) 
Class f b => Algebra f (a -> b) 
(Class f m, Class f n) => Algebra f (m, n) 

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 :: * -> * Source

The signature datatype for the class c.

class Traversable f => AlgebraSignature f where Source

Associated Types

type Class f :: * -> Constraint Source

The class for which f is the signature.

Methods

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

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