A group action is a triple (G,Omega ,μ), where G is a group, Omega a set and μ:Omega ×G→Omega a function (whose action is compatible with the group arithmetic). We call Omega the domain of the action.
In GAP, Omega can be a duplicate-free collection (an object that permits access to its elements via the Omega[n] operation, for example a list), it does not need to be sorted (see IsSet).
The acting function μ is a GAP function of the form
actfun(
pnt,
g)
that returns the image μ(pnt ,g ) for a point pnt ∈ Omega and a group element g ∈ G .
Groups always acts from the right, that is μ(μ(pnt ,g ),h )=μ(pnt ,gh ).
GAP does not test whether an acting function actfun
satisfies the
conditions for a group operation but silently assumes that is does.
(If it does not, results are unpredictable.)
The first section of this chapter, About Group Actions, describes the various ways how operations for group actions can be called.
Functions for several commonly used action are already built into GAP. These are listed in section Basic Actions.
The sections The Permutation Image of an Action and Action of a group on itself describe homomorphisms and mappings associated to group actions as well as the permutation group image of an action.
The other sections then describe operations to compute orbits, stabilizers, as well as properties of actions.
Finally section External Sets describes the concept of ``external sets'' which represent the concept of a G-set and underly the actions mechanism.
The syntax which is used by the operations for group actions is quite
flexible. For example we can call the operation OrbitsDomain
for the orbits
of the group G on the domain Omega in the following ways:
OrbitsDomain(
G,
Omega[,
actfun])
The acting function actfun is optional. If it is not given, the built-in
action OnPoints
(which defines an action via the caret operator ^
) is
used as a default.
OrbitsDomain(
G,
Omega,
gens,
acts[,
actfun])
This second version (of OrbitsDomain
) permits one to implement an action
induced by a homomorphism:
If H acts on Omega via μ and ϕ:G→ H is a
homomorphism, G acts on Omega via
μ′(ω,g)=μ(ω,gϕ):
Here gens must be a set of generators of G and acts the images of
gens under a homomorphism ϕ:G→ H.
actfun is the acting function for H, the call
to ExampleActionFunction
implements the induced action of G.
Again, the acting function actfun is optional and OnPoints
is used as a
default.
The advantage of this notation is that GAP does not need to construct this homomorphism ϕ and the range group H as GAP objects. (If a small group G acts via complicated objects acts this otherwise could lead to performance problems.)
GAP does not test whether the mapping gens →acts actually induces a homomorphism and the results are unpredictable if this is not the case.
OrbitsDomain(
extset) A
A third variant is to call the operation with an external set (which then provides G, Omega and actfun. You will find more about external sets in section External Sets.
For operations like Stabilizer
of course the domain must be replaced by an
element of Omega which is to be acted on.
GAP already provides acting functions for the more common actions of a
group. For built-in operations such as Stabilizer
special methods are
available for many of these actions.
This section also shows how to implement different actions. (Note that every action must be from the right.)
OnPoints(
pnt,
g ) F
returns pnt
^
g.
This is for example the action of a permutation group on points,
or the action of a group on its elements via conjugation.
The action of a matrix group on vectors from the right is described by
both
OnPoints
and OnRight
(see OnRight).
OnRight(
pnt,
g ) F
returns pnt
*
g.
This is for example the action of a group on its elements via right
multiplication,
or the action of a group on the cosets of a subgroup.
The action of a matrix group on vectors from the right is described by
both
OnPoints
(see OnPoints) and OnRight
.
OnLeftInverse(
pnt,
g ) F
returns g −1 *
pnt.
Forming the inverse is necessary to make this a proper action,
as in GAP groups always act from the right.
(OnLeftInverse
is used for example in the representation of a right
coset as an external set (see External Sets), that is a right coset
Ug is an external set for the group U acting on it via
OnLeftInverse
.)
OnSets(
set,
g ) F
Let set be a proper set (see Sorted Lists and Sets).
OnSets
returns the proper set formed by the images
OnPoints(
pnt,
g )
of all points pnt of set.
OnSets
is for example used to compute the action of a permutation group
on blocks.
(OnTuples
is an action on lists that preserves the ordering of entries,
see OnTuples.)
OnTuples(
tup,
g ) F
Let tup be a list.
OnTuples
returns the list formed by the images
OnPoints(
pnt,
g )
for all points pnt of tup.
(OnSets
is an action on lists that additionally sorts the entries of
the result, see OnSets.)
OnPairs(
tup,
g ) F
is a special case of OnTuples
(see OnTuples) for lists tup
of length 2.
OnSetsSets(
set,
g ) F
Action on sets of sets;
for the special case that the sets are pairwise disjoint,
it is possible to use OnSetsDisjointSets
(see OnSetsDisjointSets).
OnSetsDisjointSets(
set,
g ) F
Action on sets of pairwise disjoint sets (see also OnSetsSets).
OnSetsTuples(
set,
g ) F
Action on sets of tuples.
OnTuplesSets(
set,
g ) F
Action on tuples of sets.
OnTuplesTuples(
set,
g ) F
Action on tuples of tuples
gap> g:=Group((1,2,3),(2,3,4));; gap> Orbit(g,1,OnPoints); [ 1, 2, 3, 4 ] gap> Orbit(g,(),OnRight); [ (), (1,2,3), (2,3,4), (1,3,2), (1,3)(2,4), (1,2)(3,4), (2,4,3), (1,4,2), (1,4,3), (1,3,4), (1,2,4), (1,4)(2,3) ] gap> Orbit(g,[1,2],OnPairs); [ [ 1, 2 ], [ 2, 3 ], [ 1, 3 ], [ 3, 1 ], [ 3, 4 ], [ 2, 1 ], [ 1, 4 ], [ 4, 1 ], [ 4, 2 ], [ 3, 2 ], [ 2, 4 ], [ 4, 3 ] ] gap> Orbit(g,[1,2],OnSets); [ [ 1, 2 ], [ 2, 3 ], [ 1, 3 ], [ 3, 4 ], [ 1, 4 ], [ 2, 4 ] ]
gap> Orbit(g,[[1,2],[3,4]],OnSetsSets); [ [ [ 1, 2 ], [ 3, 4 ] ], [ [ 1, 4 ], [ 2, 3 ] ], [ [ 1, 3 ], [ 2, 4 ] ] ] gap> Orbit(g,[[1,2],[3,4]],OnTuplesSets); [ [ [ 1, 2 ], [ 3, 4 ] ], [ [ 2, 3 ], [ 1, 4 ] ], [ [ 1, 3 ], [ 2, 4 ] ], [ [ 3, 4 ], [ 1, 2 ] ], [ [ 1, 4 ], [ 2, 3 ] ], [ [ 2, 4 ], [ 1, 3 ] ] ] gap> Orbit(g,[[1,2],[3,4]],OnSetsTuples); [ [ [ 1, 2 ], [ 3, 4 ] ], [ [ 1, 4 ], [ 2, 3 ] ], [ [ 1, 3 ], [ 4, 2 ] ], [ [ 2, 4 ], [ 3, 1 ] ], [ [ 2, 1 ], [ 4, 3 ] ], [ [ 3, 2 ], [ 4, 1 ] ] ] gap> Orbit(g,[[1,2],[3,4]],OnTuplesTuples); [ [ [ 1, 2 ], [ 3, 4 ] ], [ [ 2, 3 ], [ 1, 4 ] ], [ [ 1, 3 ], [ 4, 2 ] ], [ [ 3, 1 ], [ 2, 4 ] ], [ [ 3, 4 ], [ 1, 2 ] ], [ [ 2, 1 ], [ 4, 3 ] ], [ [ 1, 4 ], [ 2, 3 ] ], [ [ 4, 1 ], [ 3, 2 ] ], [ [ 4, 2 ], [ 1, 3 ] ], [ [ 3, 2 ], [ 4, 1 ] ], [ [ 2, 4 ], [ 3, 1 ] ], [ [ 4, 3 ], [ 2, 1 ] ] ]
OnLines(
vec,
g ) F
Let vec be a normed row vector, that is,
its first nonzero entry is normed to the identity of the relevant field,
OnLines
returns the row vector obtained from normalizing
OnRight(
vec,
g )
by scalar multiplication from the left.
This action corresponds to the projective action of a matrix group
on 1-dimensional subspaces.
gap> gl:=GL(2,5);;v:=[1,0]*Z(5)^0; [ Z(5)^0, 0*Z(5) ] gap> h:=Action(gl,Orbit(gl,v,OnLines),OnLines); Group([ (2,3,5,6), (1,2,4)(3,6,5) ])
OnIndeterminates(
poly,
perm ) F
A permutation perm acts on the multivariate polynomial poly by permuting the indeterminates as it permutes points.
Permuted(
list,
perm )
The following example demonstrates Permuted
being used to implement a
permutation action on a domain:
gap> g:=Group((1,2,3),(1,2));; gap> dom:=[ "a", "b", "c" ];; gap> Orbit(g,dom,Permuted); [ [ "a", "b", "c" ], [ "c", "a", "b" ], [ "b", "a", "c" ], [ "b", "c", "a" ], [ "a", "c", "b" ], [ "c", "b", "a" ] ]
OnSubspacesByCanonicalBasis(
bas,
mat ) F
implements the operation of a matrix group on subspaces of a vector space. bas must be a list of (linearly independent) vectors which forms a basis of the subspace in Hermite normal form. mat is an element of the acting matrix group. The function returns a mutable matrix which gives the basis of the image of the subspace in Hermite normal form. (In other words: it triangulizes the product of bas with mat.)
If one needs an action for which no acting function is provided by the library it can be implemented via a GAP function that conforms to the syntax
actfun(
omega,
g)
For example one could define the following function that acts on pairs of
polynomials via OnIndeterminates
:
OnIndeterminatesPairs:=function(polypair,g) return [OnIndeterminates(polypair[1],g), OnIndeterminates(polypair[2],g)]; end;
Note that this function must implement an action from the right. This is not verified by GAP and results are unpredicatble otherwise.
If G acts on Omega the set of all images of ω ∈ Omega under elements of G is called the orbit of ω. The set of orbits of G is a partition of Omega.
Note that currently GAP does not check whether a given point really belongs to Ω. For example, consider the following example where the projective action of a matrix group on a finite vector space shall be computed.
gap> Orbit( GL(2,3), [ -1, 0 ] * Z(3)^0, OnLines ); [ [ Z(3), 0*Z(3) ], [ Z(3)^0, 0*Z(3) ], [ Z(3)^0, Z(3) ], [ Z(3)^0, Z(3)^0 ], [ 0*Z(3), Z(3)^0 ] ] gap> Size( GL(2,3) ) / Length( last ); 48/5
The error is that OnLines
(see OnLines) acts on the set of normed row
vectors (see NormedRowVectors) of the vector space in question,
but that the seed vector is itself not such a vector.
Orbit(
G[,
Omega],
pnt, [
gens,
acts, ]
act ) O
The orbit of the point pnt is the list of all images of pnt under the action.
(Note that the arrangement of points in this list is not defined by the operation.)
The orbit of pnt will always contain one element that is equal to pnt, however for performance reasons this element is not necessarily identical to pnt, in particular if pnt is mutable.
gap> g:=Group((1,3,2),(2,4,3));; gap> Orbit(g,1); [ 1, 3, 2, 4 ] gap> Orbit(g,[1,2],OnSets); [ [ 1, 2 ], [ 1, 3 ], [ 1, 4 ], [ 2, 3 ], [ 3, 4 ], [ 2, 4 ] ](See Section Basic Actions for information about specific actions.)
Orbits(
G,
seeds[,
gens,
acts][,
act] ) O
Orbits(
xset ) A
returns a duplicate-free list of the orbits of the elements in seeds under the action act of G
(Note that the arrangement of orbits or of points within one orbit is not defined by the operation.)
OrbitsDomain(
G,
Omega[,
gens,
acts][,
act] ) O
OrbitsDomain(
xset ) A
returns a list of the orbits of G on the domain Omega (given as lists) under the action act.
This operation is often faster than Orbits
.
The domain Omega must be closed under the action of G, otherwise an
error can occur.
(Note that the arrangement of orbits or of points within one orbit is not defined by the operation.)
gap> g:=Group((1,3,2),(2,4,3));; gap> Orbits(g,[1..5]); [ [ 1, 3, 2, 4 ], [ 5 ] ] gap> OrbitsDomain(g,Arrangements([1..4],3),OnTuples); [ [ [ 1, 2, 3 ], [ 3, 1, 2 ], [ 1, 4, 2 ], [ 2, 3, 1 ], [ 2, 1, 4 ], [ 3, 4, 1 ], [ 1, 3, 4 ], [ 4, 2, 1 ], [ 4, 1, 3 ], [ 2, 4, 3 ], [ 3, 2, 4 ], [ 4, 3, 2 ] ], [ [ 1, 2, 4 ], [ 3, 1, 4 ], [ 1, 4, 3 ], [ 2, 3, 4 ], [ 2, 1, 3 ], [ 3, 4, 2 ], [ 1, 3, 2 ], [ 4, 2, 3 ], [ 4, 1, 2 ], [ 2, 4, 1 ], [ 3, 2, 1 ], [ 4, 3, 1 ] ] ] gap> OrbitsDomain(g,GF(2)^2,[(1,2,3),(1,4)(2,3)], > [[[Z(2)^0,Z(2)^0],[Z(2)^0,0*Z(2)]],[[Z(2)^0,0*Z(2)],[0*Z(2),Z(2)^0]]]); [ [ <an immutable GF2 vector of length 2> ], [ <an immutable GF2 vector of length 2>, <an immutable GF2 vector of length 2>, <an immutable GF2 vector of length 2> ] ](See Section Basic Actions for information about specific actions.)
OrbitLength(
G,
Omega,
pnt, [
gens,
acts, ]
act ) O
computes the length of the orbit of pnt.
OrbitLengths(
G,
seeds[,
gens,
acts][,
act] ) O
OrbitLengths(
xset ) A
computes the lengths of all the orbits of the elements in seegs under the action act of G.
OrbitLengthsDomain(
G,
Omega[,
gens,
acts][,
act] ) O
OrbitLengthsDomain(
xset ) A
computes the lengths of all the orbits of G on Omega.
This operation is often faster than OrbitLengths
.
The domain Omega must be closed under the action of G, otherwise an
error can occur.
gap> g:=Group((1,3,2),(2,4,3));; gap> OrbitLength(g,[1,2,3,4],OnTuples); 12 gap> OrbitLengths(g,Arrangements([1..4],4),OnTuples); [ 12, 12 ]
The Stabilizer of an element ω is the set of all those g ∈ G which fix ω.
OrbitStabilizer(
G, [
Omega, ]
pnt, [
gens,
acts, ]
act ) O
computes the orbit and the stabilizer of pnt simultaneously in a single Orbit-Stabilizer algorithm.
The stabilizer must have G as its parent.
Stabilizer(
G [,
Omega],
pnt [,
gens,
acts] [,
act] ) F
computes the stabilizer in G of the point pnt, that is the subgroup of those elements of G that fix pnt. The stabilizer will have G as its parent.
gap> g:=Group((1,3,2),(2,4,3));; gap> Stabilizer(g,4); Group([ (1,3,2) ])
The stabilizer of a set or tuple of points can be computed by specifying an action of sets or tuples of points.
gap> Stabilizer(g,[1,2],OnSets); Group([ (1,2)(3,4) ]) gap> Stabilizer(g,[1,2],OnTuples); Group(()) gap> OrbitStabilizer(g,[1,2],OnSets); rec( orbit := [ [ 1, 2 ], [ 1, 3 ], [ 1, 4 ], [ 2, 3 ], [ 3, 4 ], [ 2, 4 ] ], stabilizer := Group([ (1,2)(3,4) ]) )(See Section Basic Actions for information about specific actions.)
The standard methods for all these actions are an Orbit-Stabilizer algorithm. For permutation groups backtrack algorithms are used. For solvable groups an orbit-stabilizer algorithm for solvable groups, which uses the fact that the orbits of a normal subgroup form a block system (see SOGOS) is used.
OrbitStabilizerAlgorithm(
G,
Omega,
blist,
gens,
acts,
pntact ) F
This operation should not be called by a user. It is documented however for purposes to extend or maintain the group actions package.
OrbitStabilizerAlgorithm
performs an orbit stabilizer algorithm for
the group G acting with the generators gens via the generator images
gens and the group action act on the element pnt. (For
technical reasons pnt and act are put in one record with components
pnt
and act
respectively.)
The pntact record may carry a component stabsub. If given, this must be a subgroup stabilizing all points in the domain and can be used to abbreviate stabilizer calculations.
The argument Omega (which may be replaced by false
to be ignored) is
the set within which the orbit is computed (once the orbit is the full
domain, the orbit calculation may stop). If blist is given it must be
a bit list corresponding to Omega in which elements which have been found
already will be ``ticked off'' with true
. (In particular, the entries
for the orbit of pnt still must be all set to false
). Again the
remaining action domain (the bits set initially to false
) can be
used to stop if the orbit cannot grow any longer.
Another use of the bit list is if Omega is an enumerator which can
determine PositionCanonical
s very quickly. In this situation it can be
worth to search images not in the orbit found so far, but via their
position in Omega and use a the bit list to keep track whether the
element is in the orbit found so far.
RepresentativeAction(
G [,
Omega],
d,
e [,
gens,
acts] [,
act] ) O
computes an element of G that maps d to e under the given
action and returns fail
if no such element exists.
gap> g:=Group((1,3,2),(2,4,3));; gap> RepresentativeAction(g,1,3); (1,3)(2,4) gap> RepresentativeAction(g,1,3,OnPoints); (1,3)(2,4) gap> RepresentativeAction(g,(1,2,3),(2,4,3)); (1,2,4) gap> RepresentativeAction(g,(1,2,3),(2,3,4)); fail gap> RepresentativeAction(g,Group((1,2,3)),Group((2,3,4))); (1,2,4) gap> RepresentativeAction(g,[1,2,3],[1,2,4],OnSets); (2,4,3) gap> RepresentativeAction(g,[1,2,3],[1,2,4],OnTuples); fail(See Section Basic Actions for information about specific actions.)
Again the standard method for RepresentativeAction
is an orbit-stabilizer
algorithm, for permutation groups and standard actions a backtrack algorithm
is used.
If G acts on a domain Omega, an enumeration of Omega yields a
homomorphism of G into the symmetric group on {1,…,|Omega |}. In
GAP, the enumeration of the domain Omega is provided by the
Enumerator
of Omega (see Enumerator) which of course is Omega itself
if it is a list.
ActionHomomorphism(
G,
Omega [,
gens,
acts] [,
act] [, "surjective"] ) O
ActionHomomorphism(
xset [, "surjective"] ) A
ActionHomomorphism(
action ) A
computes a homomorphism from G into the symmetric group on |Omega | points that gives the permutation action of G on Omega.
By default the homomorphism returned by ActionHomomorphism
is not
necessarily surjective (its Range
is the full symmetric group) to
avoid unnecessary computation of the image. If the optional string
argument "surjective"
is given, a surjective homomorphism is created.
The third version (which is supported only for GAP3 compatibility)
returns the action homomorphism that belongs to the image
obtained via Action
(see Action).
(See Section Basic Actions for information about specific actions.)
gap> g:=Group((1,2,3),(1,2));; gap> hom:=ActionHomomorphism(g,Arrangements([1..4],3),OnTuples); <action homomorphism> gap> Image(hom); Group([ (1,9,13)(2,10,14)(3,7,15)(4,8,16)(5,12,17)(6,11,18)(19,22,23)(20,21, 24), (1,7)(2,8)(3,9)(4,10)(5,11)(6,12)(13,15)(14,16)(17,18)(19,21)(20, 22)(23,24) ]) gap> Size(Range(hom));Size(Image(hom)); 620448401733239439360000 6 gap> hom:=ActionHomomorphism(g,Arrangements([1..4],3),OnTuples, > "surjective");; gap> Size(Range(hom)); 6
When acting on a domain, the operation PositionCanonical
is used to
determine the position of elements in the domain. This can be used to act
on a domain given by a list of representatives for which PositionCanonical
is implemented, for example a RightTransversal
(see RightTransversal).
Action(
G,
Omega [
gens,
acts] [,
act] ) O
Action(
xset ) A
returns the Image
group of ActionHomomorphism
called with the same
parameters.
Note that (for compatibility reasons to be able to get the action homomorphism) this image group internally stores the action homomorphism. If G or Omega are exteremly big, this can cause memory problems. In this case compute only generator images and form the image group yourself.
(See Section Basic Actions for information about specific actions.) The following code shows for example how to create the regular action of a group:
gap> g:=Group((1,2,3),(1,2));; gap> Action(g,AsList(g),OnRight); Group([ (1,4,5)(2,3,6), (1,3)(2,4)(5,6) ])
SparseActionHomomorphism(
G,
Omega,
start [,
gens,
acts] [,
act] ) O
SortedSparseActionHomomorphism(
G,
Omega,
start[,
gens,
acts] [,
act] ) O
SparseActionHomomorphism
computes the
ActionHomomorphism(
G,
dom[,
gens,
acts][,
act])
, where dom
is the union of the orbits Orbit(
G,
pnt[,
gens,
acts][,
act])
for all points pnt from start. If G acts on a very large domain
Omega not surjectively this may yield a permutation image of
substantially smaller degree than by action on Omega.
The operation SparseActionHomomorphism
will only use =
comparisons
of points in the orbit. Therefore it can be used even if no good <
comparison method exists. However the image group will depend on the
generators gens of G.
The operation SortedSparseActionHomomorphism
in contrast
will sort the orbit and thus produce an image group which is not
dependent on these generators.
gap> h:=Group(Z(3)*[[[1,1],[0,1]]]); Group([ [ [ Z(3), Z(3) ], [ 0*Z(3), Z(3) ] ] ]) gap> hom:=ActionHomomorphism(h,GF(3)^2,OnRight);; gap> Image(hom); Group([ (2,3)(4,9,6,7,5,8) ]) gap> hom:=SparseActionHomomorphism(h,[Z(3)*[1,0]],OnRight);; gap> Image(hom); Group([ (1,2,3,4,5,6) ])
For an action homomorphism, the operation UnderlyingExternalSet
(see UnderlyingExternalSet) will return the external set on Omega which
affords the action.
Of particular importance is the action of a group on its elements or cosets
of a subgroup. These actions can be obtained by using ActionHomomorphism
for a suitable domain (for example a list of subgroups). For the following
(frequently used) types of actions however special (often particularly
efficient) functions are provided:
FactorCosetAction(
G,
U, [
N] ) O
This command computes the action of G on the right cosets of the subgroup U. If the normal subgroup N is given, it is stored as kernel of this action.
gap> g:=Group((1,2,3,4,5),(1,2));;u:=SylowSubgroup(g,2);;Index(g,u); 15 gap> FactorCosetAction(g,u); <action epimorphism> gap> Range(last); Group([ (1,9,13,10,4)(2,8,14,11,5)(3,7,15,12,6), (1,7)(2,8)(3,9)(5,6)(10,11)(14,15) ])
RegularActionHomomorphism(
G ) A
returns an isomorphism from G onto the regular permutation representation of G.
AbelianSubfactorAction(
G,
M,
N ) O
Let G be a group and M ≥ N be subgroups of a common parent that
are normal under G, such that
the subfactor M /N is elementary abelian. The operation
AbelianSubfactorAction
returns a list [
phi,
alpha,
bas]
where
bas is a list of elements of M which are representatives for a basis
of M /N , alpha is a map from M into a n-dimensional row space
over GF(p) where [M :N ]=pn that is the
natural homomorphism of M by N with the quotient represented as an
additive group. Finally phi is a homomorphism from G
into GLn(p) that represents the action of G on the factor
M /N .
Note: If only matrices for the action are needed, LinearActionLayer
might be faster.
gap> g:=Group((1,8,10,7,3,5)(2,4,12,9,11,6),(1,9,5,6,3,10)(2,11,12,8,4,7));; gap> c:=ChiefSeries(g);;List(c,Size); [ 96, 48, 16, 4, 1 ] gap> HasElementaryAbelianFactorGroup(c[3],c[4]); true gap> SetName(c[3],"my_group");; gap> a:=AbelianSubfactorAction(g,c[3],c[4]); [ [ (1,8,10,7,3,5)(2,4,12,9,11,6), (1,9,5,6,3,10)(2,11,12,8,4,7) ] -> [ <an immutable 2x2 matrix over GF2>, <an immutable 2x2 matrix over GF2> ] , MappingByFunction( my_group, ( GF(2)^ 2 ), function( e ) ... end, function( r ) ... end ), Pcgs([ (2,8,3,9)(4,10,5,11), (1,6,12,7)(4,10,5,11) ]) ] gap> mat:=Image(a[1],g); Group([ <an immutable 2x2 matrix over GF2>, <an immutable 2x2 matrix over GF2> ]) gap> Size(mat); 3 gap> e:=PreImagesRepresentative(a[2],[Z(2),0*Z(2)]); (2,8,3,9)(4,10,5,11) gap> e in c[3];e in c[4]; true false
If only the permutation image of a single element is needed, it might not be worth to create the action homomorphism, the following operations yield the permutation image and cycles of a single element.
Permutation(
g,
Omega[,
gens,
acts][,
act] ) F
Permutation(
g,
xset ) F
computes the permutation that corresponds to the action of g on the
permutation domain Omega (a list of objects that are permuted). If an
external set xset is given, the permutation domain is the HomeEnumerator
of this external set (see Section External Sets).
Note that the points of the returned permutation refer to the positions
in Omega, even if Omega itself consists of integers.
If g does not leave the domain invariant, or does not map the domain
injectively fail
is returned.
PermutationCycle(
g,
Omega,
pnt [,
act] ) F
PermutationCycleOp(
g,
Omega,
pnt,
act ) O
computes the permutation that represents the cycle of pnt under the action of the element g.
gap> Permutation([[Z(3),-Z(3)],[Z(3),0*Z(3)]],AsList(GF(3)^2)); (2,7,6)(3,4,8) gap> Permutation((1,2,3)(4,5)(6,7),[4..7]); (1,2)(3,4) gap> PermutationCycle((1,2,3)(4,5)(6,7),[4..7],4); (1,2)
Cycle(
g,
Omega,
pnt [,
act] ) O
returns a list of the points in the cycle of pnt under the action of the element g.
CycleLength(
g,
Omega,
pnt [,
act] ) O
returns the length of the cycle of pnt under the action of the element g.
Cycles(
g,
Omega [,
act] ) O
returns a list of the cycles (as lists of points) of the action of the element g.
CycleLengths(
g,
Omega, [,
act] ) O
returns the lengths of all the cycles under the action of the element g on Omega.
gap> Cycle((1,2,3)(4,5)(6,7),[4..7],4); [ 4, 5 ] gap> CycleLength((1,2,3)(4,5)(6,7),[4..7],4); 2 gap> Cycles((1,2,3)(4,5)(6,7),[4..7]); [ [ 4, 5 ], [ 6, 7 ] ] gap> CycleLengths((1,2,3)(4,5)(6,7),[4..7]); [ 2, 2 ]
IsTransitive(
G,
Omega[,
gens,
acts][,
act] ) O
IsTransitive(
xset ) P
returns true
if the action implied by the arguments is transitive, or
false
otherwise.
We say that a group G acts transitively on a domain D if and only if for every pair of points d and e there is an element g of G such that dg = e.
Transitivity(
G,
Omega[,
gens,
acts][,
act] ) O
Transitivity(
xset ) A
returns the degree k (a non-negative integer) of transitivity of the
action implied by the arguments, i.e. the largest integer k such that
the action is k-transitive. If the action is not transitive 0
is
returned.
An action is k-transitive if every k-tuple of points can be mapped simultaneously to every other k-tuple.
gap> g:=Group((1,3,2),(2,4,3));; gap> IsTransitive(g,[1..5]); false gap> Transitivity(g,[1..4]); 2
Note: For permutation groups, the syntax IsTransitive(
g)
is also
permitted and tests whether the group is transitive on the points moved by
it, that is the group 〈(2,3,4),(2,3)〉 is transitive (on 3
points).
RankAction(
G,
Omega[,
gens,
acts][,
act] ) O
RankAction(
xset ) A
returns the rank of a transitive action, i.e. the number of orbits of the point stabilizer.
gap> RankAction(g,Combinations([1..4],2),OnSets); 4
IsSemiRegular(
G,
Omega[,
gens,
acts][,
act] ) O
IsSemiRegular(
xset ) P
returns true
if the action implied by the arguments is semiregular, or
false
otherwise.
An action is semiregular is the stabilizer of each point is the identity.
IsRegular(
G,
Omega[,
gens,
acts][,
act] ) O
IsRegular(
xset ) P
returns true
if the action implied by the arguments is regular, or
false
otherwise.
An action is regular if it is both semiregular (see IsSemiRegular) and transitive (see IsTransitive!for group actions). In this case every point pnt of Omega defines a one-to-one correspondence between G and Omega.
gap> IsSemiRegular(g,Arrangements([1..4],3),OnTuples); true gap> IsRegular(g,Arrangements([1..4],3),OnTuples); false
Earns(
G,
Omega[,
gens,
acts][,
act] ) O
Earns(
xset ) A
returns a list of the elementary abelian regular (when acting on Omega) normal subgroups of G.
At the moment only methods for a primitive group G are implemented.
IsPrimitive(
G,
Omega[,
gens,
acts][,
act] ) O
IsPrimitive(
xset ) P
returns true
if the action implied by the arguments is primitive, or
false
otherwise.
An action is primitive if it is transitive and the action admits no nontrivial block systems. See Block Systems.
gap> IsPrimitive(g,Orbit(g,(1,2)(3,4))); true
A block system (system of imprimitivity) for the action of G on Omega is a partition of Omega which -- as a partition -- remains invariant under the action of G.
Blocks(
G,
Omega[,
seed][,
gens,
acts][,
act] ) O
Blocks(
xset[,
seed] ) A
computes a block system for the action. If seed is not given and the action is imprimitive, a minimal nontrivial block system will be found. If seed is given, a block system in which seed is the subset of one block is computed. The action must be transitive.
gap> g:=TransitiveGroup(8,3); E(8)=2[x]2[x]2 gap> Blocks(g,[1..8]); [ [ 1, 8 ], [ 2, 3 ], [ 4, 5 ], [ 6, 7 ] ] gap> Blocks(g,[1..8],[1,4]); [ [ 1, 4 ], [ 2, 7 ], [ 3, 6 ], [ 5, 8 ] ](See Section Basic Actions for information about specific actions.)
MaximalBlocks(
G,
Omega [,
seed] [,
gens,
acts] [,
act] ) O
MaximalBlocks(
xset [,
seed] ) A
returns a block system that is maximal with respect to inclusion. maximal with respect to inclusion) for the action of G on Omega. If seed is given, a block system in which seed is the subset of one block is computed.
gap> MaximalBlocks(g,[1..8]); [ [ 1, 2, 3, 8 ], [ 4, 5, 6, 7 ] ]
RepresentativesMinimalBlocks(
G,
Omega[,
gens,
acts][,
act] ) O
RepresentativesMinimalBlocks(
xset ) A
computes a list of block representatives for all minimal (i.e blocks are minimal with respect to inclusion) nontrivial block systems for the action.
gap> RepresentativesMinimalBlocks(g,[1..8]); [ [ 1, 2 ], [ 1, 3 ], [ 1, 4 ], [ 1, 5 ], [ 1, 6 ], [ 1, 7 ], [ 1, 8 ] ]
AllBlocks(
G ) A
computes a list of representatives of all block systems for a permutation group G acting transitively on the points moved by the group.
gap> AllBlocks(g); [ [ 1, 8 ], [ 1, 2, 3, 8 ], [ 1, 4, 5, 8 ], [ 1, 6, 7, 8 ], [ 1, 3 ], [ 1, 3, 5, 7 ], [ 1, 3, 4, 6 ], [ 1, 5 ], [ 1, 2, 5, 6 ], [ 1, 2 ], [ 1, 2, 4, 7 ], [ 1, 4 ], [ 1, 7 ], [ 1, 6 ] ]
The stabilizer of a block can be computed via the action
OnSets
(see OnSets):
gap> Stabilizer(g,[1,8],OnSets); Group([ (1,8)(2,3)(4,5)(6,7) ])
If bs is a partition of omega, given as a set of sets, the stabilizer
under the action OnSetsDisjointSets
(see OnSetsDisjointSets) returns the
largest subgroup which preserves bs as a block system.
gap> g:=Group((1,2,3,4,5,6,7,8),(1,2));; gap> bs:=[[1,2,3,4],[5,6,7,8]];; gap> Stabilizer(g,bs,OnSetsDisjointSets); Group([ (6,7), (5,6), (5,8), (2,3), (3,4)(5,7), (1,4), (1,5,4,8)(2,6,3,7) ])
When considering group actions, sometimes the concept of a G-set is used. This is the set Omega endowed with an action of G. The elements of the G-set are the same as those of Omega, however concepts like equality and equivalence of G-sets do not only consider the underlying domain Omega but the group action as well.
IsExternalSet(
obj ) C
An external set specifies an action act: Omega ×G → Omega of a group G on a domain Omega. The external set knows the group, the domain and the actual acting function. Mathematically, an external set is the set Omega, which is endowed with the action of a group G via the group action act. For this reason GAP treats external sets as a domain whose elements are the elements of Omega. An external set is always a union of orbits. Currently the domain Omega must always be finite. If Omega is not a list, an enumerator for Omega is automatically chosen.
ExternalSet(
G,
Omega[,
gens,
acts][,
act] ) O
creates the external set for the action act of G on Omega. Omega can be either a proper set or a domain which is represented as described in Domains and Collections.
gap> g:=Group((1,2,3),(2,3,4));; gap> e:=ExternalSet(g,[1..4]); <xset:[ 1, 2, 3, 4 ]> gap> e:=ExternalSet(g,g,OnRight); <xset:<enumerator of perm group>> gap> Orbits(e); [ [ (), (1,2)(3,4), (1,3)(2,4), (1,4)(2,3), (2,4,3), (1,4,2), (1,2,3), (1,3,4), (2,3,4), (1,3,2), (1,4,3), (1,2,4) ] ]
The following three attributes of an external set hold its constituents.
ActingDomain(
xset ) A
This attribute returns the group with which the external set xset was defined.
FunctionAction(
xset ) A
the acting function act of xset
HomeEnumerator(
xset ) A
returns an enumerator of the domain Omega with which xset was defined.
For external subsets, this is different from Enumerator(
xset )
,
which enumerates only the subset.
gap> ActingDomain(e); Group([ (1,2,3), (2,3,4) ]) gap> FunctionAction(e)=OnRight; true gap> HomeEnumerator(e); <enumerator of perm group>
Most operations for actions are applicable as an attribute for an external set.
IsExternalSubset(
obj ) R
An external subset is the restriction of an external set to a subset of the domain (which must be invariant under the action). It is again an external set.
ExternalSubset(
G,
xset,
start, [
gens,
acts, ]
act ) O
constructs the external subset of xset on the union of orbits of the points in start.
IsExternalOrbit(
obj ) R
An external orbit is an external subset consisting of one orbit.
ExternalOrbit(
G,
Omega,
pnt, [
gens,
acts, ]
act ) O
constructs the external subset on the orbit of pnt. The
Representative
of this external set is pnt.
gap> e:=ExternalOrbit(g,g,(1,2,3)); (1,2,3)^G
Many subsets of a group, such as conjugacy classes or cosets (see ConjugacyClass and RightCoset) are implemented as external orbits.
StabilizerOfExternalSet(
xset ) A
computes the stabilizer of Representative(
xset)
The stabilizer must have the acting group G of xset as its parent.
gap> Representative(e); (1,2,3) gap> StabilizerOfExternalSet(e); Group([ (1,2,3) ])
ExternalOrbits(
G,
Omega[,
gens,
acts][,
act] ) O
ExternalOrbits(
xset ) A
computes a list of ExternalOrbit
s that give the orbits of G.
gap> ExternalOrbits(g,AsList(g)); [ ()^G, (2,3,4)^G, (2,4,3)^G, (1,2)(3,4)^G ]
ExternalOrbitsStabilizers(
G,
Omega[,
gens,
acts][,
act] ) O
ExternalOrbitsStabilizers(
xset ) A
In addition to ExternalOrbits
, this operation also computes the
stabilizers of the representatives of the external orbits at the same
time. (This can be quicker than computing the ExternalOrbits
first and
the stabilizers afterwards.)
gap> e:=ExternalOrbitsStabilizers(g,AsList(g)); [ ()^G, (2,3,4)^G, (2,4,3)^G, (1,2)(3,4)^G ] gap> HasStabilizerOfExternalSet(e[3]); true gap> StabilizerOfExternalSet(e[3]); Group([ (2,4,3) ])
CanonicalRepresentativeOfExternalSet(
xset ) A
The canonical representative of an external set may only depend on G,
Omega, act and (in the case of external subsets) Enumerator(
xset )
.
It must not depend, e.g., on the representative of an external orbit.
GAP does not know methods for every external set to compute a
canonical representative . See
CanonicalRepresentativeDeterminatorOfExternalSet.
CanonicalRepresentativeDeterminatorOfExternalSet(
xset ) A
returns a function that
takes as arguments the acting group and the point. It returns a list
of length 3: [canonrep, stabilizercanonrep, conjugatingelm].
(List components 2 and 3 are optional and do not need to be bound.)
An external set is only guaranteed to be able to compute a canonical
representative if it has a
CanonicalRepresentativeDeterminatorOfExternalSet
.
ActorOfExternalSet(
xset ) A
returns an element mapping Representative(
xset)
to
CanonicalRepresentativeOfExternalSet(
xset)
under the given
action.
gap> u:=Subgroup(g,[(1,2,3)]);; gap> e:=RightCoset(u,(1,2)(3,4));; gap> CanonicalRepresentativeOfExternalSet(e); (2,4,3) gap> ActorOfExternalSet(e); (1,3,2) gap> FunctionAction(e)((1,2)(3,4),last); (2,4,3)
External sets also are implicitly underlying action homomorphisms:
UnderlyingExternalSet(
ohom ) A
The underlying set of an action homomorphism is the external set on which it was defined.
gap> g:=Group((1,2,3),(1,2));; gap> hom:=ActionHomomorphism(g,Arrangements([1..4],3),OnTuples);; gap> s:=UnderlyingExternalSet(hom); <xset:[[ 1, 2, 3 ],[ 1, 2, 4 ],[ 1, 3, 2 ],[ 1, 3, 4 ],[ 1, 4, 2 ], [ 1, 4, 3 ],[ 2, 1, 3 ],[ 2, 1, 4 ],[ 2, 3, 1 ],[ 2, 3, 4 ],[ 2, 4, 1 ], [ 2, 4, 3 ],[ 3, 1, 2 ],[ 3, 1, 4 ],[ 3, 2, 1 ], ...]> gap> Print(s,"\n"); [ [ 1, 2, 3 ], [ 1, 2, 4 ], [ 1, 3, 2 ], [ 1, 3, 4 ], [ 1, 4, 2 ], [ 1, 4, 3 ], [ 2, 1, 3 ], [ 2, 1, 4 ], [ 2, 3, 1 ], [ 2, 3, 4 ], [ 2, 4, 1 ], [ 2, 4, 3 ], [ 3, 1, 2 ], [ 3, 1, 4 ], [ 3, 2, 1 ], [ 3, 2, 4 ], [ 3, 4, 1 ], [ 3, 4, 2 ], [ 4, 1, 2 ], [ 4, 1, 3 ], [ 4, 2, 1 ], [ 4, 2, 3 ], [ 4, 3, 1 ], [ 4, 3, 2 ] ]
SurjectiveActionHomomorphismAttr(
xset ) A
returns an action homomorphism for xset which is surjective.
(As the Image
of this homomorphism has to be computed to obtain the
range, this may take substantially longer
than ActionHomomorphism
.)
[Top] [Up] [Previous] [Next] [Index]
GAP 4 manual
March 2006