Copyright | (c) 2011 diagrams-core team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Monoid and semigroup actions.
Synopsis
- class Action m s where
- act :: m -> s -> s
- newtype Regular m = Regular {
- getRegular :: m
- newtype Conjugate m = Conjugate {
- getConjugate :: m
- class Group m => Torsor m s where
- difference :: s -> s -> m
Documentation
class Action m s where Source #
Type class for monoid (and semigroup) actions, where monoidal
values of type m
"act" on values of another type s
.
Instances are required to satisfy the laws
act mempty = id
act (m1 `mappend` m2) = act m1 . act m2
Semigroup instances are required to satisfy the second law but with
(<>
) instead of mappend
. Additionally, if the type s
has
any algebraic structure, act m
should be a homomorphism. For
example, if s
is also a monoid we should have act m mempty =
mempty
and act m (s1 `mappend` s2) = (act m s1) `mappend`
(act m s2)
.
By default, act = const id
, so for a type M
which should have
no action on anything, it suffices to write
instance Action M s
with no method implementations.
It is a bit awkward dealing with instances of Action
, since it
is a multi-parameter type class but we can't add any functional
dependencies---the relationship between monoids and the types on
which they act is truly many-to-many. In practice, this library
has chosen to have instance selection for Action
driven by the
first type parameter. That is, you should never write an
instance of the form Action m SomeType
since it will overlap
with instances of the form Action SomeMonoid t
. Newtype
wrappers can be used to (awkwardly) get around this.
Nothing
Instances
Action () l Source # |
|
Defined in Data.Monoid.Action | |
Fractional a => Action Rational (Product a) Source # | |
Fractional a => Action Rational (Sum a) Source # | |
Num a => Action Integer (Product a) Source # | |
Num a => Action Integer (Sum a) Source # | |
Group m => Action m (Conjugate m) Source # | |
Semigroup m => Action m (Regular m) Source # | |
Action (Endo a) a Source # |
Note that in order for this instance to satisfy the |
Defined in Data.Monoid.Action | |
Action (SM a) () Source # | |
Defined in Data.Monoid.MList | |
Action m n => Action (Split m) n Source # | By default, the action of a split monoid is the same as for the underlying monoid, as if the split were removed. |
Defined in Data.Monoid.Split | |
Action m s => Action (Maybe m) s Source # |
|
Defined in Data.Monoid.Action | |
(Action a a', Action (SM a) l) => Action (SM a) (Maybe a', l) 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 | |
(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. |
Defined in Data.Monoid.Coproduct.Strict | |
(Action (SM a) l2, Action l1 l2) => Action (a, l1) l2 Source # | |
Defined in Data.Monoid.MList |
Any monoid acts on itself by left multiplication.
This newtype witnesses this action:
getRegular
$ Regular
m1 `act
` Regular
m2 = m1 <>
m2
Regular | |
|
Any group acts on itself by conjugation.
Conjugate | |
|
class Group m => Torsor m s where Source #
An action of a group is "free transitive", "regular", or a "torsor" iff it is invertible.
Given an original value sOrig
, and a value sActed
that is the result
of acting on sOrig
by some m
,
it is possible to recover this m
.
This is encoded in the laws:
(m `
act
` s) `difference
` s = m(sActed `
difference
` sOrig) `act
` sOrig = sActed
difference :: s -> s -> m Source #
is the element difference
sActed sOrigm
such that sActed = m `
.act
` sOrig