unification-fd-0.11.0: Simple generic unification algorithms.
CopyrightCopyright (c) 2007--2015 wren gayle romano
LicenseBSD
Maintainerwren@community.haskell.org
Stabilityprovisional
Portabilitysemi-portable (Rank2Types)
Safe HaskellNone
LanguageHaskell98

Data.Functor.Fixedpoint

Description

This module provides a fixed point operator on functor types. For Haskell the least and greatest fixed points coincide, so we needn't distinguish them. This abstract nonsense is helpful in conjunction with other category theoretic tricks like Swierstra's functor coproducts (not provided by this package). For more on the utility of two-level recursive types, see:

  • Tim Sheard (2001) Generic Unification via Two-Level Types and Paramterized Modules, Functional Pearl, ICFP.
  • Tim Sheard & Emir Pasalic (2004) Two-Level Types and Parameterized Modules. JFP 14(5): 547--587. This is an expanded version of Sheard (2001) with new examples.
  • Wouter Swierstra (2008) Data types a la carte, Functional Pearl. JFP 18: 423--436.
Synopsis

Fixed point operator for functors

newtype Fix f Source #

Fix f is a fix point of the Functor f. Note that in Haskell the least and greatest fixed points coincide, so we don't need to distinguish between Mu f and Nu f. This type used to be called Y, hence the naming convention for all the yfoo functions.

This type lets us invoke category theory to get recursive types and operations over them without the type checker complaining about infinite types. The Show instance doesn't print the constructors, for legibility.

Constructors

Fix (f (Fix f)) 

Instances

Instances details
Eq (f (Fix f)) => Eq (Fix f) Source # 
Instance details

Defined in Data.Functor.Fixedpoint

Methods

(==) :: Fix f -> Fix f -> Bool #

(/=) :: Fix f -> Fix f -> Bool #

Ord (f (Fix f)) => Ord (Fix f) Source # 
Instance details

Defined in Data.Functor.Fixedpoint

Methods

compare :: Fix f -> Fix f -> Ordering #

(<) :: Fix f -> Fix f -> Bool #

(<=) :: Fix f -> Fix f -> Bool #

(>) :: Fix f -> Fix f -> Bool #

(>=) :: Fix f -> Fix f -> Bool #

max :: Fix f -> Fix f -> Fix f #

min :: Fix f -> Fix f -> Fix f #

Show (f (Fix f)) => Show (Fix f) Source # 
Instance details

Defined in Data.Functor.Fixedpoint

Methods

showsPrec :: Int -> Fix f -> ShowS #

show :: Fix f -> String #

showList :: [Fix f] -> ShowS #

unFix :: Fix f -> f (Fix f) Source #

Maps

hmap :: (Functor f, Functor g) => (forall a. f a -> g a) -> Fix f -> Fix g Source #

A higher-order map taking a natural transformation (f -> g) and lifting it to operate on Fix.

hmapM :: (Functor f, Traversable g, Monad m) => (forall a. f a -> m (g a)) -> Fix f -> m (Fix g) Source #

A monadic variant of hmap.

ymap :: Functor f => (Fix f -> Fix f) -> Fix f -> Fix f Source #

A version of fmap for endomorphisms on the fixed point. That is, this maps the function over the first layer of recursive structure.

ymapM :: (Traversable f, Monad m) => (Fix f -> m (Fix f)) -> Fix f -> m (Fix f) Source #

A monadic variant of ymap.

Builders

build :: Functor f => (forall r. (f r -> r) -> r) -> Fix f Source #

Take a Church encoding of a fixed point into the data representation of the fixed point.

Catamorphisms

cata :: Functor f => (f a -> a) -> Fix f -> a Source #

A pure catamorphism over the least fixed point of a functor. This function applies the f-algebra from the bottom up over Fix f to create some residual value.

cataM :: (Traversable f, Monad m) => (f a -> m a) -> Fix f -> m a Source #

A catamorphism for monadic f-algebras. Alas, this isn't wholly generic to Functor since it requires distribution of f over m (provided by sequence or mapM in Traversable).

N.B., this orders the side effects from the bottom up.

ycata :: Functor f => (Fix f -> Fix f) -> Fix f -> Fix f Source #

A variant of cata which restricts the return type to being a new fixpoint. Though more restrictive, it can be helpful when you already have an algebra which expects the outermost Fix.

If you don't like either fmap or cata, then maybe this is what you were thinking?

ycataM :: (Traversable f, Monad m) => (Fix f -> m (Fix f)) -> Fix f -> m (Fix f) Source #

Monadic variant of ycata.

Anamorphisms

ana :: Functor f => (a -> f a) -> a -> Fix f Source #

A pure anamorphism generating the greatest fixed point of a functor. This function applies an f-coalgebra from the top down to expand a seed into a Fix f.

anaM :: (Traversable f, Monad m) => (a -> m (f a)) -> a -> m (Fix f) Source #

An anamorphism for monadic f-coalgebras. Alas, this isn't wholly generic to Functor since it requires distribution of f over m (provided by sequence or mapM in Traversable).

N.B., this orders the side effects from the top down.

Hylomorphisms

hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b Source #

hylo phi psi == cata phi . ana psi

hyloM :: (Traversable f, Monad m) => (f b -> m b) -> (a -> m (f a)) -> a -> m b Source #

hyloM phiM psiM == cataM phiM <=< anaM psiM