Copyright | (c) 2011-2015 diagrams-core team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Data.Monoid.Coproduct
Description
The coproduct of two monoids.
Synopsis
- data m :+: n
- inL :: m -> m :+: n
- inR :: n -> m :+: n
- mappendL :: m -> (m :+: n) -> m :+: n
- mappendR :: n -> (m :+: n) -> m :+: n
- cop :: Monoid k => (m -> k) -> (n -> k) -> (m :+: n) -> k
- killL :: Monoid n => (m :+: n) -> n
- killR :: Monoid m => (m :+: n) -> m
- toAltList :: (Semigroup m, Semigroup n) => (m :+: n) -> [Either m n]
- toReducedAltList :: (Eq m, Eq n, Monoid m, Monoid n) => (m :+: n) -> [Either m n]
- untangle :: (Action m n, Monoid m, Monoid n) => (m :+: n) -> (m, n)
- untangleSemi :: (Action m n, Monoid m, Monoid n) => (m :+: n) -> Semi n m
Documentation
m :+: n
is the coproduct of monoids m
and n
. Values of
type m :+: n
consist of alternating lists of m
and n
values. The empty list is the identity, and composition is list
concatenation, with appropriate combining of adjacent elements
and removing identities when possible.
Instances
Monoid (m :+: n) Source # | The coproduct of two monoids is itself a monoid. |
Semigroup (m :+: n) Source # | |
(Show m, Show n) => Show (m :+: n) Source # | |
(Eq m, Eq n, Monoid m, Monoid n) => Eq (m :+: n) Source # | |
(Action m r, Action n r) => Action (m :+: n) r Source # | Coproducts act on other things by having each of the components act individually. |
Defined in Data.Monoid.Coproduct |
cop :: Monoid k => (m -> k) -> (n -> k) -> (m :+: n) -> k Source #
Universal map of the coproduct. The name cop
is an abbreviation
for copairing. Both functions in the signature should be monoid
homomorphisms. If they are general functions then the copairing may
not be well defined in the sense that it may send equal elements to
unequal elements. This is also the reason why cop
is not the
Data.Bifoldable.bifoldMap
function even though they have the same
signature.
killL :: Monoid n => (m :+: n) -> n Source #
killL
takes a value in a coproduct monoid and sends all the
values from the left monoid to the identity.
killR :: Monoid m => (m :+: n) -> m Source #
killR
takes a value in a coproduct monoid and sends all the
values from the right monoid to the identity.
toAltList :: (Semigroup m, Semigroup n) => (m :+: n) -> [Either m n] Source #
Extract a monoid coproduct to a list of Either
values. The
resulting list is guaranteed to be normalized, in the sense that
it will strictly alternate between Left
and Right
.
toReducedAltList :: (Eq m, Eq n, Monoid m, Monoid n) => (m :+: n) -> [Either m n] Source #
Extract a monoid coproduct to a list of Either
values. The
resulting list is guaranteed to be normalized, in the sense that
it will strictly alternate between Left
and Right
and no identity
element from m
or n
will occur in the list.
untangle :: (Action m n, Monoid m, Monoid n) => (m :+: n) -> (m, n) Source #
Same as untangleSemi
but the result is uwrapped. Concretely, given
a value from a coproduct monoid where the left monoid has an
action on the right, and "untangle" it into a pair of values. In
particular,
m1 <> n1 <> m2 <> n2 <> m3 <> n3 <> ...
is sent to
(m1 <> m2 <> m3 <> ..., (act m1 n1) <> (act (m1 <> m2) n2) <> (act (m1 <> m2 <> m3) n3) <> ...)
That is, before combining n
values, every n
value is acted on
by all the m
values to its left.