Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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.
- (>$<) :: Functor f => (a <-> b) -> f a -> f b
- (>$) :: Functor f => a -> f a -> f ()
- ($<) :: Functor f => f a -> a -> f ()
- class Functor f => Monoidal f where
- (>*) :: Monoidal f => f a -> f () -> f a
- (*<) :: Monoidal f => f () -> f a -> f a
- liftI2 :: Monoidal f => ((a, b) <-> c) -> f a -> f b -> f c
- liftI3 :: Monoidal f => ((a, b, c) <-> d) -> f a -> f b -> f c -> f d
- liftI4 :: Monoidal f => ((a, b, c, d) <-> e) -> f a -> f b -> f c -> f d -> f e
- liftI5 :: Monoidal f => ((a, b, c, d, e) <-> g) -> f a -> f b -> f c -> f d -> f e -> f g
- (>*<<) :: Monoidal f => f a -> f (b, c) -> f (a, b, c)
- (>*<<<) :: Monoidal f => f a -> f (b, c, d) -> f (a, b, c, d)
- (>*<<<<) :: Monoidal f => f a -> f (b, c, d, e) -> f (a, b, c, d, e)
- (>>*<) :: Monoidal f => f (a, b) -> f c -> f (a, b, c)
- (>>>*<) :: Monoidal f => f (a, b, c) -> f d -> f (a, b, c, d)
- (>>>>*<) :: Monoidal f => f (a, b, c, d) -> f e -> f (a, b, c, d, e)
- (>>*<<) :: Monoidal f => f (a, b) -> f (c, d) -> f (a, b, c, d)
- pureI :: Monoidal f => a -> f a
- sequenceI_ :: (Foldable t, Monoidal f) => t (f ()) -> f ()
- mapI_ :: (Foldable t, Monoidal f) => (a -> f ()) -> t a -> f ()
- forI_ :: (Foldable t, Monoidal f) => t a -> (a -> f ()) -> f ()
- sequenceMaybesI :: Monoidal f => [f (Maybe a)] -> f [a]
- mapMaybeI :: Monoidal f => (a -> f (Maybe b)) -> [a] -> f [b]
- class Monoidal f => MonoidalAlt f where
- (>|) :: MonoidalAlt f => f a -> f a -> f a
- (|<) :: MonoidalAlt f => f a -> f a -> f a
- optionalI :: MonoidalAlt f => f a -> f (Maybe a)
- defaulting :: (MonoidalAlt f, Eq a) => a -> f a -> f a
- manyI :: MonoidalAlt f => f a -> f [a]
- msumIndex :: MonoidalAlt f => [f ()] -> f Int
- msumFirst :: (MonoidalAlt f, Traversable t) => t (f a) -> f a
- msumLast :: (MonoidalAlt f, Traversable t) => t (f a) -> f a
- oneOfI :: (MonoidalAlt f, Eq a) => (a -> f ()) -> [a] -> f a
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 #
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.
(>*) :: 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.
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 (
) all the results.const
()
mapI_ :: (Foldable t, Monoidal f) => (a -> f ()) -> t a -> f () Source #
Map each element to a monoidal and sequenceI_
the results.
sequenceMaybesI :: Monoidal f => [f (Maybe a)] -> f [a] Source #
MonoidalAlt
class Monoidal f => MonoidalAlt f where Source #
Monoidal functors that allow choice.
MonoidalAlt (Free f) 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.
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 #
msumLast :: (MonoidalAlt f, Traversable t) => t (f a) -> f a Source #
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).