Safe Haskell | None |
---|---|
Language | Haskell2010 |
An Act of a semigroup \( S \) on a type \( X \) gives a way to transform terms of type \( X \) by terms of type \( S \), in a way that is compatible with the semigroup operation on \( S \).
In the special case that there is a unique way of going from one term of type \( X \) to another through a transformation by a term of type \( S \), we say that \( X \) is a torsor under \( S \).
For example, the plane has an action by translations. Given any two points, there is a unique translation that takes the first point to the second. Note that an unmarked plane (like a blank piece of paper) has no designated origin or reference point, whereas the set of translations is a plane with a given origin (the zero translation). This is the distinction between an affine space (an unmarked plane) and a vector space. Enforcing this distinction in the types can help to avoid confusing absolute points with translation vectors.
Simple Act
and Torsor
instances can be derived through self-actions:
> newtype Seconds = Seconds { getSeconds :: Double } > deriving ( Act TimeDelta, Torsor TimeDelta ) > via TimeDelta > newtype TimeDelta = TimeDelta { timeDeltaInSeconds :: Seconds } > deriving ( Semigroup, Monoid, Group ) > via Sum Double
Synopsis
- class Semigroup s => Act s x where
- transportAction :: (a -> b) -> (b -> a) -> (g -> b -> b) -> g -> a -> a
- newtype Trivial a = Trivial {
- getTrivial :: a
- class (Group g, Act g x) => Torsor g x where
- intertwiner :: forall h g a b. (Act g a, Torsor h b) => g -> (a -> b) -> a -> h
Documentation
class Semigroup s => Act s x where Source #
A left act (or left semigroup action) of a semigroup s
on x
consists of an operation
(•) :: s -> x -> x
such that:
a • ( b • x ) = ( a <> b ) • x
In case s
is also a Monoid
, we additionally require:
mempty • x = x
The synonym act = (•)
is also provided.
(•) :: s -> x -> x infixr 5 Source #
Left action of a semigroup.
act :: s -> x -> x infixr 5 Source #
Left action of a semigroup.
Instances
Act () x Source # | |
Semigroup s => Act s s Source # | Natural left action of a semigroup on itself. |
Act All Bool Source # | |
Act Any Bool Source # | |
(Group g, Act g a) => Act g (Endo a) Source # | Action of a group on endomorphisms. |
Semigroup s => Act s (Trivial a) Source # | |
(Act s x, Functor f) => Act s (Ap f x) Source # | Acting through a functor using |
Act s a => Act s (Const a b) Source # | |
Ord a => Act (Min a) a Source # | |
Ord a => Act (Max a) a Source # | |
(Act g x, Group g) => Act (Dual g) x Source # | Action of an opposite group using inverses. |
Num a => Act (Sum a) a Source # | |
Num a => Act (Product a) a Source # | |
KnownNat n => Act (Cyclic n) Int Source # | |
Act (Cyclic 2) Bool Source # | |
(Enum a, Bounded a, KnownNat n) => Act (Cyclic n) (CyclicEnum a) Source # | |
Defined in Data.Group.Cyclic (•) :: Cyclic n -> CyclicEnum a -> CyclicEnum a Source # act :: Cyclic n -> CyclicEnum a -> CyclicEnum a Source # | |
Num a => Act (Cyclic 2) (Complex a) Source # | |
Num i => Act (Cyclic 2) (Sum i) Source # | |
Fractional i => Act (Cyclic 2) (Product i) Source # | |
(Semigroup s, Act s a) => Act (Dual s) (Op b a) Source # | Acting through the contravariant function arrow functor. |
(Act s1 x1, Act s2 x2) => Act (s1, s2) (x1, x2) Source # | |
(Semigroup s, Act s a, Act t b) => Act (Dual s, t) (a -> b) Source # | Acting through a function arrow: both covariant and contravariant actions. |
(Act s1 x1, Act s2 x2, Act s3 x3) => Act (s1, s2, s3) (x1, x2, x3) Source # | |
(Act s1 x1, Act s2 x2, Act s3 x3, Act s4 x4) => Act (s1, s2, s3, s4) (x1, x2, x3, x4) Source # | |
(Act s1 x1, Act s2 x2, Act s3 x3, Act s4 x4, Act s5 x5) => Act (s1, s2, s3, s4, s5) (x1, x2, x3, x4, x5) Source # | |
transportAction :: (a -> b) -> (b -> a) -> (g -> b -> b) -> g -> a -> a Source #
Transport an act:
Trivial act of a semigroup on any type (acting by the identity).
Trivial | |
|
Instances
Semigroup s => Act s (Trivial a) Source # | |
Bounded a => Bounded (Trivial a) Source # | |
Enum a => Enum (Trivial a) Source # | |
Defined in Data.Act succ :: Trivial a -> Trivial a # pred :: Trivial a -> Trivial a # fromEnum :: Trivial a -> Int # enumFrom :: Trivial a -> [Trivial a] # enumFromThen :: Trivial a -> Trivial a -> [Trivial a] # enumFromTo :: Trivial a -> Trivial a -> [Trivial a] # enumFromThenTo :: Trivial a -> Trivial a -> Trivial a -> [Trivial a] # | |
Eq a => Eq (Trivial a) Source # | |
Data a => Data (Trivial a) Source # | |
Defined in Data.Act gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Trivial a -> c (Trivial a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Trivial a) # toConstr :: Trivial a -> Constr # dataTypeOf :: Trivial a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Trivial a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Trivial a)) # gmapT :: (forall b. Data b => b -> b) -> Trivial a -> Trivial a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Trivial a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Trivial a -> r # gmapQ :: (forall d. Data d => d -> u) -> Trivial a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Trivial a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Trivial a -> m (Trivial a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Trivial a -> m (Trivial a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Trivial a -> m (Trivial a) # | |
Ord a => Ord (Trivial a) Source # | |
Defined in Data.Act | |
Read a => Read (Trivial a) Source # | |
Show a => Show (Trivial a) Source # | |
Generic (Trivial a) Source # | |
NFData a => NFData (Trivial a) Source # | |
Generic1 Trivial Source # | |
type Rep (Trivial a) Source # | |
type Rep1 Trivial Source # | |
class (Group g, Act g x) => Torsor g x where Source #
A left torsor consists of a free and transitive left action of a group on an inhabited type.
This precisely means that for any two terms x
, y
, there exists a unique group element g
taking x
to y
,
which is denoted y <-- x
(or x --> y
, but the left-pointing arrow is more natural when working with left actions).
That is y <-- x
is the unique element satisfying:
( y <-- x ) • x = y
Note the order of composition of <--
and -->
with respect to <>
:
( z <-- y ) <> ( y <-- x ) = z <-- x
( y --> z ) <> ( x --> y ) = x --> z
(<--) :: x -> x -> g infix 7 Source #
Unique group element effecting the given transition
(-->) :: x -> x -> g infix 7 Source #
Unique group element effecting the given transition
Instances
Group g => Torsor g g Source # | Any group is a torsor under its own natural left action. |
Num a => Torsor (Sum a) a Source # | |
(Enum a, Bounded a, KnownNat n, 1 <= n) => Torsor (Cyclic n) (CyclicEnum a) Source # | |
Defined in Data.Group.Cyclic (<--) :: CyclicEnum a -> CyclicEnum a -> Cyclic n Source # (-->) :: CyclicEnum a -> CyclicEnum a -> Cyclic n Source # |
intertwiner :: forall h g a b. (Act g a, Torsor h b) => g -> (a -> b) -> a -> h Source #
Given
- \( g \in G \) acting on \( A \),
- \( B \) a torsor under \( H \),
- a map \( p \colon A \to B \),
this function returns the unique element \( h \in H \) making the following diagram commute: