Goto Chapter: Top 1 2 3 4 Bib Ind
 [Top of Book]  [Contents]   [Previous Chapter]   [Next Chapter] 

4 The Database of Low Dimensional Singer Algebras
 4.1 Overview
 4.2 Access to the Database of Singer Algebras
 4.3 On the Classification of Singer Algebras by Isomorphism Type
 4.4 Files of the Database of Singer Algebras

4 The Database of Low Dimensional Singer Algebras

4.1 Overview

Fix a positive integer z. In order to describe all Singer algebras A[q,z], it is sufficient to consider one representative q for each cyclic subgroup of the group of prime residues modulo z, see Section 1.2. The database of Singer algebras with 1 ≤ z ≤ 10000 is built according to this observation. That is, there is one entry for each such parameter pair (q,z), where we choose the smallest q from the generators of the subgroup it generates, except that q = z+1 is chosen instead of q = 1.

This implies that the number of data records for given z is exactly ∑_q 1/Phi( ord_z(q) ).

gap> ForAll( [ 1 .. 10000 ],
>            z -> Length( AllSingerAlgebraInfos( "z", z ) ) =
>                 Sum( PrimeResidues( z ),
>                      q -> 1 / Phi( OrderMod( q, z ) ) ) );
true

Note that two algebras A[q,z], A[q',z] for different such representatives q, q' can be isomorphic, and in fact this happens in many cases in a "natural" way (see Section 4.3-3). As soon as new theoretical criteria become known that admit a reduction of the set of parameters to describe all Singer algebras of a given dimension, the setup of the database may be changed.

The database stores the following information for the algebra A[q,z].

4.2 Access to the Database of Singer Algebras

4.2-1 OneSingerAlgebraInfo and AllSingerAlgebraInfos
‣ OneSingerAlgebraInfo( cond1, val1, cond2, val2, ... )( function )
‣ AllSingerAlgebraInfos( cond1, val1, cond2, val2, ... )( function )

Let cond1, cond2, ... be strings that describe precomputed properties of Singer algebras from the database, that is, they occur in the set { "z", "q", "n", "m", "e", "vprime", "diff" } (see above). The two functions compute those database entries such that the value for cond1 matches val1, the value for cond2 matches val2, etc., where "matches" means one of the following.

It is also possible to enter GAP functions as some of the cond arguments. Each such function must take a record as is returned by OneSingerAlgebraInfo, and the value returned by the function gets compared with the corresponding val argument in the same way as described above.

OneSingerAlgebraInfo returns the first matching entry if there is one, and fail otherwise. AllSingerAlgebraInfos returns the set of all matching entries.

gap> OneSingerAlgebraInfo( "z", 8 );                                  
rec( LL := 5, d := [  ], dec := 0, diff := 0, e := 1, 
  isom := [ 8, 3 ], m := 1, n := 2, q := 3, 
  vprime := [ 1, 2, 3, 2, 1 ], z := 8 )
gap> AllSingerAlgebraInfos( "diff", 1, "e", IsPrimeInt );        
[ rec( LL := 3, d := fail, dec := 1, diff := 1, 
      e := 380808546861411923, isom := [ 862, 3 ], m := 26, n := 43, 
      q := 3, vprime := [ 1, 861, 1 ], z := 862 ) ]
gap> OneSingerAlgebraInfo( "z", 8, r -> r.m, 2 );
rec( LL := 5, d := [  ], dec := 0, diff := 0, e := 3, 
  isom := [ 8, 5 ], m := 2, n := 2, q := 5, 
  vprime := [ 1, [ 3, 2 ], [ 1, 2 ] ], z := 8 )

4.2-2 DisplaySingerAlgebras
‣ DisplaySingerAlgebras( cond1, val1, cond2, val2, ... )( function )

Returns: nothing.

This function shows the precomputed data about the Singer algebras of dimension up to 10000 in a table on the screen.

The rows of the table are determined by the arguments, which have the same meaning as in the function AllSingerAlgebraInfos (4.2-1). (It is advisable to restrict the contents of the database to a small number of rows.)

The columns of the table correspond to the parameters z, q, n, LL (the Loewy length), m(q,e), diff (the difference ⌊ n(q-1)/m(q,e) ⌋ + 1 - LL), and the information whether the isomorphism type of the algebra with the given parameters is classified or not (an empty string or the flag -, respectively).

This function is available only if the Browse package is available.

gap> DisplaySingerAlgebras( "z", 7 );
    z |     q |    n |    LL | m(q,e) | diff |  isom
------+-------+------+-------+--------+------+------
    7 |     2 |    3 |     4 |      1 |    0 |     2
    7 |     3 |    6 |     3 |      6 |    0 |     3
    7 |     6 |    2 |     3 |      5 |    0 |     3
    7 |     8 |    1 |     8 |      1 |    0 |     8

gap> DisplaySingerAlgebras( "z", [ 1 .. 200 ], "diff", IsPosInt );
    z |     q |    n |    LL | m(q,e) | diff |  isom
------+-------+------+-------+--------+------+------
   70 |     3 |   12 |     3 |      8 |    1 |     3
   91 |     5 |   12 |     3 |     16 |    1 |     5
   95 |     8 |   12 |     3 |     28 |    1 |     2
  104 |     7 |   12 |     3 |     24 |    1 |     7
  123 |     2 |   20 |     3 |      6 |    1 |     2
  143 |    32 |   12 |     3 |    124 |    1 |     2
  148 |    23 |   12 |     3 |     88 |    1 |     3
  155 |    37 |   12 |     3 |    144 |    1 |     3
  182 |     5 |   12 |     3 |     16 |    1 |     5
  182 |    41 |   12 |     3 |    160 |    1 |     5
  182 |    45 |   12 |     3 |    176 |    1 |     5
  185 |    14 |   12 |     3 |     52 |    1 |     2
  185 |    27 |   12 |     3 |    104 |    1 |     2
  190 |    27 |   12 |     3 |    104 |    1 |     3
  195 |     7 |   12 |     4 |     18 |    1 |     7

4.2-3 BrowseSingerAlgebras
‣ BrowseSingerAlgebras( cond1, val1, cond2, val2, ... )( function )

Returns: the list of data selected in visual mode.

This function shows the precomputed data about the Singer algebras of dimension up to 10000 in a Browse table. The columns of the table correspond to the parameters z, q, n, LL (the Loewy length), m(q,e), diff (the difference ⌊ n(q-1)/m(q,e) ⌋ + 1 - LL), and the information whether the isomorphism type of the algebra with the given parameters is classified or not (an empty string or the flag -, respectively).

This function is available only if the Browse package is available.

gap> if IsBound( BrowseSingerAlgebras ) then
>   bsp:= [ NCurses.keys.BACKSPACE ];;  # hit the BACKSPACE key
>   d:= [ NCurses.keys.DOWN ];;  # hit the down arrow
>   l:= [ NCurses.keys.LEFT ];;  # hit the left arrow
>   BrowseData.SetReplay( Concatenation(
>         # select the 'isom?' column
>         "scrrrrrr",
>         # restrict the table to rows with unknown isom. type
>         "f-", [ NCurses.keys.ENTER ],
>         # clear the restriction
>         "!",
>         # select the 'diff' column
>         "scrrrrr",
>         # restrict the table to rows with nonzero 'diff'
>         "f", bsp, "0", d, d, d, d, l, [ NCurses.keys.ENTER ],
>         # clear the restriction
>         "!",
>         # select the first entry with 'z = 100'
>         "sc/100", [ NCurses.keys.ENTER ],
>         # add this entry to the result
>         [ NCurses.keys.ENTER ],
>         # and quit the applications
>         "Q" ) );
>   BrowseSingerAlgebras();;
>   BrowseData.SetReplay( false );
> fi;

4.2-4 IdSingerAlgebra
‣ IdSingerAlgebra( q, z )( operation )
‣ IdSingerAlgebra( A )( attribute )

Returns: a pair of positive integers, or fail.

For positive integers q and z, IdSingerAlgebra returns either fail (if the pair [ q, z ] belongs to the set of those parameters for which the distribution to isomorphism types is not yet known) or the list [ z, q' ] such that q' is minimal with the property that the Singer algebra A[q',z] is isomorphic with A[q,z].

For a Singer algebra A = A[q,z] of dimension z + 1 ≤ 10001 and with known ParametersOfSingerAlgebra (3.1-3) value, IdSingerAlgebra returns the value for the arguments q and z.

gap> List( [ 2 .. 8 ], q -> IdSingerAlgebra( q, 7 ) );
[ [ 7, 2 ], [ 7, 3 ], [ 7, 2 ], [ 7, 3 ], [ 7, 3 ], fail, [ 7, 8 ] ]
gap> IdSingerAlgebra( 100, 259 );
fail
gap> IdSingerAlgebra( SingerAlgebra( 10, 11 ) );
[ 11, 2 ]

4.3 On the Classification of Singer Algebras by Isomorphism Type

Up to now, the algebras A[q,z], for z ≤ 10000, have not yet been fully classified up to isomorphism type. The following sections show how the current status of this classification can be obtained.

4.3-1 The Datastructure that Describes our Knowledge about the Distribution to Isomorphism Types

We introduce a global variable KnownDistribution, a list that stores at position z (1 ≤ z ≤ 10000) the currently known distribution of the relevant prime residues q modulo z (that is, the smallest representatives from cyclic groups of prime residues) into equivalence classes. Each equivalence class describes the smallest union of isomorphism classes of the algebras A[q,z] that is currently known.

We encode each equivalence class by a list [ I_1, I_2, ..., I_n ] where each I_i is a list of values q such that the A[q,z] are known to be isomorphic; the algebras given by values in different sets I_j can be isomorphic or not. If n = 1 then the equivalence class is known to describe exactly one isomorphism class.

In the following sections, we will successively refine the underlying equivalence relation. Initially, we define it by equality of the Loewy vector of A[q,z] –isomorphic algebras have the same Loewy vector– such that the class for the Loewy vector v, say, has the form [ [ q_1 ], [ q_2 ], ..., [ q_n ] ], where A[q_1,z], A[q_2,z], ..., A[q_n,z] are exactly the representatives of Singer algebras with Loewy vector v.

gap> maxz:= 10000;;
gap> KnownDistribution:= [];;
gap> vectors:= "dummy";;
gap> for z in [ 1 .. maxz ] do
>      allforz:= AllSingerAlgebraInfos( "z", z );
>      vectors:= Set( allforz, r -> MakeImmutable( r.vprime ) );
>      positions:= List( allforz, r -> Position( vectors, r.vprime ) );
>      KnownDistribution[z]:= List( vectors, x -> [] );
>      for i in [ 1 .. Length( positions ) ] do
>        Add( KnownDistribution[z][ positions[i] ],
>             [ allforz[i].q ] );
>      od;
>    od;

We provide a small function that prints information about our current knowledge, and call it.

gap> ShowDistributionStatus:= function()
>    Print( "#I  min. no. of isom. types: ",
>           Sum( KnownDistribution, Length ), "\n",
>           "#I  max. no. of isom. types: ",
>           Sum( List( KnownDistribution,
>                      l -> Sum( l, Length ) ) ), "\n",
>           "#I  no. of nontriv. classes: ",
>           Sum( KnownDistribution,
>                l -> Number( l, x -> Length( x ) > 1 ) ), "\n",
>           "#I  no. of entries in these classes: ",
>           Length( Flat( Filtered( Concatenation( KnownDistribution ),
>                         x -> Length( x ) > 1 ) ) ), "\n",
>           "#I  no. of dimensions with open questions: ",
>           Number( KnownDistribution,
>                   l -> Maximum( List( l, Length ) ) > 1 ), "\n" );
>    end;;
gap> ShowDistributionStatus();
#I  min. no. of isom. types: 475581
#I  max. no. of isom. types: 768512
#I  no. of nontriv. classes: 47834
#I  no. of entries in these classes: 340765
#I  no. of dimensions with open questions: 9963

4.3-2 Isomorphism of Algebras with Loewy Vector (1, k, 1, ..., 1)

By [BHHK20, Prop. 5.2], we know that two Singer algebras with the same Loewy vector of the form (1, k, 1, ..., 1) are isomorphic; in particular, two Singer algebras of the same dimension and Loewy length 3 are isomorphic.

In the data records, a Loewy vector of the form (1, k, 1, ..., 1) appears if and only if the vprime component has one of the forms [ [ 1, z+1 ] ] or [ 1, z-1, 1 ] or [ 1, k, [ 1, z-k ] ].

gap> for z in [ 1 .. maxz ] do
>      for i in [ 1 .. Length( KnownDistribution[z] ) ] do
>        C:= KnownDistribution[z][i];
>        vector:= OneSingerAlgebraInfo( "z", z, "q", C[1][1] ).vprime;
>        if Length( vector ) = 1 or
>           ( Length( vector ) = 3 and IsInt( vector[2] ) ) then
>          KnownDistribution[z][i]:= [ Concatenation( C ) ];
>        fi;
>      od;
>    od;
gap> ShowDistributionStatus();
#I  min. no. of isom. types: 475581
#I  max. no. of isom. types: 557645
#I  no. of nontriv. classes: 31852
#I  no. of entries in these classes: 113916
#I  no. of dimensions with open questions: 5714

4.3-3 Canonical Isomorphisms of Singer Algebras

We call A[q,z] and A[q',z] canonically isomorphic if the map B(A[q,z])_i ↦ B(A[q',z])_i, for 1 ≤ i ≤ z+1, induces an algebra isomorphism A[q,z] → A[q',z]. By [BHHK21, Lemma 7.5], this holds whenever q and q' generate the same group of prime residues modulo z, and the database contains only one representative of each of the equivalence classes defined by this relation. However, it turns out that there are many more canonical isomorphisms.

The algebras A[q,z] and A[q',z] are canonically isomorphic if and only if their multiplication tables w.r.t. the canonical bases (see SingerAlg.MultTable (3.3-2)) are equal; equivalently, they are canonically isomorphic if their multiplication tables w.r.t. the canonical bases contain zero in the same places.

The parameters for which canonical isomorphisms occur have been computed and stored in the file data/joinsCan.json of the package; the file is in JSON format, and its contents can also be entered into GAP by applying EvalString (Reference: EvalString) to its contents. We use these data for refining our equivalence relation. The file encodes a list of pairs; the first entry of each pair is the relevant value of z, and the second is the list of those subsets { q_1, q_2, ... } such that there are canonical isomorphisms between A[q_1,z], A[q_2,z], ....

gap> joins:= SingerAlg.ContentsOfDataFile( "joinsCan.json" )[2];;
gap> L:= "dummy";;
gap> for ll in joins do
>      # a pair of the form [ z, [ [ q1, q2, ... ], [ ... ], ... ] ]
>      z:= ll[1];
>      for i in [ 1 .. Length( KnownDistribution[z] ) ] do
>        L:= KnownDistribution[z][i];
>        for j in [ 1 .. Length( L ) ] do
>          for k in [ 1 .. j-1 ] do
>            if IsBound( L[k] ) and IsBound( L[j] ) and
>               ForAny( ll[2],
>                       l -> IsSubset( l, Set( [ L[j][1], L[k][1] ] ) ) ) then
>              # join the two classes
>              Append( L[k], L[j] );
>              Unbind( L[j] );
>            fi;
>          od;
>        od;
>        KnownDistribution[z][i]:= SortedList( Compacted( L ) );
>      od;
>    od;
gap> ShowDistributionStatus();
#I  min. no. of isom. types: 475581
#I  max. no. of isom. types: 484234
#I  no. of nontriv. classes: 7042
#I  no. of entries in these classes: 19924
#I  no. of dimensions with open questions: 2195

Many of the canonical isomorphisms concern algebras A[q,kn,z] and A[q^k,n,z]. In fact, two such algebras are isomorphic whenever they have the same Loewy vector and z ≤ 10000 holds, see Section 4.3-7 for details.

4.3-4 Permutation Isomorphisms of Singer Algebras

We call A[q,z] and A[q',z] permutation isomorphic if there is a permutation π of the set { 1, 2, ..., z+1 } such that the map B(A[q,z])_i ↦ B(A[q',z])_{π(i)}, for 1 ≤ i ≤ z+1, induces an algebra isomorphism A[q,z] → A[q',z]. In the following, we consider only those permutation isomorphisms that are not canonical, i. e., where π is not the identity.

A necessary condition on π to induce a permutation isomorphism is that the product B(A[q',z])_{π(i)} ⋅ B(A[q',z])_{π(j)} is zero if and only if the product B(A[q,z])_i ⋅ B(A[q,z])_j is zero, for all i, j ∈ { 1, 2, ..., z+1 }. This means that π induces a graph isomorphism between the two simple undirected graphs Γ( B(A[q,z]) ) and Γ( B(A[q',z]) ), where Γ( B(A[q,z]) ) has the vertex set B(A[q,z]) and there is an edge between B(A[q,z])_i and B(A[q,z])_j if and only if B(A[q,z])_i ⋅ B(A[q,z])_j is nonzero. We use the interface to [McK90] provided by GAP's GraPe package [Soi19] for computing such a graph isomorphism if it exists, and then check whether it induces a permutation isomorphism of Singer algebras. In order to speed up the computations, we prescribe a partition of the vertices that must be respected by the desired graph isomorphism π; such a partition is given by the property that the numbers of zero entries in the i-th and π(i)-th row of the multiplication tables w.r.t. B(A[q,z]) and B(A[q',z]) must be equal.

The parameters for which permutation isomorphisms occur, which are not canonical isomorphisms, have been computed and stored in the file data/joinsPerm.json of the package; the file is in JSON format, and its contents can also be entered into GAP by applying EvalString (Reference: EvalString) to its contents. We use these data for refining our equivalence relation. If we are interested also in explicit permutation isomorphisms then we can use the file joinsPermExt.json instead. (Note that this file does not contain the permutations but abbreviated variants because the permutations would need about 75 MB of space. An earlier version of the package had contained a file of this size.)

gap> joins:= SingerAlg.ContentsOfDataFile( "joinsPerm.json" )[2];;
gap> applyjoin:= function( z, q1, q2 )
>      local i, L, j, k;
>      for i in [ 1 .. Length( KnownDistribution[z] ) ] do
>        L:= KnownDistribution[z][i];
>        for j in [ 1 .. Length( L ) ] do
>          for k in [ 1 .. j-1 ] do
>            if IsSubset( Set( [ q1, q2 ] ),
>                         Set( [ L[j][1], L[k][1] ] ) ) then
>              # join the two equivalence classes
>              Append( L[k], L[j] );
>              Unbind( L[j] );
>              KnownDistribution[z][i]:= SortedList( Compacted( L ) );
>              return;
>            fi;
>          od;
>        od;
>      od;
>      # This triple was not used at all.
>      Print( "#E  unnecessary join: ", [ z, q1, q2 ], "\n" );
>    end;;
gap> for l in joins do
>      # 'l' is a triple of the form [ z, q1, q2 ]
>      CallFuncList( applyjoin, l );
>    od;
gap> ShowDistributionStatus();
#I  min. no. of isom. types: 475581
#I  max. no. of isom. types: 481744
#I  no. of nontriv. classes: 5174
#I  no. of entries in these classes: 15608
#I  no. of dimensions with open questions: 1754

Only 94 candidate pairs that satisfy the abovementioned necessary criterion for permutation isomorphism do not admit a graph automorphism of the graphs Γ, thus the criterion is quite good.

In all cases where a graph isomorphism is returned, the proposed permutation really induces an algebra isomorphism. This implies: Any two Singer algebras in our list for which we do not know yet whether they are isomorphic are definitely not permutation isomorphic.

4.3-5 Combinatorial Invariants Distinguishing Singer Algebras

We know several subspaces of Singer algebras that are invariant under algebra isomorphisms. Examples are the members of the radical and socle series, and sums and products of invariant subspaces, see Section 3.3. If we know an invariant subspace such that the dimension is different for two Singer algebras then these algebras are not isomorphic.

In the following, we consider the combinatorial invariants that are used in the function ConsiderInvariantsByParameters (3.5-1). The idea is to run over the nontrivial equivalence classes in KnownDistribution, and to split these classes whenever we find a distinguishing invariant. (There are cases where more than 500 combinatorial invariants exist. We had stopped the computations after at most 100 of them.)

The parameters for which such splits occur have been computed and stored in the file data/splitsComb.json of the package; the file is in JSON format, and its contents can also be entered into GAP by applying EvalString (Reference: EvalString) to its contents. We use these data for refining our equivalence relation.

gap> splits:= SingerAlg.ContentsOfDataFile( "splitsComb.json" )[2];;
gap> applysplit:= function( z, entry, entries, why )
>      local pos, len, elen, i;
>      pos:= Position( KnownDistribution[z], entry );
>      if pos = fail then
>        Print( "#E  did not find <entry> = ", entry,
>               " in KnownDistribution[", z, "]\n" );
>      elif Set( entry ) <> Union( entries ) then
>        Print( "#E  <entry> = ", entry,
>               " does not correspond to <entries> = ", entries, "\n" );
>      else
>        len:= Length( KnownDistribution[z] );
>        elen:= Length( entries ) - 1;
>        for i in [ len, len-1 .. pos+1 ] do
>          KnownDistribution[z][ i+elen ]:= KnownDistribution[z][i];
>        od;
>        KnownDistribution[z]{ [ pos .. pos + elen ] }:= entries;
>      fi;
>    end;;
gap> for l in splits do
>      CallFuncList( applysplit, l );
>    od;
gap> ShowDistributionStatus();
#I  min. no. of isom. types: 479512
#I  max. no. of isom. types: 481744
#I  no. of nontriv. classes: 1934
#I  no. of entries in these classes: 5422
#I  no. of dimensions with open questions: 791

4.3-6 Other Invariants Distinguishing Singer Algebras

As soon as invariants are involved that are not combinatorial, in the sense of Section 3.3, computations are expected to get harder.

An example of such a non-combinatorial invariant is the dimension of the matrix Lie algebra of derivations (see Derivations (Reference: Derivations)). This works for low dimensional examples, for example the smallest one from the list in data/splitsComb.json, which states that A[3,40] and A[19,40] are not isomorphic.

gap> splits[1];
[ 40, [ [ 3 ], [ 19 ] ], [ [ [ 3 ] ], [ [ 19 ] ] ], "Roots(0,2,1)" ]
gap> b:= CanonicalBasis( SingerAlgebra( 3, 40, GF(2) ) );;
gap> Dimension( Derivations( b ) );
118
gap> b:= CanonicalBasis( SingerAlgebra( 19, 40, GF(2) ) );;
gap> Dimension( Derivations( b ) );
112

This argument distiguishes also A[23,182] and A[25,182], where the dimensions of derivations are 9514 and 9502, respectively. For both A[11,171] and A[68,171], the algebra of derivations has dimension 8048. However, these computations run out of space for larger examples.

Another type of invariant concerns the number of solutions of an equation. A few open questions can be decided by computing the cardinality of the set

{ (x,y) ∈ V × V; x ⋅ y ∈ U },

where U and V are combinatorial subspaces of the algebra in question, see SingerAlg.NumberOfProductsInSubspace (3.5-3).

These cases are collected in the file data/splitsOther.json. Computations of this kind are feasible only if the number of indeterminates is small, we call SingerAlg.NumberOfProductsInSubspace (3.5-3) with third argument 15 (which is the default value).

gap> splits:= SingerAlg.ContentsOfDataFile( "splitsOther.json" )[2];;
gap> for l in splits do
>      CallFuncList( applysplit, l );
>    od;
gap> ShowDistributionStatus();
#I  min. no. of isom. types: 481069
#I  max. no. of isom. types: 481744
#I  no. of nontriv. classes: 649
#I  no. of entries in these classes: 1495
#I  no. of dimensions with open questions: 350

Finally, we check whether the currently stored information about the open cases (in the file data/opencases.json of the package) and about the distribution to isomorphism types (in the file data/id.json) coincides with the above data.

gap> str:= Concatenation( "[",
>              SingerAlg.ComputedOpenCases(), "]" );;
gap> if EvalString( str ) <>
>       SingerAlg.ContentsOfDataFile( "opencases.json" )[2] then
>      Print( "#E  'data/opencases.json' is not up to date." );
>    fi;
gap> str:= Concatenation( "[",
>              SingerAlg.ComputedIdInfoForSingerAlgebras(), "]" );;
gap> if EvalString( str ) <> SingerAlg.IdData[2] then
>      Print( "#E  The stored isomorphism type data are not up to date." );
>    fi;

4.3-7 Inspect some of the Canonical Isomorphisms

By [BHHK21, proof of Prop. 3.6], the canonical bases b_0, b_1, ..., b_z and B_0, B_1, ..., B_z of the algebras A[q,kn,z] and A[q^k,n,z], respectively, have the property that B_i B_j is nonzero whenever b_i b_j is nonzero; the converse is in general not true; for example, consider the case n = 1.

However, it turns out that at least under the condition z ≤ 10000, the converse holds as soon as A[q,kn,z] and A[q^k,n,z] have the same Loewy vector. Note that this implies that A[q,kn,z] and A[q^k,n,z] are then canonically isomorphic.

We can verify this observation as follows. First we collect, for all z, the relevant parameters q, q^k.

gap> candidates:= [];;
gap> for z in [ 1 .. 10000 ] do
>      # Fetch the data for this z and sort them by decreasing n.
>      cand:= AllSingerAlgebraInfos( "z", z );
>      SortParallel( List( cand, x -> - x.n ), cand );
>      qs:= List( cand, x -> x.q );
>      # Run over those candidates for which we know
>      # that the Loewy vector determines the isomorphism type.
>      for r in Filtered( cand, r -> Length( r.vprime ) <> 3 ) do
>        q:= r.q;
>        n:= r.n;
>        result:= [ q ];
>        # Find parameters [ Q, m, z ] such that m divides n
>        # and Q is the minimal representative of the subgroup of prime
>        # residues modulo z that is generated by q^(n/m),
>        # and such that the Loewy vector is the same as for r.
>        for d in Difference( DivisorsInt( r.n ), [ 1 ] ) do
>          m:= n/d;
>          Q:= PowerModInt( q, d, z );
>          Q:= Minimum( List( PrimeResidues( m ), 
>                             e -> PowerModInt( Q, e, z ) ) );
>          if Q = 1 then
>            Q:= z+1;
>          fi;
>          R:= cand[ Position( qs, Q ) ];
>          if r.vprime = R.vprime then
>            # The Loewy vectors for q and Q are equal.
>            AddSet( result, Q );
>          fi;
>        od;
>        if Length( result ) > 1 then
>          Add( candidates, [ z, result ] );
>        fi;
>      od;
>    od;
gap> Length( candidates );
22518

Then we test whether all these candidates occur in the file that lists the precomputed canonical isomorphisms.

gap> joins:= SingerAlg.ContentsOfDataFile( "joinsCan.json" )[2];;
gap> for entry in candidates do
>      z:= entry[1];
>      joinsz:= First( joins, l -> l[1] = z );
>      if not ForAny( joinsz[2], l -> IsSubset( l, entry[2] ) ) then
>        Error( "did not find ", entry, " among the known canon. isom." );
>      fi;
>    od;

4.4 Files of the Database of Singer Algebras

The data files are stored in the data subdirectory of the package directory. Currently they are all valid JSON (JavaScript Object Notation) texts (see [JSO14]), and they are also valid GAP code. Thus they can be evaluated with SingerAlg.ContentsOfDataFile (3.6-3).

Each file contains a GAP list. Its first entry is a list of strings that describes the contents and the format of the remaining entries.

 [Top of Book]  [Contents]   [Previous Chapter]   [Next Chapter] 
Goto Chapter: Top 1 2 3 4 Bib Ind

generated by GAPDoc2HTML