Copyright | (c) 2008 University of Minho |
---|---|
License | BSD3 |
Maintainer | hpacheco@di.uminho.pt |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell98 |
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.
- data Id x = IdF {
- unIdF :: x
- data Const t x = ConsF {
- unConsF :: t
- data (g :+: h) x
- data (g :*: h) x = ProdF (g x) (h x)
- data (g :@: h) x = CompF {
- unCompF :: g (h x)
- newtype Fix f = Inn {}
- type family PF a :: * -> *
- type family Rep f x :: *
- class ShowRep f where
- class ToRep f where
- class Functor f where
- lzip :: (a -> c) -> ([a], [c]) -> [(a, c)]
- type F a x = Rep (PF a) x
- pmap :: Functor (PF a) => Ann a -> (x -> y) -> F a x -> F a y
- class Mu a where
- inn' :: Mu a => Ann a -> F a a -> a
- out' :: Mu a => Ann a -> a -> F a a
- data I = FixId
- data K a = FixConst {
- unFixConst :: a
- data a :+!: b = FixSum {}
- data a :*!: b = FixProd {}
- data a :@!: b = FixComp {}
- nil :: One -> [a]
- cons :: (a, [a]) -> [a]
- data Nat = Nat Int
- nzero :: Nat
- nsucc :: Nat -> Nat
- zero :: One -> Int
- suck :: Int -> Int
- natInt :: Nat -> Int
- intNat :: Int -> Nat
- true :: One -> Bool
- false :: One -> Bool
- maybe2bool :: Maybe a -> Bool
Functors
Definition and operations over functors
Identity functor.
Constant functor.
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.
(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.
ProdF (g x) (h x) |
(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.
(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. |
Explicit fixpoint operator.
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
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.
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 |
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) |
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.
Polytypic Functor
class for functor representations
Functor [] | The list functor maps the specific |
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 |
type F a x = Rep (PF a) x Source
Short alias to express the structurally equivalent sum of products for some data type
:: 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
The Mu
class provides the value-level translation between data types and their sum of products representations
Packs a sum of products into one equivalent data type
unpacks a data type into the equivalent sum of products
Fixpoint combinators
In order to simplify type-level composition of functors, we can create fixpoint combinators that implicitely assume fixpoint application.
FixConst | |
|
(Typeable * a, Observable a) => Observable (K a) | |
Mu (K a) | |
type PF (K a) = Const a |
Default definitions for commonly used data types
List
Natural Numbers
Int (positive only)
Bool
Maybe
maybe2bool :: Maybe a -> Bool Source