acts-0.3.0.0: Semigroup actions, groups, and torsors.
Safe HaskellNone
LanguageHaskell2010

Data.Act

Description

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

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.

Minimal complete definition

(•) | act

Methods

(•) :: s -> x -> x infixr 5 Source #

Left action of a semigroup.

act :: s -> x -> x infixr 5 Source #

Left action of a semigroup.

Instances

Instances details
Act () x Source # 
Instance details

Defined in Data.Act

Methods

(•) :: () -> x -> x Source #

act :: () -> x -> x Source #

Semigroup s => Act s s Source #

Natural left action of a semigroup on itself.

Instance details

Defined in Data.Act

Methods

(•) :: s -> s -> s Source #

act :: s -> s -> s Source #

Act All Bool Source # 
Instance details

Defined in Data.Act

Methods

(•) :: All -> Bool -> Bool Source #

act :: All -> Bool -> Bool Source #

Act Any Bool Source # 
Instance details

Defined in Data.Act

Methods

(•) :: Any -> Bool -> Bool Source #

act :: Any -> Bool -> Bool Source #

(Semigroup s, Act s (Finite n), Finitary a, n ~ Cardinality a) => Act s (Finitely a) Source #

Act on a type through its Finitary instance.

Instance details

Defined in Data.Act

Methods

(•) :: s -> Finitely a -> Finitely a Source #

act :: s -> Finitely a -> Finitely a Source #

(Group g, Act g a) => Act g (Endo a) Source #

Action of a group on endomorphisms.

Instance details

Defined in Data.Act

Methods

(•) :: g -> Endo a -> Endo a Source #

act :: g -> Endo a -> Endo a Source #

Semigroup s => Act s (Trivial a) Source # 
Instance details

Defined in Data.Act

Methods

(•) :: s -> Trivial a -> Trivial a Source #

act :: s -> Trivial a -> Trivial a Source #

(Act s x, Functor f) => Act s (Ap f x) Source #

Acting through a functor using fmap.

Instance details

Defined in Data.Act

Methods

(•) :: s -> Ap f x -> Ap f x Source #

act :: s -> Ap f x -> Ap f x Source #

Act s a => Act s (Const a b) Source # 
Instance details

Defined in Data.Act

Methods

(•) :: s -> Const a b -> Const a b Source #

act :: s -> Const a b -> Const a b Source #

Num a => Act (Sum a) a Source # 
Instance details

Defined in Data.Act

Methods

(•) :: Sum a -> a -> a Source #

act :: Sum a -> a -> a Source #

Num a => Act (Product a) a Source # 
Instance details

Defined in Data.Act

Methods

(•) :: Product a -> a -> a Source #

act :: Product a -> a -> a Source #

(Semigroup s, Act s a) => Act (Dual s) (Op b a) Source #

Acting through the contravariant function arrow functor: right action.

If acting by a group, use `anti :: Group g => g -> Dual g` to act by the original group instead of the opposite group.

Instance details

Defined in Data.Act

Methods

(•) :: Dual s -> Op b a -> Op b a Source #

act :: Dual s -> Op b a -> Op b a Source #

(Act s1 x1, Act s2 x2) => Act (s1, s2) (x1, x2) Source # 
Instance details

Defined in Data.Act

Methods

(•) :: (s1, s2) -> (x1, x2) -> (x1, x2) Source #

