pointless-haskell-0.0.9: Pointless Haskell library

Copyright(c) 2008 University of Minho
LicenseBSD3
Maintainerhpacheco@di.uminho.pt
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Generics.Pointless.Functors

Contents

Description

Pointless Haskell: point-free programming with recursion patterns as hylomorphisms

This module defines data types as fixed points of functor. Pointless Haskell works on a view of data types as fixed points of functors, in the same style as the PolyP (http://www.cse.chalmers.se/~patrikj/poly/polyp/) library. Instead of using an explicit fixpoint operator, a type function is used to relate the data types with their equivalent functor representations.

Synopsis

Functors

Definition and operations over functors

data Id x Source

Identity functor.

Constructors

IdF 

Fields

unIdF :: x
 

Instances

Functor Id 
Functor Id

The identity functor applies the mapping function the argument type

ToRep Id 
ShowRep Id 
Fctrable Id 
FunctorO Id 
Eq x => Eq (Id x) 
Show x => Show (Id x) 
Typeable (* -> *) Id 
type Rep Id x = x

The identity functor applied to some type is the type itself.

data Const t x Source

Constant functor.

Constructors

ConsF 

Fields

unConsF :: t
 

Instances

Functor (Const t) 
Functor (Const t)

The constant functor preserves the argument type

ToRep (Const c) 
Show t => ShowRep (Const t) 
Fctrable (Const c) 
(Typeable * a, Observable a) => FunctorO (Const a) 
Eq t => Eq (Const t x) 
Show t => Show (Const t x) 
Typeable (* -> * -> *) Const 
type Rep (Const t) x = t

The constant functor applied to some type is the type parameterized by the functor.

data (g :+: h) x infixr 5 Source

Sum of functors.

Constructors

InlF (g x) 
InrF (h x) 

Instances

(Functor g, Functor h) => Functor ((:+:) g h) 
(Functor g, Functor h) => Functor ((:+:) g h)

The sum functor recursively applies the mapping function to each alternative

(ToRep f, ToRep g) => ToRep ((:+:) f g) 
(ShowRep f, ShowRep g) => ShowRep ((:+:) f g) 
(Functor f, Fctrable f, Functor g, Fctrable g) => Fctrable ((:+:) f g) 
(FunctorO f, FunctorO g) => FunctorO ((:+:) f g) 
Typeable ((* -> *) -> (* -> *) -> * -> *) (:+:) 
(Eq (g x), Eq (h x)) => Eq ((:+:) g h x) 
(Show (g x), Show (h x)) => Show ((:+:) g h x) 
type Rep ((:+:) g h) x = Either (Rep g x) (Rep h x)

The application of a sum of functors to some type is the sum of applying the functors to the argument type.

data (g :*: h) x infixr 6 Source

Product of functors.

Constructors

ProdF (g x) (h x) 

Instances

(Functor g, Functor h) => Functor ((:*:) g h) 
(Functor g, Functor h) => Functor ((:*:) g h)

The product functor recursively applies the mapping function to both sides

(ToRep f, ToRep g) => ToRep ((:*:) f g) 
(ShowRep f, ShowRep g) => ShowRep ((:*:) f g) 
(FMonoid f, FMonoid g) => FMonoid ((:*:) f g) 
(Functor f, Fctrable f, Functor g, Fctrable g) => Fctrable ((:*:) f g) 
(FunctorO f, FunctorO g) => FunctorO ((:*:) f g) 
Typeable ((* -> *) -> (* -> *) -> * -> *) (:*:) 
(Eq (g x), Eq (h x)) => Eq ((:*:) g h x) 
(Show (g x), Show (h x)) => Show ((:*:) g h x) 
type Rep ((:*:) g h) x = (Rep g x, Rep h x)

The application of a product of functors to some type is the product of applying the functors to the argument type.

data (g :@: h) x infixr 9 Source

Composition of functors.

Constructors

CompF 

Fields

unCompF :: g (h x)
 

Instances

(Functor g, Functor h) => Functor ((:@:) g h) 
(Functor g, Functor h) => Functor ((:@:) g h)

The composition functor applies in the nesting of the mapping function to the nested functor applications

(Functor f, Functor f, ToRep f, ToRep g) => ToRep ((:@:) f g) 
(ShowRep f, ShowRep g) => ShowRep ((:@:) f g) 
FMonoid f => FMonoid ((:@:) f g) 
(Functor f, Fctrable f, Functor g, Fctrable g) => Fctrable ((:@:) f g) 
(FunctorO g, FunctorO h) => FunctorO ((:@:) g h) 
Typeable ((* -> *) -> (* -> *) -> * -> *) (:@:) 
Eq (g (h x)) => Eq ((:@:) g h x) 
Show (g (h x)) => Show ((:@:) g h x) 
type HF ((:@:) f g) = App (HF f) g 
type Rep ((:@:) g h) x = Rep g (Rep h x)

The application of a composition of functors to some type is the nested application of the functors to the argument type.

This particular instance requires that nexted type function application is enabled as a type system extension.

newtype Fix f Source

Explicit fixpoint operator.

Constructors

Inn 

Fields

ouT :: Rep f (Fix f)

The unfolding of the fixpoint of a functor is the functor applied to its fixpoint.

unFix is specialized with the application of Rep in order to subsume functor application

Instances

ShowRep f => Show (Fix f) 
(Functor f, FunctorO f) => Observable (Fix f) 
Mu (Fix f)

Expandingcontracting the fixed point of a functor is the same as consumingapplying it's single type constructor

type PF (Fix f) = f

The pattern functor of the fixpoint of a functor is the functor itself.

type family PF a :: * -> * Source

Family of patterns functors of data types.

The type function is not necessarily injective, this is, different data types can have the same base functor.

Semantically, we can say that a = Fix f.

Instances

type PF Bool = (:+:) (Const One) (Const One) 
type PF Int = (:+:) (Const One) Id 
type PF Nat = (:+:) (Const One) Id 
type PF I = Id 
type PF [a] = (:+:) (Const One) ((:*:) (Const a) Id) 
type PF (Maybe a) = (:+:) (Const One) (Const a) 
type PF (K a) = Const a 
type PF (Fix f) = f

The pattern functor of the fixpoint of a functor is the functor itself.

type PF (Rose a) = (:*:) (Const a) ((:@:) [] Id)

The functor of a rose tree.

type PF (LTree a) = (:+:) (Const a) ((:*:) Id Id)

The functor of a leaf tree.

type PF (Tree a) = (:+:) (Const One) ((:*:) (Const a) ((:*:) Id Id))

The functor of a binary tree.

type PF (Some a) = (:+:) (Const a) ((:*:) (Const a) Id) 
type PF ((:@!:) a b) = (:@:) (PF a) (PF b) 
type PF ((:*!:) a b) = (:*:) (PF a) (PF b) 
type PF ((:+!:) a b) = (:+:) (PF a) (PF b) 

type family Rep f x :: * Source

Family of functor representations.

The Rep family implements the implicit coercion between the application of a functor and the structurally equivalent sum of products.

Functors applied to types can be represented as sums of products.

Instances

type Rep [] x = [x]

The application of the list functor to some type returns a list of the argument type.

type Rep Id x = x

The identity functor applied to some type is the type itself.

type Rep (Const t) x = t

The constant functor applied to some type is the type parameterized by the functor.

type Rep (BPar a) x = a 
type Rep (BId a) x = x

Representation of bifunctors with the Rep functor representation class.

type Rep ((:@:) g h) x = Rep g (Rep h x)

The application of a composition of functors to some type is the nested application of the functors to the argument type.

This particular instance requires that nexted type function application is enabled as a type system extension.

type Rep ((:*:) g h) x = (Rep g x, Rep h x)

The application of a product of functors to some type is the product of applying the functors to the argument type.

type Rep ((:+:) g h) x = Either (Rep g x) (Rep h x)

The application of a sum of functors to some type is the sum of applying the functors to the argument type.

type Rep (BConst t a) x = t 
type Rep ((:@|) g h a) x = Rep (g a) (Rep (h a) x) 
type Rep ((:*|) g h a) x = (Rep (g a) x, Rep (h a) x) 
type Rep ((:+|) g h a) x = Either (Rep (g a) x) (Rep (h a) x) 

class ShowRep f where Source

A specific Show class for functor representations that receives a show function for recursive instances. This avoids infinite loops in the type inference of fixpoints.

Methods

showrep :: Ann (Fix f) -> (x -> String) -> Rep f x -> String Source

Instances

ShowRep Id 
Show t => ShowRep (Const t) 
(ShowRep f, ShowRep g) => ShowRep ((:@:) f g) 
(ShowRep f, ShowRep g) => ShowRep ((:*:) f g) 
(ShowRep f, ShowRep g) => ShowRep ((:+:) f g) 

class ToRep f where Source

Methods

rep :: f x -> Rep f x Source

fun :: f x -> Ann (Fix f) Source

val :: f x -> Ann x Source

unrep :: Ann (Fix f) -> Ann x -> Rep f x -> f x Source

Instances

ToRep [] 
ToRep Id 
ToRep (Const c) 
(Functor f, Functor f, ToRep f, ToRep g) => ToRep ((:@:) f g) 
(ToRep f, ToRep g) => ToRep ((:*:) f g) 
(ToRep f, ToRep g) => ToRep ((:+:) f g) 

class Functor f where Source

Polytypic Functor class for functor representations

Methods

fmap Source

Arguments

:: Ann (Fix f)

For desambiguation purposes, the type of the functor must be passed as an explicit parameter to fmap

-> (x -> y) 
-> Rep f x 
-> Rep f y

The mapping over representations

fzip Source

Arguments

:: Ann (Fix f) 
-> (a -> c) 
-> (Rep f a, Rep f c) 
-> Rep f (a, c)

The polytypic functor zipping combinator. Gives preference to the abstract (first) F-structure.

Instances

Functor []

The list functor maps the specific map function over lists of types

Functor Id

The identity functor applies the mapping function the argument type

Functor (Const t)

The constant functor preserves the argument type

(Functor g, Functor h) => Functor ((:@:) g h)

The composition functor applies in the nesting of the mapping function to the nested functor applications

(Functor g, Functor h) => Functor ((:*:) g h)

The product functor recursively applies the mapping function to both sides

(Functor g, Functor h) => Functor ((:+:) g h)

The sum functor recursively applies the mapping function to each alternative

lzip :: (a -> c) -> ([a], [c]) -> [(a, c)] Source

type F a x = Rep (PF a) x Source

Short alias to express the structurally equivalent sum of products for some data type

pmap Source

Arguments

:: Functor (PF a) 
=> Ann a

A value of a data type that is the fixed point of the desired functor

-> (x -> y) 
-> F a x 
-> F a y

The mapping over the equivalent sum of products

Polytypic map function

class Mu a where Source

The Mu class provides the value-level translation between data types and their sum of products representations

Methods

inn :: F a a -> a Source

Packs a sum of products into one equivalent data type

out :: a -> F a a Source

unpacks a data type into the equivalent sum of products

Instances

Mu Bool 
Mu Int 
Mu Nat 
Mu I 
Mu [a] 
Mu (Maybe a) 
Mu (K a) 
Mu (Fix f)

Expandingcontracting the fixed point of a functor is the same as consumingapplying it's single type constructor

Mu (Rose a) 
Mu (LTree a) 
Mu (Tree a) 
Mu (Some a) 
Mu ((:@!:) a b) 
Mu ((:*!:) a b) 
Mu ((:+!:) a b) 

inn' :: Mu a => Ann a -> F a a -> a Source

out' :: Mu a => Ann a -> a -> F a a Source

Fixpoint combinators

data I Source

In order to simplify type-level composition of functors, we can create fixpoint combinators that implicitely assume fixpoint application.

Semantically, we can say that I = Fix Id.

Constructors

FixId 

Instances

Observable I 
Mu I 
type PF I = Id 

data K a Source

Semantically, we can say that K t = Fix (Const t).

Constructors

FixConst 

Fields

unFixConst :: a
 

Instances

(Typeable * a, Observable a) => Observable (K a) 
Mu (K a) 
type PF (K a) = Const a 

data a :+!: b infixr 5 Source

Semantically, we can say that Fix f :+!: Fix g = Fix (f :+: g).

Constructors

FixSum 

Fields

unFixSum :: F (a :+!: b) (a :+!: b)
 

Instances

(FunctorO (PF a), FunctorO (PF b)) => Observable ((:+!:) a b) 
Mu ((:+!:) a b) 
type PF ((:+!:) a b) = (:+:) (PF a) (PF b) 

data a :*!: b infixr 6 Source

Semantically, we can say that Fix f :*!: Fix g = Fix (f :*: g).

Constructors

FixProd 

Fields

unFixProd :: F (a :*!: b) (a :*!: b)
 

Instances

(FunctorO (PF a), FunctorO (PF b)) => Observable ((:*!:) a b) 
Mu ((:*!:) a b) 
type PF ((:*!:) a b) = (:*:) (PF a) (PF b) 

data a :@!: b infixr 9 Source

Semantically, we can say that Fix f :@!: Fix g = Fix (f ':@: g).

Constructors

FixComp 

Fields

unFixComp :: F (a :@!: b) (a :@!: b)
 

Instances

(FunctorO (PF a), FunctorO (PF b)) => Observable ((:@!:) a b) 
Mu ((:@!:) a b) 
type PF ((:@!:) a b) = (:@:) (PF a) (PF b) 

Default definitions for commonly used data types

List

nil :: One -> [a] Source

cons :: (a, [a]) -> [a] Source

Natural Numbers

data Nat Source

Constructors

Nat Int 

Instances

Int (positive only)

Bool

Maybe