| Copyright | (c) Alice Rixte 2024 |
|---|---|
| License | BSD 3 |
| Maintainer | alice.rixte@u-bordeaux.fr |
| Stability | unstable |
| Portability | non-portable (GHC extensions) |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Act.Cyclic
Description
Presentation
Cyclic actions
A cyclic action (see or LActCyclic) is an action such that
every element of the actee set can be obtained by acting on some generator,
which we call here the origin of the actee set.RActCyclic
For example, acts cyclically on Sum Integer because for every
Integern :: Integer, we have Sum n <>$ O == n. In this example, 0 is a
generator of the action and in this library, we will
call it LAct Int (Sum Int).lorigin
This gives us a way to lift any actee element into an action element. In this
library, we call that lifting (resp. lshift). In the
previous example we get rshift.lshift = Sum
Actions generated by a subset of generators
In a more general setting, this library also provides and
LActGen. In theory, they should be superclasses of RActGen and
LActCyclic. In practice it is annoying to need RActCyclic instances for
defining Eq and lgenerators. Please open an issue if you
actually need this.rgenerators
Usage
>>>{-# LANGUAGE TypeApplications #-}>>>import Data.Act.Cyclic>>>import Data.Semigroup>>>lorigin @(Sum Int) :: Int0>>>lshift (4 :: Int) :: Sum IntSum {getSum = 4}
Formal algebraic definitions
In algebraic terms, a subset u of the set x is a generating set of the
action LAct x s if for every x :: x, there exists a pair (u,s) :: (u,s)
such that s <>$ u = x. When the set u is finite, the action LAct x s is
said to be finitely generated. When the set u is a singleton, the action is
said to be cyclic.
When the previous decomposition is unique, the action is said to be free. If it is both free and cyclic, it is 1-free.
(See Monoids, Acts and Categories by Mati Kilp, Ulrich Knauer, Alexander V. Mikhalev, definition 1.5.1, p.63.)
Remark : Freeness could be represented with classes LActFree and
LActOneFree that have no methods. Feel free to open an issue if you need
them.
Synopsis
- class LAct x s => LActCyclic x s where
- lorigin :: forall s x. LActCyclic x s => x
- class RAct x s => RActCyclic x s where
- rorigin :: forall s x. RActCyclic x s => x
- class LAct x s => LActGen x s where
- lgenerators' :: x -> Bool
- lgeneratorsList' :: [x]
- lshiftFromGen :: x -> (x, s)
- lgenerators :: forall s x. LActGen x s => x -> Bool
- lgeneratorsList :: forall s x. LActGen x s => [x]
- lorigins :: forall s x. LActGen x s => [x]
- class RAct x s => RActGen x s where
- rgenerators' :: x -> Bool
- rgeneratorsList' :: [x]
- rshiftFromGen :: x -> (x, s)
- rgenerators :: forall s x. RActGen x s => x -> Bool
- rgeneratorsList :: forall s x. RActGen x s => [x]
- rorigins :: forall s x. RActGen x s => [x]
Cyclic actions
class LAct x s => LActCyclic x s where Source #
A left action generated by a single generator.
Instances must satisfy the following law :
In other words, lorigin is a generator of the action LAct x s.
Methods
The only generator of the action LAct x s.
>>>lorigin' @Int @(Sum Int)0
To avoid having to use the redundant first type aplication, use
.lorigin
Instances
| Monoid s => LActCyclic s (ActSelf s) Source # | |
| Default x => LActCyclic x (First x) Source # | |
| Default x => LActCyclic x (First x) Source # | |
| Num x => LActCyclic x (Product x) Source # | |
| Num x => LActCyclic x (Sum x) Source # | |
| (Coercible x s, Monoid s) => LActCyclic x (ActSelf' s) Source # | |
| LActCyclic x s => LActCyclic (Identity x) (Identity s) Source # | |
| Num x => LActCyclic (Sum x) (Product x) Source # | |
lorigin :: forall s x. LActCyclic x s => x Source #
A version of such that the first type application is lorigin's.
>>>lorigin @(Sum Int) :: Int0
class RAct x s => RActCyclic x s where Source #
A right action generated by a single generator.
Instances must satisfy the following law :
In other words, rorigin is a generator of the action RAct x s.
Methods
The only generator of the action RAct x s.
>>>rorigin' @Int @(Sum Int) :: Int0
To avoid having to use the redundant first type aplication, use
.rorigin
Shifts an element of x into an action rshift x such that
rshift x $<> rorigin == x.
Instances
| Monoid s => RActCyclic s (ActSelf s) Source # | |
| Default x => RActCyclic x (Last x) Source # | |
| Default x => RActCyclic x (Last x) Source # | |
| Num x => RActCyclic x (Product x) Source # | |
| Num x => RActCyclic x (Sum x) Source # | |
| (Coercible x s, Monoid s) => RActCyclic x (ActSelf' s) Source # | |
| RActCyclic x s => RActCyclic (Identity x) (Identity s) Source # | |
| Num x => RActCyclic (Sum x) (Product x) Source # | |
rorigin :: forall s x. RActCyclic x s => x Source #
A version of such that the first type application is rorigin's.
>>>rorigin @(Sum Int) :: Int0
Action generated by a subset of generators
class LAct x s => LActGen x s where Source #
A left action generated by a subset of generators .lgenerators
Intuitively, by acting repeteadly on generators with actions
of s, we can reach any element of x.
Since the generating subset of x maybe infinite, we give two alternative
ways to define it : one using a characteristic function and
the other using a list lgenerators.lgeneratorsList
All the above is summarized by the following law that all instances must satisfy :
snd(lshiftFromGenx) <>$fst(lshiftFromGenx) == xlgenerators(fst$lshiftFromGenx) == Truelgeneratorsx == x `elem'lgeneratorsListproxy
Minimal complete definition
Nothing
Methods
lgenerators' :: x -> Bool Source #
The set of origins of the action .LAct x s
This is a subset of x, represented as its characteristic function,
meaning the function that returns True for all elements of x that are
origins of the action and False otherwise.
To use , you need TypeApplications:lgenerators
>>>lgenerators' @Int @(Sum Int) 4False
>>>lgenerators' @Int @(Sum Int) 0True
To avoid having to use the redundant first type aplication, use
.lgenerators
default lgenerators' :: Eq x => x -> Bool Source #
lgeneratorsList' :: [x] Source #
The set of origins of the action LAct x s seen as a list.
You can let this function undefined if the set of origins cannot be represented as a list.
>>>lgeneratorsList' @Int @(Sum Int)[0]
To avoid having to use the redundant first type aplication, use
.lgeneratorsList
default lgeneratorsList' :: LActCyclic x s => [x] Source #
lshiftFromGen :: x -> (x, s) Source #
Returns a point's associated genrator u along with an action s such
that s <>$ u == x.
default lshiftFromGen :: LActCyclic x s => x -> (x, s) Source #
Instances
lgenerators :: forall s x. LActGen x s => x -> Bool Source #
A version of such that the first type application is lgenerators's.
>>>lgenerators @(Sum Int) (4 :: Int)False
>>>lgenerators @(Sum Int) (0 :: Int)True
lgeneratorsList :: forall s x. LActGen x s => [x] Source #
A version of such that the first type application is
lgeneratorsList's.
>>>lgeneratorsList @(Sum Int) :: [Int][0]
lorigins :: forall s x. LActGen x s => [x] Source #
An alias for .lgeneratorsList
class RAct x s => RActGen x s where Source #
A right action generated by a subset of generators .lgenerators
Intuitively, by acting repeteadly on generators with actions
of s, we can reach any element of x.
Since the generating subset of x maybe infinite, we give two alternative
ways to define it : one using a characteristic function and
the other using a list rgenerators.rgeneratorsList
All the above is summarized by the following law that all instances must satisfy :
rgenerators(fst$rshiftFromGenx) == Truefst(rshiftFromGenx) $<>snd(rshiftFromGenx) == xrgeneratorsx == x `elem'rgeneratorsListx
Minimal complete definition
Nothing
Methods
rgenerators' :: x -> Bool Source #
The set of origins of the action .RAct x s
This is a subset of x, represented as its characteristic function,
meaning the function that returns True for all elements of x that are
origins of the action and False otherwise.
To use , you need TypeApplications:rgenerators
>>>rgenerators' @(Sum Int) (4 :: Int)False
>>>rgenerators' @(Sum Int) (0 :: Int)True
To avoid having to use the redundant first type aplication, use
.rgenerators
default rgenerators' :: Eq x => x -> Bool Source #
rgeneratorsList' :: [x] Source #
The set of origins of the action RAct x s seen as a list.
You can let this function undefined if the set of origins cannot be represented as a list.
>>>rgeneratorsList' @(Sum Int) :: [Int][0]
default rgeneratorsList' :: RActCyclic x s => [x] Source #
rshiftFromGen :: x -> (x, s) Source #
Returns a point's associated generator u along with an action s such
that u $<> s == x.
default rshiftFromGen :: RActCyclic x s => x -> (x, s) Source #
Instances
rgenerators :: forall s x. RActGen x s => x -> Bool Source #
A version of such that the first type application is rgenerators's.
>>>rgenerators @(Sum Int) (4 :: Int)False
>>>rgenerators @(Sum Int) (0 :: Int)True
rgeneratorsList :: forall s x. RActGen x s => [x] Source #
A version of such that the first type application is
rgeneratorsList's.
>>>rgeneratorsList @(Sum Int) :: [Int][0]
rorigins :: forall s x. RActGen x s => [x] Source #
An alias for .rgeneratorsList