invertible-0.1.2: 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.

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

Given a value an an invariant for that value, always provide that value and ignore the produced value. fmap . flip consts ()

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

flip (>$)

Monoidal

class Functor f => Monoidal f where Source #

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.

Minimal complete definition

unit, (>*<)

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 (Free f) Source # 

Methods

unit :: Free f () Source #

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

Monoidal (Bijection (->) ()) Source # 

Methods

unit :: Bijection (->) () () Source #

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

(>*) :: 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.

sequenceI_ :: (Foldable t, Monoidal f) => t (f ()) -> f () Source #

Sequence (like sequenceA_) a list of monoidals, ignoring (const ()) all the results.

mapI_ :: (Foldable t, Monoidal f) => (a -> f ()) -> t a -> f () Source #

Map each element to a monoidal and sequenceI_ the results.

forI_ :: (Foldable t, Monoidal f) => t a -> (a -> f ()) -> f () Source #

flip mapI_

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.

Minimal complete definition

(>|<)

Methods

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

Associative binary choice.

Instances

MonoidalAlt (Free f) Source # 

Methods

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

(>|) :: MonoidalAlt f => f a -> f a -> f a infixl 3 Source #

Assymetric (and therefore probably not bijective) version of >|< that returns whichever action succeeds but always uses the left one on inputs.

(|<) :: MonoidalAlt f => f a -> f a -> f a infixl 3 Source #

Assymetric (and therefore probably not bijective) version of >|< that returns whichever action succeeds but always uses the right one on inputs.

optionalI :: 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.

manyI :: MonoidalAlt f => f a -> f [a] Source #

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

msumIndex :: MonoidalAlt f => [f ()] -> f Int Source #

Try a list of monoidal actions in sequence, producing the index of the first successful action, and evaluating the action with the given index.

msumFirst :: (MonoidalAlt f, Traversable t) => t (f a) -> f a Source #

Fold a structure with >| (|<), thus always applying the input to the first (last) item for generation.

msumLast :: (MonoidalAlt f, Traversable t) => t (f a) -> f a Source #

Fold a structure with >| (|<), thus always applying the input to the first (last) item for generation.

oneOfI :: (MonoidalAlt f, Eq a) => (a -> f ()) -> [a] -> f a Source #

Take a list of items and apply them to the action in sequence until one succeeds and return the cooresponding item; match the input with the list and apply the corresponding action (or produce an error if the input is not an element of the list).