Annotations-0.2.2: Constructing, analyzing and destructing annotated trees

Safe HaskellSafe
LanguageHaskell98

Annotations.MultiRec.ErrorAlg

Synopsis

Documentation

type family ErrorAlg (f :: (* -> *) -> * -> *) e a :: * Source #

Type family that converts pattern functors to convenient algebra types.

Instances

type ErrorAlg U e a Source # 
type ErrorAlg U e a = Either e a
type ErrorAlg ((:+:) f g) e a Source # 
type ErrorAlg ((:+:) f g) e a = (ErrorAlg f e a, ErrorAlg g e a)
type ErrorAlg ((:*:) (I xi) f) e a Source # 
type ErrorAlg ((:*:) (I xi) f) e a = a -> ErrorAlg f e a
type ErrorAlg ((:*:) (K b) f) e a Source # 
type ErrorAlg ((:*:) (K b) f) e a = b -> ErrorAlg f e a
type ErrorAlg ((:>:) f xi) e a Source # 
type ErrorAlg ((:>:) f xi) e a = ErrorAlg f e a

type ErrorAlg_PF f e a = forall ix. f (K0 a) ix -> Either e a Source #

An error algebra over pattern functors.

class MkErrorAlg f where Source #

Converts convenient algebras to algebras that are able to work with pattern functors.

Minimal complete definition

mkErrorAlg

Methods

mkErrorAlg :: ErrorAlg f e a -> ErrorAlg_PF f e a Source #

Instances

MkErrorAlg U Source # 

Methods

mkErrorAlg :: ErrorAlg U e a -> ErrorAlg_PF U e a Source #

(MkErrorAlg f, MkErrorAlg g) => MkErrorAlg ((:+:) f g) Source # 

Methods

mkErrorAlg :: ErrorAlg (f :+: g) e a -> ErrorAlg_PF (f :+: g) e a Source #

MkErrorAlg f => MkErrorAlg ((:*:) (I xi) f) Source # 

Methods

mkErrorAlg :: ErrorAlg (I xi :*: f) e a -> ErrorAlg_PF (I xi :*: f) e a Source #

MkErrorAlg f => MkErrorAlg ((:*:) (K a) f) Source # 

Methods

mkErrorAlg :: ErrorAlg (K a :*: f) e a -> ErrorAlg_PF (K a :*: f) e a Source #

MkErrorAlg f => MkErrorAlg ((:>:) f xi) Source # 

Methods

mkErrorAlg :: ErrorAlg (f :>: xi) e a -> ErrorAlg_PF (f :>: xi) e a Source #

errorCata :: HFunctor phi f => ErrorAlg_PF f e r -> phi ix -> HFix (K x :*: f) ix -> Except [(e, x)] r Source #

Reduces a tree to a value according to the algebra, collecting potential errors. The errors are combined with the annotations in the tree at the positions at which the errors occurred.

(&) :: a -> b -> (a, b) infixr 5 Source #

For constructing algebras that are made of nested pairs rather than n-ary tuples, it is helpful to use this pairing combinator.