act :: (s1, s2) -> (x1, x2) -> (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.

If acting by a group, use `anti :: Group g => g -> Dual g` to act by the original group instead of the opposite group.

Instance details

Defined in Data.Act

Methods

(•) :: (Dual s, t) -> (a -> b) -> a -> b Source #

act :: (Dual s, t) -> (a -> b) -> a -> b Source #

(Act s1 x1, Act s2 x2, Act s3 x3) => Act (s1, s2, s3) (x1, x2, x3) Source # 
Instance details

Defined in Data.Act

Methods

(•) :: (s1, s2, s3) -> (x1, x2, x3) -> (x1, x2, x3) Source #

act :: (s1, s2, s3) -> (x1, x2, x3) -> (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 # 
Instance details

Defined in Data.Act

Methods

(•) :: (s1, s2, s3, s4) -> (x1, x2, x3, x4) -> (x1, x2, x3, x4) Source #

act :: (s1, s2, s3, s4) -> (x1, x2, x3, x4) -> (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 # 
Instance details

Defined in Data.Act

Methods

(•) :: (s1, s2, s3, s4, s5) -> (x1, x2, x3, x4, x5) -> (x1, x2, x3, x4, x5) Source #

act :: (s1, s2, s3, s4, s5) -> (x1, x2, x3, x4, x5) -> (x1, x2, x3, x4, x5) Source #

transportAction :: (a -> b) -> (b -> a) -> (g -> b -> b) -> g -> a -> a Source #

Transport an act:

newtype Trivial a Source #

Trivial act of a semigroup on any type (acting by the identity).

Constructors

Trivial 

Fields

Instances

Instances details
Semigroup s => Act s (Trivial a) Source # 
Instance details

Defined in Data.Act

Methods

(•) :: s -> Trivial a -> Trivial a Source #

act :: s -> Trivial a -> Trivial a Source #

Bounded a => Bounded (Trivial a) Source # 
Instance details

Defined in Data.Act

Enum a => Enum (Trivial a) Source # 
Instance details

Defined in Data.Act

Methods

succ :: Trivial a -> Trivial a #

pred :: Trivial a -> Trivial a #

toEnum :: Int -> 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 # 
Instance details

Defined in Data.Act

Methods

(==) :: Trivial a -> Trivial a -> Bool #

(/=) :: Trivial a -> Trivial a -> Bool #

Data a => Data (Trivial a) Source # 
Instance details

Defined in Data.Act

Methods

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 # 
Instance details

Defined in Data.Act

Methods

compare :: Trivial a -> Trivial a -> Ordering #

(<) :: Trivial a -> Trivial a -> Bool #

(<=) :: Trivial a -> Trivial a -> Bool #

(>) :: Trivial a -> Trivial a -> Bool #

(>=) :: Trivial a -> Trivial a -> Bool #

max :: Trivial a -> Trivial a -> Trivial a #

min :: Trivial a -> Trivial a -> Trivial a #

Read a => Read (Trivial a) Source # 
Instance details

Defined in Data.Act

Show a => Show (Trivial a) Source # 
Instance details

Defined in Data.Act

Methods

showsPrec :: Int -> Trivial a -> ShowS #

show :: Trivial a -> String #

showList :: [Trivial a] -> ShowS #

Generic (Trivial a) Source # 
Instance details

Defined in Data.Act

Associated Types

type Rep (Trivial a) :: Type -> Type #

Methods

from :: Trivial a -> Rep (Trivial a) x #

to :: Rep (Trivial a) x -> Trivial a #

NFData a => NFData (Trivial a) Source # 
Instance details

Defined in Data.Act

Methods

rnf :: Trivial a -> () #

Generic1 Trivial Source # 
Instance details

Defined in Data.Act

Associated Types

type Rep1 Trivial :: k -> Type #

Methods

from1 :: forall (a :: k). Trivial a -> Rep1 Trivial a #

to1 :: forall (a :: k). Rep1 Trivial a -> Trivial a #

type Rep (Trivial a) Source # 
Instance details

Defined in Data.Act

type Rep (Trivial a) = D1 ('MetaData "Trivial" "Data.Act" "acts-0.3.0.0-inplace" 'True) (C1 ('MetaCons "Trivial" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTrivial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Rep1 Trivial Source # 
Instance details

Defined in Data.Act

type Rep1 Trivial = D1 ('MetaData "Trivial" "Data.Act" "acts-0.3.0.0-inplace" 'True) (C1 ('MetaCons "Trivial" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTrivial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

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

Minimal complete definition

(-->) | (<--)

Methods

(<--) :: 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

Instances details
Group g => Torsor g g Source #

Any group is a torsor under its own natural left action.

Instance details

Defined in Data.Act

Methods

(<--) :: g -> g -> g Source #

(-->) :: g -> g -> g Source #

(Group g, Torsor g (Finite n), Finitary a, n ~ Cardinality a) => Torsor g (Finitely a) Source #

Torsor for a type using its Finitary instance.

Instance details

Defined in Data.Act

Methods

(<--) :: Finitely a -> Finitely a -> g Source #

(-->) :: Finitely a -> Finitely a -> g Source #

Num a => Torsor (Sum a) a Source # 
Instance details

Defined in Data.Act

Methods

(<--) :: a -> a -> Sum a Source #

(-->) :: a -> a -> Sum a Source #

anti :: Group g => g -> Dual g Source #

A group's inversion anti-automorphism corresponds to an isomorphism to the opposite group.

The inversion allows us to obtain a left action from a right action (of the same group); the equivalent operation is not possible for general semigroups.

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:

newtype Finitely a Source #

Newtype for the action on a type through its Finitary instance.

data ABCD = A | B | C | D
  deriving stock    ( Eq, Generic )
  deriving anyclass Finitary
  deriving ( Act ( Sum ( Finite 4 ) ), Torsor ( Sum ( Finite 4 ) ) )
    via Finitely ABCD

Sizes are checked statically. For instance if we had instead written:

  deriving ( Act ( Sum ( Finite 3 ) ), Torsor ( Sum ( Finite 3 ) ) )
    via Finitely ABCD

we would have gotten the error messages:

* No instance for (Act (Sum (Finite 3)) (Finite 4))
* No instance for (Torsor (Sum (Finite 3)) (Finite 4))

Constructors

Finitely 

Fields

Instances

Instances details
(Group g, Torsor g (Finite n), Finitary a, n ~ Cardinality a) => Torsor g (Finitely a) Source #

Torsor for a type using its Finitary instance.

Instance details

Defined in Data.Act

Methods

(<--) :: Finitely a -> Finitely a -> g Source #

(-->) :: Finitely a -> Finitely a -> g Source #

(Semigroup s, Act s (Finite n), Finitary a, n ~ Cardinality a) => Act s (Finitely a) Source #

Act on a type through its Finitary instance.

Instance details

Defined in Data.Act

Methods

(•) :: s -> Finitely a -> Finitely a Source #

act :: s -> Finitely a -> Finitely a Source #

Eq a => Eq (Finitely a) Source # 
Instance details

Defined in Data.Act

Methods

(==) :: Finitely a -> Finitely a -> Bool #

(/=) :: Finitely a -> Finitely a -> Bool #

Data a => Data (Finitely a) Source # 
Instance details

Defined in Data.Act

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Finitely a -> c (Finitely a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Finitely a) #

toConstr :: Finitely a -> Constr #

dataTypeOf :: Finitely a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Finitely a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Finitely a)) #

gmapT :: (forall b. Data b => b -> b) -> Finitely a -> Finitely a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Finitely a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Finitely a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Finitely a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Finitely a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Finitely a -> m (Finitely a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Finitely a -> m (Finitely a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Finitely a -> m (Finitely a) #

Ord a => Ord (Finitely a) Source # 
Instance details

Defined in Data.Act

Methods

compare :: Finitely a -> Finitely a -> Ordering #

(<) :: Finitely a -> Finitely a -> Bool #

(<=) :: Finitely a -> Finitely a -> Bool #

(>) :: Finitely a -> Finitely a -> Bool #

(>=) :: Finitely a -> Finitely a -> Bool #

max :: Finitely a -> Finitely a -> Finitely a #

min :: Finitely a -> Finitely a -> Finitely a #

Read a => Read (Finitely a) Source # 
Instance details

Defined in Data.Act

Show a => Show (Finitely a) Source # 
Instance details

Defined in Data.Act

Methods

showsPrec :: Int -> Finitely a -> ShowS #

show :: Finitely a -> String #

showList :: [Finitely a] -> ShowS #

Generic (Finitely a) Source # 
Instance details

Defined in Data.Act

Associated Types

type Rep (Finitely a) :: Type -> Type #

Methods

from :: Finitely a -> Rep (Finitely a) x #

to :: Rep (Finitely a) x -> Finitely a #

NFData a => NFData (Finitely a) Source # 
Instance details

Defined in Data.Act

Methods

rnf :: Finitely a -> () #

Generic1 Finitely Source # 
Instance details

Defined in Data.Act

Associated Types

type Rep1 Finitely :: k -> Type #

Methods

from1 :: forall (a :: k). Finitely a -> Rep1 Finitely a #

to1 :: forall (a :: k). Rep1 Finitely a -> Finitely a #

type Rep (Finitely a) Source # 
Instance details

Defined in Data.Act

type Rep (Finitely a) = D1 ('MetaData "Finitely" "Data.Act" "acts-0.3.0.0-inplace" 'True) (C1 ('MetaCons "Finitely" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFinitely") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Rep1 Finitely Source # 
Instance details

Defined in Data.Act

type Rep1 Finitely = D1 ('MetaData "Finitely" "Data.Act" "acts-0.3.0.0-inplace" 'True) (C1 ('MetaCons "Finitely" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFinitely") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))