monoid-extras-0.7: Various extra monoid-related definitions and utilities
Copyright(c) 2011-2015 diagrams-core team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.Coproduct

Description

The coproduct of two monoids.

Synopsis

Documentation

data m :+: n Source #

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

Instances details
Monoid (m :+: n) Source #

The coproduct of two monoids is itself a monoid.

Instance details

Defined in Data.Monoid.Coproduct

Methods

mempty :: m :+: n #

mappend :: (m :+: n) -> (m :+: n) -> m :+: n #

mconcat :: [m :+: n] -> m :+: n #

Semigroup (m :+: n) Source # 
Instance details

Defined in Data.Monoid.Coproduct

Methods

(<>) :: (m :+: n) -> (m :+: n) -> m :+: n #

sconcat :: NonEmpty (m :+: n) -> m :+: n #

stimes :: Integral b => b -> (m :+: n) -> m :+: n #

(Show m, Show n) => Show (m :+: n) Source # 
Instance details

Defined in Data.Monoid.Coproduct

Methods

showsPrec :: Int -> (m :+: n) -> ShowS #

show :: (m :+: n) -> String #

showList :: [m :+: n] -> ShowS #

(Eq m, Eq n, Monoid m, Monoid n) => Eq (m :+: n) Source # 
Instance details

Defined in Data.Monoid.Coproduct

Methods

(==) :: (m :+: n) -> (m :+: n) -> Bool #

(/=) :: (m :+: n) -> (m :+: n) -> Bool #

(Action m r, Action n r) => Action (m :+: n) r Source #

Coproducts act on other things by having each of the components act individually.

Instance details

Defined in Data.Monoid.Coproduct

Methods

act :: (m :+: n) -> r -> r Source #

inL :: m -> m :+: n Source #

Injection from the left monoid into a coproduct.

inR :: n -> m :+: n Source #

Injection from the right monoid into a coproduct.

mappendL :: m -> (m :+: n) -> m :+: n Source #

Prepend a value from the left monoid.

mappendR :: n -> (m :+: n) -> m :+: n Source #

Prepend a value from the right monoid.

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.

untangleSemi :: (Action m n, Monoid m, Monoid n) => (m :+: n) -> Semi n m Source #

The copairing of embed and inject homomorphisms into the semidirect product. Note that embed and inject are monoid homomorphisms. Therefore untangleSemi is also a monoid homomorphism.