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

Data.Monoid.Coproduct.Strict

Description

A strict coproduct of two monoids.

Synopsis

Coproduct

data m :+: n Source #

m :+: n is the coproduct of monoids m and n. Concatentation is equivilent to

(m1 :+: n1) <> (m2 :+: n2) = (m1 <> m2) :+: (n1 <> act m1 n2)@

but has a more efficient internal implimentation.

Instances

Instances details
(Action m n, Monoid m, Monoid' n, Show m, Show n) => Show (m :+: n) Source # 
Instance details

Defined in Data.Monoid.Coproduct.Strict

Methods

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

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

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

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

Defined in Data.Monoid.Coproduct.Strict

Methods

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

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

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

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

Defined in Data.Monoid.Coproduct.Strict

Methods

mempty :: m :+: n #

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

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

(Action m n, Action m r, Action n r, Semigroup n) => 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.Strict

Methods

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

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

Construct a coproduct with a left value.

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

Construct a coproduct with a right value.

prependL :: Semigroup m => m -> (m :+: n) -> m :+: n Source #

Prepend a value from the left.

prependR :: Semigroup n => n -> (m :+: n) -> m :+: n Source #

Prepend a value from the right.

killL :: (Action m n, Monoid' n) => (m :+: n) -> n Source #

Extract n from a coproduct.

killR :: Monoid m => (m :+: n) -> m Source #

Extract m from a coproduct.

untangle :: (Action m n, Monoid m, Monoid' n) => (m :+: n) -> (m, n) Source #

Lenses

untangled :: (Action m n, Monoid m, Monoid' n) => Lens (m :+: n) (m' :+: n') (m, n) (m', n') Source #

Lens onto the both m and n.

_L :: (Action m n, Monoid m, Semigroup n) => Lens (m :+: n) (m' :+: n) m m' Source #

Lens onto the left value of a coproduct.

_R :: (Action m n, Monoid' n) => Lens (m :+: n) (m :+: n') n n' Source #

Lens onto the right value of a coproduct.