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

Safe HaskellSafe
LanguageHaskell2010

Control.Invertible.Monoidal

Contents

Description

Invariant monoidal functors.

This roughly corresponds to Control.Applicative, but exposes a non-overlapping API so can be imported unqualified. It does, however, use operators similar to those provided by contravariant.

Synopsis

Functor

(>$<) :: Functor f => (a <-> b) -> f a -> f b infixl 4 Source

Another synonym for fmap to match other operators in this module.

Monoidal

class Functor f => Monoidal f where Source

Lax invariant monoidal functor. This roughly corresponds to Applicative, which, for covariant functors, is equivalent to a monoidal functor. Invariant functors, however, may admit a monoidal instance but not applicative.

Methods

unit :: f () Source

Lift a unit value, analogous to pure () (but also like const ()).

(>*<) :: f a -> f b -> f (a, b) infixl 4 Source

Merge two functors into a tuple, analogous to liftA2 (,). (Sometimes known as **.)

Instances

(>*) :: Monoidal f => f a -> f () -> f a infixl 4 Source

Sequence actions, discarding/inhabiting the unit value of the second argument.

(*<) :: Monoidal f => f () -> f a -> f a infixl 4 Source

Sequence actions, discarding/inhabiting the unit value of the first argument.

Tuple combinators

liftI2 :: Monoidal f => ((a, b) <-> c) -> f a -> f b -> f c Source

Lift an (uncurried) bijection into a monoidal functor.

liftI3 :: Monoidal f => ((a, b, c) <-> d) -> f a -> f b -> f c -> f d Source

liftI4 :: Monoidal f => ((a, b, c, d) <-> e) -> f a -> f b -> f c -> f d -> f e Source

liftI5 :: Monoidal f => ((a, b, c, d, e) <-> g) -> f a -> f b -> f c -> f d -> f e -> f g Source

(>*<<) :: Monoidal f => f a -> f (b, c) -> f (a, b, c) infixr 3 Source

(>*<<<) :: Monoidal f => f a -> f (b, c, d) -> f (a, b, c, d) infixr 3 Source

(>*<<<<) :: Monoidal f => f a -> f (b, c, d, e) -> f (a, b, c, d, e) infixr 3 Source

(>>*<) :: Monoidal f => f (a, b) -> f c -> f (a, b, c) infixl 4 Source

(>>>*<) :: Monoidal f => f (a, b, c) -> f d -> f (a, b, c, d) infixl 4 Source

(>>>>*<) :: Monoidal f => f (a, b, c, d) -> f e -> f (a, b, c, d, e) infixl 4 Source

(>>*<<) :: Monoidal f => f (a, b) -> f (c, d) -> f (a, b, c, d) infix 3 Source

pureI :: Monoidal f => a -> f a Source

A constant monoidal (like pure), which always produces the same value and ignores everything.

sequenceMaybesI :: Monoidal f => [f (Maybe a)] -> f [a] Source

Sequence (like sequenceA) and filter (like catMaybes) a list of monoidals, producing the list of non-Nothing values. Shorter input lists pad with Nothings and longer ones are ignored.

mapMaybeI :: Monoidal f => (a -> f (Maybe b)) -> [a] -> f [b] Source

Map each element to a Maybe monoidal and sequence the results (like traverse and mapMaybe).

MonoidalAlt

class Monoidal f => MonoidalAlt f where Source

Monoidal functors that allow choice.

Methods

(>|<) :: f a -> f b -> f (Either a b) infixl 3 Source

Associative binary choice.

possible :: MonoidalAlt f => f a -> f (Maybe a) Source

Analogous to optional.

defaulting :: (MonoidalAlt f, Eq a) => a -> f a -> f a Source

Return a default value if a monoidal functor fails, and only apply it to non-default values.

while :: MonoidalAlt f => f a -> f [a] Source

Repeatedly apply a monoidal functor until it fails. Analogous to many.