Annotations-0.2.2: Constructing, analyzing and destructing annotated trees

Safe HaskellSafe
LanguageHaskell98

Annotations.F.Fixpoints

Contents

Synopsis

Fixed points of functors

newtype Fix fT Source #

Fixpoint of functors.

Constructors

In 

Fields

Instances

Eq (f (Fix f)) => Eq (Fix f) Source # 

Methods

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

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

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

Methods

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

show :: Fix f -> String #

showList :: [Fix f] -> ShowS #

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

Apply a transformation to a tree's direct children.

type Algebra fT aT = fT aT -> aT Source #

Algebras for catamorphisms.

cata :: Functor fT => Algebra fT aT -> Fix fT -> aT Source #

Reduces a tree to a value according to the algebra.

type Coalgebra fT aT = aT -> fT aT Source #

Coalgebras for anamorphisms.

ana :: Functor fT => Coalgebra fT aT -> aT -> Fix fT Source #

Constructs a tree from a value according to the coalgebra.

type ErrorAlgebra fT eT aT = fT aT -> Either eT aT Source #

Algebras for error catamorphisms.

cascade :: (Traversable fT, Monoid eT) => ErrorAlgebra fT eT aT -> Algebra fT (Except eT aT) Source #

Reduces a tree to a value according to the algebra, propagating potential errors.