invertible-0.2.0.3: bidirectional arrows, bijective functions, and invariant functors

Safe HaskellNone
LanguageHaskell2010

Control.Invertible.Monoidal.Free

Description

A vague analog of free monads for invariant monoidals. This can provide a simple basis for things like invertible parsers.

Synopsis

Documentation

data Free f a where Source #

Produce a MonoidalAlt out of any type constructor, simply by converting each monoidal operation into a constructor. Although a version more analogous to a free monad could be defined for instances of Functor and restricted to Monoidal, including the Yoneda transform makes this the more general case.

Constructors

Void :: Free f Void 
Empty :: Free f () 
Free :: !(f a) -> Free f a 
Join :: Free f a -> Free f b -> Free f (a, b) 
Choose :: Free f a -> Free f b -> Free f (Either a b) 
Transform :: (a <-> b) -> Free f a -> Free f b 

Instances

Functor (Free f) Source # 

Methods

fmap :: (a <-> b) -> Free f a -> Free f b Source #

MonoidalAlt (Free f) Source # 

Methods

zero :: Free f Void Source #

(>|<) :: Free f a -> Free f b -> Free f (Either a b) Source #

Monoidal (Free f) Source # 

Methods

unit :: Free f () Source #

(>*<) :: Free f a -> Free f b -> Free f (a, b) Source #

(Functor f, Show1 f) => Show (Free f a) Source # 

Methods

showsPrec :: Int -> Free f a -> ShowS #

show :: Free f a -> String #

showList :: [Free f a] -> ShowS #

showsFree :: (forall a'. f a' -> ShowS) -> Free f a -> ShowS Source #

Construct a string representation of a Free structure, given a way to show any f a.

mapFree :: (forall a'. f a' -> m a') -> Free f a -> Free m a Source #

Transform the type constructor within a Free.

foldFree :: Monoid b => (forall a'. f a' -> a' -> b) -> Free f a -> a -> b Source #

Given a way to extract a b from any f a, use a Free applied to a value to produce a b by converting >*< to <>.

produceFree :: Alternative m => (forall a'. f a' -> a' -> b) -> Free f a -> a -> m b Source #

foldFree over Alternative rather than Monoid.

runFree :: Alternative f => Free f a -> f a Source #

Evaluate a Free into an underlying Alternative, by evaluating >|< with <|>.

parseFree :: MonadPlus m => (forall a'. f a' -> b -> m a') -> Free f a -> [b] -> m (a, [b]) Source #

Given a way to convert b elements into any f a, use a Free to parse a list of b elements into a value. This just uses unconsState with runFree, and is the inverse of produceFree, provided the given conversions are themselves inverses.

reverseFree :: Free f a -> Free f a Source #

Flip the effective order of each >*< operation in a Free, so that processing is done in the reverse order. It probably goes without saying, but applying this to an infinite structure, such as those produced by manyI, will not terminate.

freeTNF :: Free f a -> Free f a Source #

Convert a Free to Transform Normal Form: extract and merge all the Transform, if any, to a single Transform at the top.

freeTDNF :: Free f a -> Free f a Source #

Convert a Free to Transform Disjunctive Normal Form: reorder the terms so thet at most one Transform is on the outside, followed by Choose terms, which are above all Join terms', with Empty and Free as leaves. Since each Join above a Choose creates a duplicate Join term, the complexity and result size can be exponential (just as with boolean logic DNF).

sortFreeTDNF :: (forall a' b'. f a' -> f b' -> Ordering) -> Free f a -> Free f a Source #

Equivalent to freeTDNF, but also sorts the terms within each Join clause to conform to the given ordering. The resulting Join trees will be right-linearized (Join x (Join y (Join z ...)) such that x <= y, y <= z, etc. THis performs a O(n^2) bubble sort on the already exponential TDNF.