pointless-haskell-0.0.2: Pointless Haskell library

Portabilitynon-portable
Stabilityexperimental
Maintainerhpacheco@di.uminho.pt

Generics.Pointless.Bifunctors

Contents

Description

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

This module defines polymorphic data types as fixed points of bifunctor. 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

Bifunctors

newtype BId a x Source

Constructors

BId 

Fields

unBId :: x
 

newtype BConst t a x Source

Constructors

BConst 

Fields

unBConst :: t
 

Instances

newtype BPar a x Source

Constructors

Par 

Fields

unPar :: a
 

data (g :+| h) a x Source

Constructors

BInl (g a x) 
BInr (h a x) 

Instances

data (g :*| h) a x Source

Constructors

BProd (g a x) (h a x) 

Instances

newtype (g :@| h) a x Source

Constructors

BComp 

Fields

unBComp :: g a (h a x)
 

Instances

(Bifunctor g, Bifunctor h) => Bifunctor (:@| g h) 

newtype BFix f Source

Constructors

BFix 

Fields

unBFix :: f (BFix f) (BFix f)
 

type family BF f :: * -> * -> *Source

type family BRep f a :: * -> *Source

class Bifunctor f whereSource

Methods

bmap :: BFix f -> (a -> b) -> (x -> y) -> Rep (BRep f a) x -> Rep (BRep f b) ySource

type B d a x = Rep (BRep (BF d) a) xSource

class Bimu d whereSource

Methods

binn :: B d a (d a) -> d aSource

bout :: d a -> B d a (d a)Source

Instances

Bimu [] 
Bimu BI 
Bimu (BK a) 
Bimu (:@!| a b) 
Bimu (:*!| a b) 
Bimu (:+!| a b) 

pbmap :: Bifunctor (BF d) => d a -> (a -> b) -> (x -> y) -> B d a x -> B d b ySource

Fixpoint combinators

data BI x Source

Constructors

FixBId 

Instances

data BK a x Source

Constructors

FixBConst 

Fields

unFixBConst :: a
 

Instances

Bimu (BK a) 

data (a :+!| b) x Source

Constructors

FixBSum 

Fields

unFixBSum :: B (a :+!| b) x ((a :+!| b) x)
 

Instances

Bimu (:+!| a b) 

data (a :*!| b) x Source

Constructors

FixBProd 

Fields

unFixBProd :: B (a :*!| b) x ((a :*!| b) x)
 

Instances

Bimu (:*!| a b) 

data (a :@!| b) x Source

Constructors

FixBComp 

Fields

unFixBComp :: B (a :@!| b) x ((a :@!| b) x)
 

Instances

Bimu (:@!| a b) 

Default definitions for commonly used data types

Lists