pointless-haskell-0.0.8: Pointless Haskell library

Portabilitynon-portable
Stabilityexperimental
Maintainerhpacheco@di.uminho.pt

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 aSource

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

newtype HConst c f a Source

Constant higher-order functor

Constructors

ConsH 

Fields

unConsH :: c
 

Instances

newtype HParam f a Source

Parameter higher-order functor

Constructors

HPar 

Fields

unParH :: a
 

Instances

newtype Functor g => HFun g f a Source

Constructors

HFun 

Fields

unFunH :: g a
 

Instances

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

Sum higher-order functor

Constructors

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

Instances

(HFoldable f, HFoldable g) => HFoldable (:+~: f g) 

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

Product higher-order functor

Constructors

ProdH (g f a) (h f a) 

Instances

(HFoldable f, HFoldable g) => HFoldable (:*~: f g) 

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

Composition of a regular functor with an higher-order functor

Constructors

CompH 

Fields

unCompH :: g (h f a)
 

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) 

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

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

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

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

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

type H t a = HRep (HF t) aSource

class Hu t whereSource

Methods

hinn :: H t t a -> t aSource

hout :: t a -> H t t aSource

Instances

Hu [] 
Hu (HFix f) 

Foldable higher-order functors

class FMonoid f whereSource

Polymorphic monoid class

Methods

fzero :: f aSource

fplus :: f a -> f a -> f aSource

Instances

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

class HFoldable f whereSource

Methods

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

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