pointless-haskell-0.0.9: Pointless Haskell library

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

Generics.Pointless.HFunctors

Contents

Description

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

This module defines polymorphic data types as fixed points of higher-order functor.

Synopsis

Documentation

type (:~>) s v = forall a. s a -> v a infixr 8 Source

The type of natural transformations

Higher-order functors

newtype Functor f => HId f a Source

Identity higher-order functor

Constructors

IdH 

Fields

unIdH :: f a
 

Instances

HFoldable HId 
type App HId g = HId 
type HRep HId f = f 

newtype HConst c f a Source

Constant higher-order functor

Constructors

ConsH 

Fields

unConsH :: c
 

Instances

HFoldable (HConst a) 
type App (HConst t) g = HConst t 
type HRep (HConst c) f = Const c 

newtype HParam f a Source

Parameter higher-order functor

Constructors

HPar 

Fields

unParH :: a
 

Instances

HFoldable HParam 
type App HParam g = HFun g 
type HRep HParam f = Id 

newtype Functor g => HFun g f a Source

Constructors

HFun 

Fields

unFunH :: g a
 

Instances

HFoldable (HFun g) 
type App (HFun h) g = HFun ((:@:) h g) 
type HRep (HFun g) f = g 

data (g :+~: h) f a infixr 5 Source

Sum higher-order functor

Constructors

InlH (g f a) 
InrH (h f a) 

Instances

(HFoldable f, HFoldable g) => HFoldable ((:+~:) f g) 
type App ((:+~:) f g) h = (:+~:) (App f h) (App g h) 
type HRep ((:+~:) g h) f = (:+:) (HRep g f) (HRep h f) 

data (g :*~: h) f a infixr 6 Source

Product higher-order functor

Constructors

ProdH (g f a) (h f a) 

Instances

(HFoldable f, HFoldable g) => HFoldable ((:*~:) f g) 
type App ((:*~:) f g) h = (:*~:) (App f h) (App g h) 
type HRep ((:*~:) g h) f = (:*:) (HRep g f) (HRep h f) 

data (g :@~: h) f a infixr 9 Source

Composition of a regular functor with an higher-order functor

Constructors

CompH 

Fields

unCompH :: g (h f a)
 

Instances

type App ((:@~:) f g) h = (:@~:) f (App g h) 
type HRep ((:@~:) g h) f = (:@:) g (HRep h f) 

newtype HFix f a Source

The fixpoint of an higher-order functor is a regular functor

Constructors

HInn 

Fields

hOut :: HRep f (HFix f) a
 

Instances

Hu (HFix f) 
type HF (HFix f) = f 

data AnnH f Source

Annotations of higher-order functors, only to provide type-level information to the compiler

Application of higher-order functors to a regular functor

type family HRep g f :: * -> * Source

Instances

type HRep HParam f = Id 
type HRep HId f = f 
type HRep (HFun g) f = g 
type HRep (HConst c) f = Const c 
type HRep ((:@~:) g h) f = (:@:) g (HRep h f) 
type HRep ((:*~:) g h) f = (:*:) (HRep g f) (HRep h f) 
type HRep ((:+~:) g h) f = (:+:) (HRep g f) (HRep h f) 

Functor composition as the fixpoint of an higher-order functor (using the fixpoint of the first functor)

type family App f g :: (* -> *) -> * -> * Source

Instances

type App HParam g = HFun g 
type App HId g = HId 
type App (HFun h) g = HFun ((:@:) h g) 
type App (HConst t) g = HConst t 
type App ((:@~:) f g) h = (:@~:) f (App g h) 
type App ((:*~:) f g) h = (:*~:) (App f h) (App g h) 
type App ((:+~:) f g) h = (:+~:) (App f h) (App g h) 

User-defined polymorphic types as fixed points of higher-order functors

type family HF t :: (* -> *) -> * -> * Source

Instances

type HF [] = (:+~:) (HConst One) ((:*~:) HParam HId) 
type HF (HFix f) = f 
type HF ((:@:) f g) = App (HF f) g 

type H t a = HRep (HF t) a Source

class Hu t where Source

Methods

hinn :: H t t a -> t a Source

hout :: t a -> H t t a Source

Instances

Hu [] 
Hu (HFix f) 

Foldable higher-order functors

class FMonoid f where Source

Polymorphic monoid class

Methods

fzero :: f a Source

fplus :: f a -> f a -> f a Source

Instances

FMonoid [] 
FMonoid f => FMonoid ((:@:) f g) 
(FMonoid f, FMonoid g) => FMonoid ((:*:) f g) 

class HFoldable f where Source

Minimal complete definition

reduce

Methods

reduce :: FMonoid g => AnnH f -> HRep f g :~> g Source

reduce' :: FMonoid g => AnnH f -> Ann (Fix g) -> HRep f g :~> g Source