semi-iso-1.0.0.0: Weakened partial isomorphisms, reversible computations.

Copyright(c) Paweł Nowak
LicenseMIT
MaintainerPaweł Nowak <pawel834@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.SIArrow

Contents

Description

Categories of reversible computations.

Synopsis

Arrow.

class (Products cat, Coproducts cat, CatPlus cat) => SIArrow cat where Source

A category equipped with an embedding siarr from SemiIso into cat and some additional structure.

SIArrow abstracts categories of reversible computations (with reversible side effects).

The category cat should contain SemiIso as a sort of "subcategory of pure computations".

Minimal complete definition

(siarr | sipure), sibind

Methods

siarr :: ASemiIso' a b -> cat a b Source

Allows you to lift a SemiIso into cat. The resulting arrow should be in some sense minimal or "pure", similiar to pure, return and arr from Control.Category.

sipure :: ASemiIso' b a -> cat a b Source

Reversed version of siarr.

Use this where you would use pure.

sibind :: ASemiIso a (cat a b) (cat a b) b -> cat a b Source

Allows a computation to depend on a its input value.

I am not sure if this is the right way to get that ArrowApply or Monad like power. It seems quite easy to break the parser/pretty-printer inverse guarantee using this. On the other hand we have to be careful only when constructing the SemiIso using 'iso'/'semiIso' - and with an invalid SemiIso we could break everything anyway using siarr.

sisome :: cat () b -> cat () [b] Source

sisome v repeats v as long as possible, but no less then once.

simany :: cat () b -> cat () [b] Source

simany v repeats v as long as possible.

Instances

(^>>) :: SIArrow cat => ASemiIso' a b -> cat b c -> cat a c infixr 1 Source

Composes a SemiIso with an arrow.

(>>^) :: SIArrow cat => cat a b -> ASemiIso' b c -> cat a c infixr 1 Source

Composes an arrow with a SemiIso.

(^<<) :: SIArrow cat => ASemiIso' b c -> cat a b -> cat a c infixr 1 Source

Composes a SemiIso with an arrow, backwards.

(<<^) :: SIArrow cat => cat b c -> ASemiIso' a b -> cat a c infixr 1 Source

Composes an arrow with a SemiIso, backwards.

(#>>) :: SIArrow cat => ASemiIso' b a -> cat b c -> cat a c infixr 1 Source

Composes a reversed SemiIso with an arrow.

(>>#) :: SIArrow cat => cat a b -> ASemiIso' c b -> cat a c infixr 1 Source

Composes an arrow with a reversed SemiIso.

(#<<) :: SIArrow cat => ASemiIso' c b -> cat a b -> cat a c infixr 1 Source

Composes a reversed SemiIso with an arrow, backwards.

(<<#) :: SIArrow cat => cat b c -> ASemiIso' b a -> cat a c infixr 1 Source

Composes an arrow with a reversed SemiIso, backwards.

Functor and applicative.

(/$/) :: SIArrow cat => ASemiIso' b' b -> cat a b -> cat a b' infixl 4 Source

Postcomposes an arrow with a reversed SemiIso. The analogue of <$> and synonym for '#<<'.

(/$~) :: (SIArrow cat, HFoldable b', HFoldable b, HUnfoldable b', HUnfoldable b, Rep b' ~ Rep b) => ASemiIso' a b' -> cat c b -> cat c a infixl 4 Source

Convenient fmap.

ai /$~ f = ai . morphed /$/ f

This operator handles all the hairy stuff with uncurried application: it reassociates the argument tuple and removes unnecessary (or adds necessary) units to match the function type. You don't have to use /* and */ with this operator.

(/*/) :: SIArrow cat => cat () b -> cat () c -> cat () (b, c) infixl 5 Source

The product of two arrows with duplicate units removed. Side effect are sequenced from left to right.

The uncurried analogue of <*>.

(/*) :: SIArrow cat => cat () a -> cat () () -> cat () a infixl 5 Source

The product of two arrows, where the second one has no input and no output (but can have side effects), with duplicate units removed. Side effect are sequenced from left to right.

The uncurried analogue of <*.

(*/) :: SIArrow cat => cat () () -> cat () a -> cat () a infixl 5 Source

The product of two arrows, where the first one has no input and no output (but can have side effects), with duplicate units removed. Side effect are sequenced from left to right.

The uncurried analogue of *>.

Signaling errors.

sifail :: SIArrow cat => String -> cat a b Source

An arrow that fails with an error message.

(/?/) :: SIArrow cat => cat a b -> String -> cat a b infixl 3 Source

Provides an error message in the case of failure.

Combinators.

sisequence :: SIArrow cat => [cat () a] -> cat () [a] Source

Equivalent of sequence.

sisequence_ :: SIArrow cat => [cat () ()] -> cat () () Source

Equivalent of sequence_, restricted to units.

sireplicate :: SIArrow cat => Int -> cat () a -> cat () [a] Source

Equivalent of replicateM.

sireplicate_ :: SIArrow cat => Int -> cat () () -> cat () () Source

Equivalent of replicateM_, restricted to units.