1#############################################################################
2####
3##
4#W  anupqi.gi              ANUPQ package                          Greg Gamble
5##
6##  This file installs interactive functions that execute individual pq  menu
7##  options.
8##
9#Y  Copyright (C) 2001  Lehrstuhl D fuer Mathematik,  RWTH Aachen,  Germany
10##
11
12#############################################################################
13##
14#F  PQ_UNBIND( <datarec>, <fields> ) . . . . . unbind fields of a data record
15##
16##  unbinds the fields in the list <fields> of that data record <datarec>.
17##
18InstallGlobalFunction( PQ_UNBIND, function( datarec, fields )
19local field;
20  for field in fields do
21    Unbind( datarec.(field) );
22  od;
23end );
24
25#############################################################################
26##
27#F  PQ_AUT_GROUP( <G> ) . . . . . . . . . . . . . . . . .  automorphism group
28##
29##  returns the automorphism group of  a  $p$-group  as  a  record,  avoiding
30##  computation if possible (currently it *isn't*  possible),  or  else  uses
31##  {\AutPGrp}'s `AutomorphismGroupPGroup'.
32##
33InstallGlobalFunction( PQ_AUT_GROUP, function( G )
34
35  local autgrp;
36
37  if not IsPGroup(G) then
38      Error("group <G> must be a p-group\n");
39  fi;
40  if false and HasANUPQAutomorphisms(G) then
41      # Can't use this because we currently don't know how to interpret
42      # the automorphism information returned by the standalone properly.
43
44      autgrp := PqSupplementInnerAutomorphisms(G);
45
46  elif false and HasAutomorphismGroup(G) then
47
48      # Can't use existing automorphism information because it does not
49      # contain the information required by the standalone.
50
51      autgrp := AutomorphismGroup( G );
52
53  elif LoadPackage("autpgrp") = true or IsAbelian(G) then
54
55      autgrp := AutomorphismGroupPGroup(G);
56
57  else
58      return Error( "since package `AutPGrp' is not installed\n",
59                    "<G> must have class 1 or <G>'s aut. group must be known.\n",
60                    "Please install the `AutPGrp' package\n" );
61  fi;
62  return autgrp;
63end );
64
65#############################################################################
66##
67#F  PQ_AUT_INPUT( <datarec>, <G> : <options> ) . . . . . . automorphism input
68##
69##  inputs automorphism data for `<datarec>.group' given by <options> to  the
70##  `pq' binary derived from the pc group  <G>  (used  in  option  1  of  the
71##  $p$-Group Generation menu and option 2 of the Standard Presentation menu).
72##
73InstallGlobalFunction( PQ_AUT_INPUT, function( datarec, G )
74
75  local   autrec,  nrautos,  rank,  gens,  i,  aut,  j,  g, exponents;
76
77  autrec  := PQ_AUT_GROUP( G );
78  nrautos := Length( autrec.glAutos ) + Length( autrec.agAutos );
79
80  ## the automorphisms have to be in a special form which PQ_AUT_GROUP()
81  ## *must* deliver.
82
83  rank := RankPGroup( G );
84  gens := PcgsPCentralSeriesPGroup( G );
85
86  ToPQ(datarec, [ nrautos ], [ "  #number of automorphisms" ]);
87
88  ##  First write out the automorphisms generating a soluble normal subgroup
89  ##  of the automorphism group of the p-group.  These automorphisms may
90  ##  not have a faithful representation on the Frattini quotient of the
91  ##  p-group and are treated accordingly by the standalone.
92  ##
93  ##  They are written out in bottom up fashion as this is the order in
94  ##  which the orbit algorithm for a group given by an ag-system needs
95  ##  them.
96  for i in Reversed([1..Length(autrec.agAutos)]) do
97      aut := autrec.agAutos[i];
98
99      for j in [1..rank] do
100          g := gens[j];
101          exponents := Flat( List( ExponentsOfPcElement(gens, Image( aut, g )),
102                                   e -> [ String(e), " "] ) );
103
104          ToPQ(datarec, [ exponents ],
105               [ " #gen'r exp'ts of im(ag aut ", i, ", gen ", j, ")" ]);
106      od;
107  od;
108
109  ##  Now output the automorphisms from the insoluble quotient of the
110  ##  automorphism group of the p-group.  These have a faithful
111  ##  representation on the Frattini quotient of the p-group and are
112  ##  treated accordingly by the standalone.
113  for i in Reversed( [1..Length(autrec.glAutos)] ) do
114      aut := autrec.glAutos[i];
115
116      for j in [1..rank] do
117          g := gens[j];
118          exponents := Flat( List( ExponentsOfPcElement(gens, Image( aut, g )),
119                                   e -> [ String(e), " "] ) );
120
121          ToPQ(datarec, [ exponents ],
122               [ " #gen'r exp'ts of im(gl aut ", i, ", gen ", j, ")" ]);
123      od;
124  od;
125
126  if PQ_MENU(datarec) = "pG" then
127      ##  ?? Why only the pG menu ??
128      ##  Finally, tell the standalone the number of soluble automorphisms
129      ##  and the relative order of each automorphism.
130      ToPQ(datarec, [ Length(autrec.agOrder) ],
131           [ "  #number of soluble automorphisms" ]);
132
133      for i in Reversed( [1..Length( autrec.agOrder )] ) do
134          ToPQ( datarec, [ autrec.agOrder[i] ],
135                [ "  #rel order of ", i, "th ag automorphism" ] );
136      od;
137  fi;
138
139end );
140
141#############################################################################
142##
143#F  PQ_MANUAL_AUT_INPUT(<datarec>,<mlist>) . automorphism input w/o an Aut gp
144##
145##  inputs automorphism data for `<datarec>.group' given by  <mlist>  to  the
146##  `pq' binary.
147##
148InstallGlobalFunction( PQ_MANUAL_AUT_INPUT, function( datarec, mlist )
149local line, nauts, nsolauts, rank, nexpts, i, j, aut, exponents;
150  nauts  := Length(mlist);
151  rank   := Length(mlist[1]);
152  ToPQ(datarec, [ nauts ], [ "  #no. of auts" ]);
153  if datarec.line = "Input the number of exponents: " then
154    nexpts := Length(mlist[1][1]);
155    ToPQ(datarec, [ nexpts ], [ "  #no. of exponents" ]);
156  fi;
157  for i in [1..nauts] do
158    aut := mlist[i];
159    for j in [1..rank] do
160      exponents := Flat( List( aut[j], e -> [ String(e), " "] ) );
161      ToPQ(datarec, [ exponents ],
162                    [ " #gen'r exp'ts of im(aut ", i, ", gen ", j, ")" ]);
163    od;
164  od;
165  if PQ_MENU(datarec) = "pG" then
166    ##  ?? Why only the pG menu ??
167    ##  Finally, tell the standalone the number of soluble automorphisms
168    ##  and the relative order of each automorphism.
169    ToPQ(datarec, [ datarec.NumberOfSolubleAutomorphisms ],
170                  [ "  #number of soluble automorphisms" ]);
171    if datarec.NumberOfSolubleAutomorphisms > 0 then
172      for i in datarec.RelativeOrders do
173        ToPQ( datarec, [ datarec.RelativeOrders[i] ],
174                       [ "  #rel order of ", i, "th ag automorphism" ] );
175      od;
176    fi;
177  fi;
178end );
179
180#############################################################################
181##
182#F  PQ_AUT_ARG_CHK(<minnargs>, <args>) . checks args for a func defining auts
183##
184##  checks that  the  arguments  make  sense  for  a  function  that  defines
185##  automorphisms, and if one fo the arguments is a list checks as much as is
186##  possible that it is a list of  matrices  that  will  be  valid  input  as
187##  automorphisms for the `pq' binary.  If  the  arguments  look  ok  a  list
188##  containing the `ANUPQData.io' index of the data record and, if  relevant,
189##  a list of matrices is returned.
190##
191InstallGlobalFunction( PQ_AUT_ARG_CHK, function( minnargs, args )
192local ioIndex, datarec, mlist, rank, nexpts;
193  if Length(args) < minnargs then
194    Error("expected at least 1 argument\n"); #minnargs is 0 or 1
195  elif 2 < Length(args) then
196    Error("expected at most 2 arguments\n");
197  fi;
198  if not IsEmpty(args) and IsList(args[ Length(args) ]) then
199    mlist := args[ Length(args) ];
200    args := args{[1 .. Length(args) - 1]};
201  fi;
202  ioIndex := CallFuncList(PqProcessIndex, args);
203  if not IsBound(mlist) then
204    return [ioIndex];
205  elif not( IsList(mlist) and ForAll(mlist, IsMatrix) and
206            ForAll(Flat(mlist), i -> IsInt(i) and i >= 0) ) then
207    Error("<mlist> must be a list of matrices with ",
208          "non-negative integer coefficients\n");
209  fi;
210  datarec := ANUPQData.io[ ioIndex ];
211  if IsBound( datarec.pQuotient ) then
212    rank := RankPGroup( datarec.pQuotient );
213  else
214    rank := Length(mlist[1]); # Should we allow this?
215  fi;
216  if not ForAll(mlist, mat -> Length(mat) = rank) then
217    Error("no. of rows in each matrix of <mlist> must be the rank of ",
218          "p-quotient (", rank, ")\n");
219  fi;
220  nexpts := Length(mlist[1][1]);
221  if not ForAll(mlist, mat -> Length(mat[1]) = nexpts) then
222    Error("each matrix of <mlist> must have the same no. of columns\n");
223  fi;
224  return [ioIndex, mlist];
225end );
226
227#############################################################################
228##
229#F  PQ_PC_PRESENTATION( <datarec>, <menu> ) . . . . . .  p-Q/SP menu option 1
230##
231##  inputs  data  given  by  <options>  to  the   `pq'   binary   for   group
232##  `<datarec>.group' to compute a  pc  presentation  (do  option  1  of  the
233##  relevant menu) according to the  <menu>  menu,  where  <menu>  is  either
234##  `"pQ"' (main $p$-Quotient menu) or `"SP' (Standard Presentation menu).
235##
236InstallGlobalFunction( PQ_PC_PRESENTATION, function( datarec, menu )
237local gens, rels, p, fpgrp, identities, pcgs, len, strp, i, j, Rel, line;
238
239  p := VALUE_PQ_OPTION("Prime", fail, datarec); # "Prime" is a `global' option
240
241  PQ_MENU(datarec, menu);
242
243  identities := menu = "pQ" and
244                VALUE_PQ_OPTION("Identities", [], datarec) <> [];
245
246  # Option 1 of p-Quotient/Standard Presentation Menu: defining the group
247  ToPQk(datarec, [1], ["  #define group"]);
248  if VALUE_PQ_OPTION("GroupName", "[grp]", datarec) = "[grp]" and
249     IsBound(datarec.group) and IsBound(datarec.group!.Name) then
250    datarec.GroupName := datarec.group!.Name;
251  fi;
252  ToPQk(datarec, ["name ",  datarec.GroupName], []);
253  ToPQk(datarec, ["prime ", p], []);
254  if identities then
255    datarec.prevngens := 0;
256    ToPQk(datarec, ["class ", 1], []);
257  else
258    ToPQk(datarec, ["class ", VALUE_PQ_OPTION("ClassBound", 63, datarec)], []);
259  fi;
260  ToPQk(datarec, ["exponent ", VALUE_PQ_OPTION("Exponent", 0, datarec)], []);
261                                             # "Exponent" is a `global' option
262  if VALUE_PQ_OPTION( "Metabelian", false, datarec ) = true then
263    ToPQk(datarec, [ "metabelian" ], []);
264  fi;
265  ToPQk(datarec, ["output ", VALUE_PQ_OPTION("OutputLevel", 0, datarec)], []);
266
267  if IsFpGroup(datarec.group) then
268    gens := FreeGeneratorsOfFpGroup(datarec.group);
269    rels := VALUE_PQ_OPTION("Relators", datarec);
270    if rels = fail then
271      rels := RelatorsOfFpGroup(datarec.group);
272    elif ForAll( rels, rel -> PqParseWord(datarec.group, rel) ) then
273      Info(InfoANUPQ, 2, "Relators parsed ok.");
274    fi;
275  elif not( IsPGroup(datarec.group) ) then
276    fpgrp := FpGroupPcGroup( datarec.group );
277    gens := FreeGeneratorsOfFpGroup(fpgrp);
278    rels := RelatorsOfFpGroup(fpgrp);
279  else
280    pcgs := PcgsPCentralSeriesPGroup(datarec.group);
281    datarec.pcgs := pcgs;
282    len  := Length(pcgs);
283    gens := List( [1..len], i -> Concatenation( "g", String(i) ) );
284    strp := String(p);
285
286    Rel := function(elt, eltstr)
287      local rel, expts, factors;
288
289      rel := eltstr;
290      expts := ExponentsOfPcElement( pcgs, elt );
291      if ForAny( expts, x -> x<>0 )  then
292        factors
293            := Filtered(
294                   List( [1..len],
295                         function(i)
296                           if expts[i] = 0 then
297                             return "";
298                           fi;
299                           return Concatenation(gens[i], "^", String(expts[i]));
300                         end ),
301                   factor -> factor <> "");
302        Append(rel, "=");
303        Append(rel, JoinStringsWithSeparator(factors, "*"));
304      fi;
305      return rel;
306    end;
307
308    rels := List( [1..len],
309                  i -> Rel( pcgs[i]^p, Concatenation(gens[i], "^", strp) ) );
310    for i in [1..len] do
311      for j in [1..i-1]  do
312        Add(rels, Rel( Comm( pcgs[i], pcgs[j] ),
313                       Concatenation("[", gens[i], ",", gens[j], "]") ));
314      od;
315    od;
316  fi;
317  if Length(gens) > 511 then
318    # The pq program defines MAXGENS to be 511 in `../include/runtime.h'
319    # ... on the other hand, the number of pc gen'rs can be up to 65535
320    Error("number of defining generators, ", Length(gens), ", too large.\n",
321          "The pq program defines MAXGENS (the maximum number of defining\n",
322          "generators) to be 511.\n");
323  fi;
324  datarec.gens := gens;
325  datarec.rels := rels;
326  ToPQk(datarec, "gens", []);
327  datarec.match := true;
328  ToPQ(datarec, "rels", []);
329  ## pq is intolerant of long lines and integers that are split over lines
330  #rels := Concatenation(
331  #            "relators   { ", JoinStringsWithSeparator( rels, ", " ), " };");
332  #while Length(rels) >= 69 do
333  #  i := 68;
334  #  while not (rels[i] in "*^, ") do i := i - 1; od;
335  #  ToPQk(datarec, [ rels{[1 .. i]} ], []);
336  #  rels := Concatenation( "  ", rels{[i + 1 .. Length(rels)]} );
337  #od;
338  #ToPQ(datarec, [ rels ], []);
339  datarec.haspcp := true;
340  # The `pq' only sets OutputLevel locally within the menu item
341  # ... for the GAP interface this would be too confusing; so we
342  # set it `globally'
343  PQ_SET_OUTPUT_LEVEL(datarec, datarec.OutputLevel);
344  PQ_SET_GRP_DATA(datarec);
345  if identities and datarec.ngens[1] <> 0 then
346    PQ_EVALUATE_IDENTITIES(datarec);
347    VALUE_PQ_OPTION("ClassBound", 63, datarec);
348    while datarec.class < datarec.ClassBound and
349          datarec.prevngens <> datarec.ngens[ datarec.class ] do
350      PQ_NEXT_CLASS(datarec);
351    od;
352  fi;
353end );
354
355#############################################################################
356##
357#F  PqPcPresentation( <i> : <options> ) . . user version of p-Q menu option 1
358#F  PqPcPresentation( : <options> )
359##
360##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
361##  binary to compute the pc presentation  of  the  quotient  (determined  by
362##  <options>) of the group of the process, which for process <i>  is  stored
363##  as `ANUPQData.io[<i>].group'.
364##
365##  The  possible  <options>  are  the  same  as  for  the  interactive  `Pq'
366##  (see~"Pq!interactive")   function,   namely:    `Prime',    `ClassBound',
367##  `Exponent', `Relators', `GroupName', `Metabelian' and `OutputLevel'  (see
368##  Chapter~"ANUPQ options" for a detailed description  for  these  options).
369##  The option `Prime' is required  unless  already  provided  to  `PqStart'.
370##  Also, option `ClassBound' *must* be supplied.
371##
372##  *Notes*
373##
374##  The pc presentation is held by the `pq' binary. There is no output  of  a
375##  {\GAP} pc group; see~`PqCurrentGroup' ("PqCurrentGroup") if you need  the
376##  corresponding {\GAP} pc group.
377##
378##  For those familiar with the `pq' binary, `PqPcPresentation' performs menu
379##  item 1 of the main $p$-Quotient menu.
380##
381InstallGlobalFunction( PqPcPresentation, function( arg )
382local datarec;
383  PQ_OTHER_OPTS_CHK("PqPcPresentation", true);
384  datarec := CallFuncList(ANUPQDataRecord, arg);
385  PQ_PC_PRESENTATION( datarec, "pQ" );
386end );
387
388#############################################################################
389##
390#F  PQ_SAVE_PC_PRESENTATION( <datarec>, <filename> ) . . .  p-Q menu option 2
391##
392##  directs the `pq' binary to save the pc presentation  previously  computed
393##  for  `<datarec>.group'  to  <filename>  using  option  2  of   the   main
394##  $p$-Quotient menu.
395##
396InstallGlobalFunction( PQ_SAVE_PC_PRESENTATION, function( datarec, filename )
397  PQ_MENU(datarec, "pQ");
398  ToPQ(datarec, [ 2 ], [ "  #save pc presentation to file" ]);
399  datarec.filter := ["Presentation"];
400  ToPQ(datarec, [ filename ], [ "  #filename" ]);
401  Unbind(datarec.filter);
402end );
403
404#############################################################################
405##
406#F  PQ_PATH_CURRENT_DIRECTORY() . . . . . . . . . .  essentially the UNIX pwd
407##
408##  returns a string that is the path of the current directory.
409##
410InstallGlobalFunction( PQ_PATH_CURRENT_DIRECTORY, function()
411local path, stream;
412  path := "";
413  stream := OutputTextString(path, true);
414  if 0 = Process( DirectoryCurrent(),
415                  Filename(DirectoriesSystemPrograms(), "pwd"),
416                  InputTextNone(),
417                  stream,
418                  [] ) then
419    CloseStream(stream);
420    return Chomp(path);
421  fi;
422  Error("could not determine the path of the current directory!?!\n");
423end );
424
425#############################################################################
426##
427#F  PQ_CHK_PATH(<filename>, <rw>, <datarec>) . . . . . . .  check/add to path
428##
429##  checks <filename> is a non-empty string, if it doesn't begin with  a  `/'
430##  prepends a path for the current directory, and checks the result  is  the
431##  name of a readable (resp. writable) if <rw> is `"r"' (resp.  if  <rw>  is
432##  `"w"') and if there is no error returns the result.
433##
434InstallGlobalFunction( PQ_CHK_PATH, function( filename, rw, datarec )
435  if not IsString(filename) or filename = "" then
436    Error( "argument <filename> must be a non-empty string\n" );
437  fi;
438  if filename[1] <> '/' then
439    # we need to do this as pq executes in ANUPQData.tmpdir
440    filename := Concatenation(PQ_PATH_CURRENT_DIRECTORY(), "/", filename);
441  fi;
442  if rw = "r" then
443    if IsReadableFile(filename) <> true then
444      Error( "file with name <filename> is not readable\n" );
445    fi;
446  else # rw = "w"
447    if not IsBound(datarec.setupfile) then
448      PrintTo(filename, ""); # This is what will generate the error
449                             # but it also ensures it's empty
450    fi;
451    if IsWritableFile(filename) <> true then
452      Error( "file with name <filename> cannot be written to\n" );
453    fi;
454  fi;
455  return filename;
456end );
457
458#############################################################################
459##
460#F  PqSavePcPresentation( <i>, <filename> ) . .  user ver. of p-Q menu opt. 2
461#F  PqSavePcPresentation( <filename> )
462##
463##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
464##  program to save the pc presentation previously computed for the  quotient
465##  of the group of that process to the file with  name  <filename>.  If  the
466##  first character of the  string  <filename>  is  not  `/',  <filename>  is
467##  assumed to be the path of a writable file relative to  the  directory  in
468##  which  {\GAP}  was  started.  A   saved   file   may   be   restored   by
469##  `PqRestorePcPresentation' (see~"PqRestorePcPresentation").
470##
471##  *Note:* For those familiar with the `pq'  binary,  `PqSavePcPresentation'
472##  performs menu item 2 of the main $p$-Quotient menu.
473##
474InstallGlobalFunction( PqSavePcPresentation, function( arg )
475local datarec, filename;
476  if 0 = Length(arg) or Length(arg) > 2 then
477    Error( "expected 1 or 2 arguments\n" );
478  fi;
479  datarec := CallFuncList(ANUPQDataRecord, arg{[1..Length(arg) - 1]});
480  filename := PQ_CHK_PATH( arg[Length(arg)], "w", datarec );
481  PQ_SAVE_PC_PRESENTATION( datarec, filename );
482end );
483
484#############################################################################
485##
486#F  PQ_RESTORE_PC_PRESENTATION( <datarec>, <filename> ) . . p-Q menu option 3
487##
488##  directs the `pq' binary to restore the pc presentation  previously  saved
489##  to <filename> using option 3 of the main $p$-Quotient menu.
490##
491InstallGlobalFunction( PQ_RESTORE_PC_PRESENTATION, function( datarec, filename )
492  PQ_MENU(datarec, "pQ");
493  ToPQ(datarec, [ 3 ], [ "  #restore pc presentation from file" ]);
494  datarec.match := true;
495  ToPQ(datarec, [ filename ], [ "  #filename" ]);
496  datarec.haspcp := true;
497  PQ_SET_GRP_DATA(datarec);
498end );
499
500#############################################################################
501##
502#F  PqRestorePcPresentation( <i>, <filename> ) . user ver. of p-Q menu opt. 3
503#F  PqRestorePcPresentation( <filename> )
504##
505##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
506##  program to restore the pc presentation previously saved to <filename>, by
507##  `PqSavePcPresentation'   (see~"PqSavePcPresentation").   If   the   first
508##  character of the string <filename> is not `/', <filename> is  assumed  to
509##  be the path of a readable file relative to the directory in which  {\GAP}
510##  was started.
511##
512##  *Note:*
513##  For  those  familiar  with  the  `pq'  binary,  `PqRestorePcPresentation'
514##  performs menu item 3 of the main $p$-Quotient menu.
515##
516InstallGlobalFunction( PqRestorePcPresentation, function( arg )
517local datarec, filename;
518  if 0 = Length(arg) or Length(arg) > 2 then
519    Error( "expected 1 or 2 arguments\n" );
520  fi;
521  datarec := CallFuncList(ANUPQDataRecord, arg{[1..Length(arg) - 1]});
522  filename := PQ_CHK_PATH( arg[Length(arg)], "r", datarec );
523  PQ_RESTORE_PC_PRESENTATION( datarec, filename );
524end );
525
526#############################################################################
527##
528#F  PQ_DISPLAY_PRESENTATION( <datarec> ) . . . . . . . . .  any menu option 4
529##
530##  directs the `pq' binary to display the pc presentation of  the  group  to
531##  the current class, using option 4 of the current menu.
532##
533InstallGlobalFunction( PQ_DISPLAY_PRESENTATION, function( datarec )
534  if datarec.menu[ Length(datarec.menu) ] <> 'G' and
535     VALUE_PQ_OPTION("OutputLevel", datarec) <> fail then
536    PQ_SET_OUTPUT_LEVEL( datarec, datarec.OutputLevel );
537  fi;
538  ToPQ(datarec, [ 4 ], [ "  #display presentation" ]);
539end );
540
541#############################################################################
542##
543#F  PQ_GRP_EXISTS_CHK( <datarec> ) . . check the `pq' binary knows about a gp
544##
545##  checks that `<datarec>.ngens' is set and non-empty (which can only happen
546##  if the `pq' binary has been fed a group) and generates an error if not.
547##
548InstallGlobalFunction( PQ_GRP_EXISTS_CHK, function( datarec )
549  if not IsBound(datarec.ngens) or IsEmpty(datarec.ngens) then
550    Error( "huh! No current group defined for this process!?\n" );
551  fi;
552end );
553
554#############################################################################
555##
556#F  PQ_SET_GRP_DATA( <datarec> ) .  save group data of current class of group
557##
558##  If `<datarec>.matchedline' is not  set  the  `pq'  binary  is  called  to
559##  display the presentation; usually  `<datarec>.matchedline'  is  set  when
560##  filtering `pq' output for lines starting with `"Group"' (the  value  set
561##  for `<datarec>.match'), but no such  lines  occur  when  computing  a  pc
562##  presentation with the `OutputLevel' option set to 0, or when restoring  a
563##  pc presentation, or when computing tails etc. From this line  the  fields
564##  `name', `class' and `forder' of the record <datarec> are set to the name,
565##  class  and  factored   order   of   that   group,   respectively.   Also,
566##  `<datarec>.ngens' is updated, and if it is afterwards incomplete and  the
567##  call to `PQ_SET_GRP_DATA' was not initiated by `PQ_DATA'  then  `PQ_DATA'
568##  is called to ensure `<datarec>.ngens' is complete.
569##
570InstallGlobalFunction( PQ_SET_GRP_DATA, function( datarec )
571local line, classpos;
572  if IsBound(datarec.setupfile) then
573    # A fudge ... some things we can only know by actually running it!
574    Info(InfoANUPQ + InfoWarning,1,
575         "Guess made of `class' and `ngens' fields");
576    Info(InfoANUPQ + InfoWarning,1,
577         "... please check commands ok by running without `SetupFile' option");
578    Info(InfoANUPQ + InfoWarning,1,
579         "and comparing with `ToPQ> ' commands observed at InfoANUPQ level 4");
580    datarec.class := datarec.ClassBound;
581    datarec.ngens := [ 1 ];
582    return;
583  fi;
584  # Either datarec.matchedline is of one of the following forms:
585  # Group completed. Lower exponent-<p> central class = <c>, Order = <p>^<n>
586  # Group: [grp] to lower exponent-<p> central class <c> has order <p>^<n>
587  if not IsBound(datarec.matchedline) then
588    PushOptions(rec(nonuser := true));
589    ToPQ(datarec, [ 4 ], [ "  #display presentation" ]);
590    PopOptions();
591  fi;
592  line := SplitString(datarec.matchedline, "", ":,. ^\n");
593  if line[2] = "completed" then
594    classpos := Position(line, "class") + 2;
595    #if not IsBound(datarec.name) then #do we need to bother?
596    #  datarec.name := "[grp]";
597    #fi;
598  else
599    # Only the ``incomplete'' form of datarec.matchedline gives the name
600    datarec.name := line[2];
601    datarec.gpnum := JoinStringsWithSeparator(
602                         line{[3 .. Position(line, "to") - 1]}, " " );
603    classpos := Position(line, "class") + 1;
604  fi;
605  datarec.class  := Int( line[classpos] );
606  datarec.forder := List( line{[classpos + 3, classpos + 4]}, Int);
607  PQ_UNBIND(datarec, ["match", "matchedline"]);
608  # First see if we can update datarec.ngens cheaply
609  if not IsBound(datarec.ngens) then
610    datarec.ngens := [];
611  fi;
612  if datarec.class > 0 then
613    datarec.ngens[ datarec.class ] := datarec.forder[2];
614    #The `pq' binary reduces the class by 1
615    #if the no. of gen'rs doesn't increase
616    Unbind( datarec.ngens[ datarec.class + 1 ] );
617  fi;
618
619  if not IsBound(datarec.inPQ_DATA) and not IsDenseList(datarec.ngens) then
620    # It wasn't possible to update datarec.ngens cheaply
621    PQ_DATA( datarec );
622  fi;
623end );
624
625#############################################################################
626##
627#F  PQ_DATA( <datarec> ) . . . . gets class/gen'r data from (A)p-Q menu opt 4
628##
629##  ensures that the menu is a $p$-Quotient menu and that the output level is
630##  3 and using option 4 of the now  current  menu  extracts  the  number  of
631##  generators of each class currently known to the `pq' binary.  (The  order
632##  of each $p$-class quotient is taken as $p^n$ where $n$ is the  number  of
633##  generators for the class; this may be an over-estimate if tails have been
634##  added  and  the  necessary  consistency  checks,  relation   collections,
635##  exponent law checks and redundant generator eliminations  have  not  been
636##  done for a class.) All output that would  have  appeared  at  `InfoANUPQ'
637##  levels 1 or 2 if user-initiated is `Info'-ed at `InfoANUPQ' level 3.  The
638##  menu and output level are reset to their original values (if changed)  on
639##  leaving.
640##
641InstallGlobalFunction( PQ_DATA, function( datarec )
642local menu, lev, ngen, i, line, class;
643  if not( IsBound(datarec.haspcp) and datarec.haspcp ) then
644    Error( "a pc presentation for the group of the process ",
645           "has not yet been defined\n" );
646  fi;
647  PushOptions(rec(nonuser := true));
648  datarec.inPQ_DATA := true;
649  if datarec.menu[ Length(datarec.menu) ] <> 'Q' then
650    menu := datarec.menu;
651    PQ_MENU(datarec, "pQ");
652  fi;
653  if not IsBound(datarec.OutputLevel) then
654    lev := 0;
655    PQ_SET_OUTPUT_LEVEL( datarec, 3 );
656  elif datarec.OutputLevel < 3 then
657    lev := datarec.OutputLevel;
658    PQ_SET_OUTPUT_LEVEL( datarec, 3 );
659  fi;
660  datarec.matchlist := ["Group", "Class", " is defined on "];
661  datarec.matchedlines := [];
662  ToPQ(datarec, [ 4 ], [ "  #display presentation" ]);
663  datarec.matchedline := datarec.matchedlines[1];
664  PQ_SET_GRP_DATA(datarec);
665  for i in [2 .. Length(datarec.matchedlines)] do
666    line := SplitString(datarec.matchedlines[i], "", " \n");
667    if line[1] = "Class" then
668      class := Int( line[2] );
669      if class > 1 then
670        datarec.ngens[class - 1] := Int(ngen);
671        if class = datarec.class then
672          break;
673        fi;
674      fi;
675    else
676      ngen := line[1];
677    fi;
678  od;
679  if IsBound(menu) then
680    PQ_MENU(datarec, menu);
681  fi;
682  if IsBound(lev) then
683    PQ_SET_OUTPUT_LEVEL( datarec, lev );
684  fi;
685  PQ_UNBIND( datarec, ["matchlist", "matchedlines", "inPQ_DATA"] );
686  PopOptions();
687end );
688
689#############################################################################
690##
691#F  PQ_DATA_CHK( <args> ) . . .  call PQ_DATA if class/gen'r data out-of-date
692##
693##  determines the data record <datarec>, calls `PQ_DATA'  if  necessary  and
694##  returns <datarec>.
695##
696InstallGlobalFunction( PQ_DATA_CHK, function( args )
697local datarec;
698  datarec := CallFuncList(ANUPQDataRecord, args);
699  if not IsBound(datarec.ngens) or IsEmpty(datarec.ngens) or
700     not IsDenseList(datarec.ngens) then
701    PQ_DATA( datarec );
702  fi;
703  return datarec;
704end );
705
706#############################################################################
707##
708#F  PqFactoredOrder( <i> ) . the `pq' binary's current group's factored order
709#F  PqFactoredOrder()
710##
711##  for the <i>th or default interactive {\ANUPQ} process, return an estimate
712##  of the factored order of the lower exponent  $p$-class  quotient  of  the
713##  group currently determined by the process as a list `[<p>, <n> ]'.
714##
715##  *Note:* The order of each $p$-class quotient is taken as $p^n$ where  $n$
716##  is the number of generators for the class; this may be  an  over-estimate
717##  if tails have been added and the necessary consistency  checks,  relation
718##  collections, exponent law checks  and  redundant  generator  eliminations
719##  have not yet been done for a class.
720##
721InstallGlobalFunction( PqFactoredOrder, function( arg )
722  return PQ_DATA_CHK(arg).forder;
723end );
724
725#############################################################################
726##
727#F  PqOrder( <i> ) . . . .  the order of the current group of the `pq' binary
728#F  PqOrder()
729##
730##  for the <i>th or default interactive {\ANUPQ} process, return an estimate
731##  of the order of the  lower  exponent  $p$-class  quotient  of  the  group
732##  currently determined by the process.
733##
734##  *Note:* The order of each $p$-class quotient is taken as $p^n$ where  $n$
735##  is the number of generators for the class; this may be  an  over-estimate
736##  if tails have been added and the necessary consistency  checks,  relation
737##  collections, exponent law checks  and  redundant  generator  eliminations
738##  have not been done for a class.
739##
740InstallGlobalFunction( PqOrder, function( arg )
741local forder;
742  forder := CallFuncList( PqFactoredOrder, arg );
743  return forder[1]^forder[2];
744end );
745
746#############################################################################
747##
748#F  PqPClass( <i> ) . . . the p class of the current group of the `pq' binary
749#F  PqPClass()
750##
751##  for the <i>th or default interactive {\ANUPQ} process, return  the  lower
752##  exponent $p$-class of the quotient  group  currently  determined  by  the
753##  process.
754##
755InstallGlobalFunction( PqPClass, function( arg )
756  return PQ_DATA_CHK(arg).class;
757end );
758
759#############################################################################
760##
761#F  PqNrPcGenerators( <i> ) . number of pc gen'rs of `pq' binary's current gp
762#F  PqNrPcGenerators()
763##
764##  for the <i>th or default interactive {\ANUPQ} process, return the  number
765##  of pc generators of the lower exponent $p$-class quotient  of  the  group
766##  currently determined by the process.
767##
768InstallGlobalFunction( PqNrPcGenerators, function( arg )
769  return PQ_DATA_CHK(arg).forder[2];
770end );
771
772#############################################################################
773##
774#F  PqWeight( <i>, <j> ) . . . . . . . . . . . . . . .  weight of a generator
775#F  PqWeight( <j> )
776##
777##  for the <i>th or default interactive {\ANUPQ} process, return the  weight
778##  of the <j>th pc generator of the lower exponent $p$-class quotient of the
779##  group currently determined by the process, or `fail' if there is no  such
780##  numbered pc generator.
781##
782InstallGlobalFunction( PqWeight, function( arg )
783local ngens, i, j;
784  if not Length(arg) in [1, 2] then
785    Error( "expected 1 or 2 arguments\n" );
786  fi;
787  j := arg[ Length(arg) ];
788  if not IsPosInt(j) then
789    Error( "argument <j> should be a positive integer\n" );
790  fi;
791  Unbind( arg[ Length(arg) ] );
792  ngens := PQ_DATA_CHK(arg).ngens;
793  return First([1 .. Length(ngens)], i -> ngens[i] >= j);
794end );
795
796#############################################################################
797##
798#F  PqCurrentGroup( <i> ) . extracts current p-quotient or p-cover as a pc gp
799#F  PqCurrentGroup()
800##
801##  for the <i>th or default interactive {\ANUPQ} process, return  the  lower
802##  exponent $p$-class quotient of the group or $p$-covering group  currently
803##  determined by the process as a {\GAP} pc group.
804##
805InstallGlobalFunction( PqCurrentGroup, function( arg )
806local datarec, out;
807  datarec := PQ_DATA_CHK(arg);
808  datarec.outfname := ANUPQData.outfile;
809  PushOptions( rec(nonuser := true) );
810  PQ_WRITE_PC_PRESENTATION(datarec, datarec.outfname);
811  PopOptions();
812  if IsBound(datarec.pcoverclass) and datarec.pcoverclass = datarec.class then
813    out := "pCover";
814  else
815    out := "pQuotient";
816  fi;
817  PQ_GROUP_FROM_PCP( datarec, out );
818  return datarec.(out);
819end );
820
821#############################################################################
822##
823#F  PqDisplayPcPresentation( <i> ) . . . .  user version of any menu option 4
824#F  PqDisplayPcPresentation()
825##
826##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
827##  binary to display the pc presentation of  the  lower  exponent  $p$-class
828##  quotient of the group currently determined by the process.
829##
830##  Except if the last command communicating  with  the  `pq'  binary  was  a
831##  $p$-group generation command (for which there is only  a  verbose  output
832##  level), to set the amount of information this command  displays  you  may
833##  wish  to  call  `PqSetOutputLevel'  first  (see~"PqSetOutputLevel"),   or
834##  equivalently pass the option `OutputLevel' (see~"option OutputLevel").
835##
836##  *Note:*
837##  For  those  familiar  with  the  `pq'  binary,  `PqDisplayPcPresentation'
838##  performs menu item 4 of the current menu of the `pq' binary.
839##
840InstallGlobalFunction( PqDisplayPcPresentation, function( arg )
841local datarec;
842  datarec := CallFuncList(ANUPQDataRecord, arg);
843  PQ_GRP_EXISTS_CHK( datarec );
844  PQ_DISPLAY_PRESENTATION( datarec );
845end );
846
847#############################################################################
848##
849#F  PQ_SET_OUTPUT_LEVEL(<datarec>, <lev>) . . . .  p-Q/SP/A p-Q menu option 5
850##
851##  inputs data to the `pq' binary to set the print level  to  <lev>  in  the
852##  current menu or the ``basic'' $p$-Quotient menu if the current menu is  a
853##  $p$-Group generation menu.
854##
855InstallGlobalFunction( PQ_SET_OUTPUT_LEVEL, function( datarec, lev )
856  if datarec.menu[ Length(datarec.menu) ] = 'G' then
857    PQ_MENU(datarec, "pQ");
858  fi;
859  ToPQ(datarec, [ 5 ], [ "  #set output level" ]);
860  ToPQ(datarec, [ lev ], [ "  #output level" ]);
861  datarec.OutputLevel := lev;
862end );
863
864#############################################################################
865##
866#F  PqSetOutputLevel( <i>, <lev> ) .  user version of p-Q/SP/A p-Q menu opt 5
867#F  PqSetOutputLevel( <lev> )
868##
869##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
870##  binary to set the output level of the `pq' binary to <lev>.
871##
872##  *Note:* For those  familiar  with  the  `pq'  binary,  `PqSetOutputLevel'
873##  performs menu item 5 of the main (or advanced) $p$-Quotient menu, or  the
874##  Standard Presentation menu.
875##
876InstallGlobalFunction( PqSetOutputLevel, function( arg )
877local datarec, lev;
878  if not(Length(arg) in [1, 2]) then
879    Error( "1 or 2 arguments expected\n");
880  fi;
881  lev := arg[Length(arg)];
882  if not(lev in [0..3]) then
883    Error( "argument <lev> should be an integer in [0 .. 3]\n" );
884  fi;
885  datarec := CallFuncList(ANUPQDataRecord, arg{[1..Length(arg) - 1]});
886  PQ_SET_OUTPUT_LEVEL( datarec, lev);
887end );
888
889#############################################################################
890##
891#F  PQ_NEXT_CLASS( <datarec> ) . . . . . . . . . . . . . .  p-Q menu option 6
892##
893##  directs the `pq' binary to calculate the next class of `<datarec>.group',
894##  using option 6 of the main $p$-Quotient menu.
895##
896#T  Another possibility for checking for whether a queue factor is needed
897#T  is to test for `<datarec>.hasAuts'.
898##
899InstallGlobalFunction( PQ_NEXT_CLASS, function( datarec )
900local line;
901  PQ_MENU(datarec, "pQ");
902  PQ_UNBIND(datarec, ["pQuotient", "pQepi", "pCover"]);
903  if VALUE_PQ_OPTION("Identities", [], datarec) <> [] then
904    if datarec.class >= 1 then
905      datarec.prevngens := datarec.ngens[ datarec.class ];
906    fi;
907    PQ_P_COVER(datarec);
908    PQ_FINISH_NEXT_CLASS(datarec);
909  else
910    datarec.match := true;
911    ToPQ(datarec, [ 6 ], [ "  #calculate next class" ]);
912    if IsMatchingSublist(datarec.line, "Input queue factor:") then
913      ToPQ(datarec, [ VALUE_PQ_OPTION("QueueFactor", 15) ],
914                    [ " #queue factor"]);
915    fi;
916    PQ_SET_GRP_DATA(datarec);
917  fi;
918end );
919
920#############################################################################
921##
922#F  PqNextClass( <i> [: <option>]) . . . .  user version of p-Q menu option 6
923#F  PqNextClass( [: <option>])
924##
925##  for the <i>th or default interactive {\ANUPQ} process, direct the `pq' to
926##  calculate the next class of `ANUPQData.io[<i>].group'.
927##
928##  \atindex{option QueueFactor}{@option \noexpand`QueueFactor'}
929##  `PqNextClass'  accepts  the  option   `QueueFactor'   (see   also~"option
930##  QueueFactor") which should be a positive integer  if  automorphisms  have
931##  been previously supplied. If the `pq' binary requires a queue factor  and
932##  none is supplied via the option `QueueFactor' a default of 15 is taken.
933##
934##  *Notes*
935##
936##  The single command: `PqNextClass(<i>);' is equivalent to executing
937##
938##  \){\kernttindent}PqSetupTablesForNextClass(<i>);
939##  \){\kernttindent}PqTails(<i>, 0);
940##  \){\kernttindent}PqDoConsistencyChecks(<i>, 0, 0);
941##  \){\kernttindent}PqCollectDefiningRelations(<i>);
942##  \){\kernttindent}PqDoExponentChecks(<i>);
943##  \){\kernttindent}PqEliminateRedundantGenerators(<i>);
944##
945##  For those familiar with the `pq' binary, `PqNextClass' performs menu item
946##  6 of the main $p$-Quotient menu.
947##
948InstallGlobalFunction( PqNextClass, function( arg )
949local datarec;
950  PQ_OTHER_OPTS_CHK("PqNextClass", true);
951  datarec := CallFuncList(ANUPQDataRecord, arg);
952  PQ_GRP_EXISTS_CHK( datarec );
953  PQ_NEXT_CLASS( datarec );
954end );
955
956#############################################################################
957##
958#F  PQ_P_COVER( <datarec> ) . . . . . . . . . . . . . . . . p-Q menu option 7
959##
960##  directs  the  `pq'  binary  to  compute   the   $p$-covering   group   of
961##  `<datarec>.group', using option 7 of the main $p$-Quotient menu.
962##
963InstallGlobalFunction( PQ_P_COVER, function( datarec )
964local savefile;
965  PQ_MENU(datarec, "pQ");
966  Unbind( datarec.pCover );
967  datarec.match := true;
968  ToPQ(datarec, [ 7 ], [ "  #compute p-cover" ]);
969  PQ_SET_GRP_DATA(datarec);
970  datarec.pcoverclass := datarec.class;
971  Unbind(datarec.capable);
972end );
973
974#############################################################################
975##
976#F  PqComputePCover( <i> ) . . . . . . . .  user version of p-Q menu option 7
977#F  PqComputePCover()
978##
979##  for the <i>th or default interactive {\ANUPQ} process, direct the `pq' to
980##  compute the $p$-covering group of `ANUPQData.io[<i>].group'.
981##
982##  *Notes*
983##
984##  The single command: `PqComputePCover(<i>);' is equivalent to executing
985##
986##  \){\kernttindent}PqSetupTablesForNextClass(<i>);
987##  \){\kernttindent}PqTails(<i>, 0);
988##  \){\kernttindent}PqDoConsistencyChecks(<i>, 0, 0);
989##  \){\kernttindent}PqEliminateRedundantGenerators(<i>);
990##
991##  For those familiar with the `pq' binary, `PqComputePCover' performs  menu
992##  item 7 of the main $p$-Quotient menu.
993##
994InstallGlobalFunction( PqComputePCover, function( arg )
995local datarec;
996  datarec := CallFuncList(ANUPQDataRecord, arg);
997  PQ_GRP_EXISTS_CHK( datarec );
998  PQ_P_COVER( datarec );
999end );
1000
1001#############################################################################
1002##
1003#F  PQ_EVALUATE_IDENTITIES(<datarec>) . evaluate Identities option identities
1004##
1005InstallGlobalFunction( PQ_EVALUATE_IDENTITIES, function( datarec )
1006local identity, procId;
1007  procId := datarec.procId;
1008  for identity in VALUE_PQ_OPTION("Identities", [], datarec) do
1009    PQ_EVALUATE_IDENTITY(procId, identity);
1010  od;
1011  PQ_ELIMINATE_REDUNDANT_GENERATORS( datarec );
1012  Info(InfoANUPQ, 1, "Class ", datarec.class, " with ",
1013                     PqNrPcGenerators(procId), " generators." );
1014end );
1015
1016#############################################################################
1017##
1018#F  PqEvaluateIdentities( <i> ) . . . . evaluate Identities option identities
1019#F  PqEvaluateIdentities()
1020##
1021##  for the  <i>th  or  default  interactive  {\ANUPQ}  process,  invoke  the
1022##  evaluation  of  identities  defined  by  the  `Identities'  option,   and
1023##  eliminate any redundant pc generators formed. Since a previous  value  of
1024##  `Identities'  is  saved  in  the  data  record  of  the  process,  it  is
1025##  unnecessary to pass the `Identities' if set previously.
1026##
1027##  *Note:* This function is mainly implemented at the {\GAP} level. It  does
1028##  not correspond to a menu item of the `pq' program.
1029##
1030InstallGlobalFunction( PqEvaluateIdentities, function( arg )
1031  PQ_OTHER_OPTS_CHK("PqEvaluateIdentities", true);
1032  PQ_EVALUATE_IDENTITIES( CallFuncList(ANUPQDataRecord, arg) );
1033end );
1034
1035#############################################################################
1036##
1037#F  PQ_FINISH_NEXT_CLASS( <datarec> ) . . .  take the p-cover to a next class
1038##
1039##  does the usual operations required after calculating the  <p>-cover  that
1040##  brings the pcp back to a next class, except that it  also  slips  in  the
1041##  evaluation of the identities of the `Identities' option.
1042##
1043InstallGlobalFunction( PQ_FINISH_NEXT_CLASS, function( datarec )
1044  PushOptions( rec(nonuser := true) );
1045  PQ_COLLECT_DEFINING_RELATIONS( datarec );
1046  PQ_DO_EXPONENT_CHECKS( datarec, [1, datarec.class] );
1047  PQ_EVALUATE_IDENTITIES( datarec );
1048  PopOptions();
1049end );
1050
1051#############################################################################
1052##
1053#F  PQ_COLLECT( <datarec>, <word> ) . . . . . . . . . . . A p-Q menu option 1
1054##
1055##  instructs the  `pq'  binary  to  do  a  collection  on  <word>  a  string
1056##  representing a word in the  current  pc  generators,  e.g.  `"x3*x2*x1"',
1057##  using option 1 of the interactive $p$-Quotient menu.
1058##
1059InstallGlobalFunction( PQ_COLLECT, function( datarec, word )
1060
1061  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1062  ToPQ(datarec, [ 1 ], [ "  #do individual collection" ]);
1063  datarec.match := "The result of collection is";
1064  ToPQ(datarec, [ word, ";"], [ "  #word to be collected" ]);
1065  return PQ_WORD(datarec);
1066end );
1067
1068#############################################################################
1069##
1070#F  PQ_CHECK_WORD( <datarec>, <wordOrList>, <ngens> ) . .  check word or list
1071##
1072##  checks that <wordOrList> is a valid word in  the  current  pc  generators
1073##  (<ngens> is the number of current pc  generators)  or  a  valid  list  of
1074##  generator number-exponent pairs that  will  generate  such  a  word,  and
1075##  either emits an error or returns the valid word.
1076##
1077InstallGlobalFunction( PQ_CHECK_WORD, function( datarec, wordOrList, ngens )
1078local parts, gens;
1079  if not IsList(wordOrList) or
1080     not IsString(wordOrList) and
1081     not ForAll(wordOrList, pair -> IsList(pair) and 2 = Length(pair) and
1082                                    ForAll(pair, IsInt) ) then
1083    Error( "argument <wordOrList> should be a string e.g. \"x3*x2^2*x1\",\n",
1084           "or a list of gen'r no.-exponent pairs from which such a word ",
1085           "may be generated\n" );
1086  fi;
1087  if IsString(wordOrList) then
1088    #check word makes sense
1089    PqParseWord(ngens, wordOrList);
1090
1091  elif IsList(wordOrList) then
1092    if not ForAll(wordOrList,
1093                  pair -> IsPosInt(pair[1]) and pair[1] <= ngens) then
1094      Error( "generator numbers in argument <wordOrList> must be in the ",
1095             "range: ", "[1 .. ", ngens, "]\n" );
1096    fi;
1097    wordOrList := JoinStringsWithSeparator(
1098                      List( wordOrList,
1099                            pair -> Concatenation( "x", String(pair[1]),
1100                                                   "^", String(pair[2]) ) ),
1101                      "*" );
1102  fi;
1103  if IsEmpty(wordOrList) then
1104    wordOrList := "x1^0";
1105  fi;
1106  return wordOrList;
1107end );
1108
1109#############################################################################
1110##
1111#F  PQ_WORD( <datarec> ) . . . .  parse pq output for a word in pc generators
1112##
1113##  parses `<datarec>.matchedline' for a word in the  current  pc  generators
1114##  and returns it as a list of gen'r no.-exponent  pairs;  `<datarec>.match'
1115##  must have previously been set.
1116##
1117InstallGlobalFunction( PQ_WORD, function( datarec )
1118local word;
1119  word := SplitString( datarec.matchedline{[Length(datarec.match) + 1 ..
1120                                            Length(datarec.matchedline)]},
1121                       "", " \n" );
1122  if word = [ "IDENTITY" ] then
1123    word := [];
1124  else
1125    word := List( word,
1126                  function(syl)
1127                    syl := List( SplitString(syl, "", ".^"), Int );
1128                    if 1 = Length(syl) then
1129                      Add(syl, 1);
1130                    fi;
1131                    return syl;
1132                  end );
1133  fi;
1134  PQ_UNBIND(datarec, ["match", "matchedline"]);
1135  return word;
1136end );
1137
1138#############################################################################
1139##
1140#F  PQ_CHK_COLLECT_COMMAND_ARGS( <args> ) . . check args for a collect cmd ok
1141##
1142##  returns a list of valid arguments for  a  low-level  collect  command  or
1143##  generates an error.
1144##
1145InstallGlobalFunction( PQ_CHK_COLLECT_COMMAND_ARGS, function( args )
1146local datarec, wordOrList, ngens;
1147  if IsEmpty(args) or 2 < Length(args) then
1148    Error( "1 or 2 arguments expected\n");
1149  fi;
1150  wordOrList := args[Length(args)];
1151  datarec := CallFuncList(ANUPQDataRecord, args{[1..Length(args) - 1]});
1152  ngens := datarec.ngens[ Length(datarec.ngens) ];
1153  wordOrList := PQ_CHECK_WORD(datarec, wordOrList, ngens);
1154  return [datarec, wordOrList];
1155end );
1156
1157#############################################################################
1158##
1159#F  PqCollect( <i>, <word> ) . . . . . .  user version of A p-Q menu option 1
1160#F  PqCollect( <word> )
1161##
1162##  for the <i>th or default interactive {\ANUPQ} process, instruct the  `pq'
1163##  program to do a collection on <word>, a word in the current pc generators
1164##  (the form of <word> required is described below). `PqCollect' returns the
1165##  resulting word of the collection as a list of generator number,  exponent
1166##  pairs (the same form as the second allowed  input  form  of  <word>;  see
1167##  below).
1168##
1169##  The argument <word> may be input in either of the following ways:
1170##
1171##  \beginlist%ordered
1172##
1173##  \item{1.}
1174##  <word> may be a string, where the <i>th pc generator  is  represented  by
1175##  `x<i>', e.g.~`"x3*x2^2*x1"'. This way is quite versatile  as  parentheses
1176##  and left-normed commutators -- using square brackets, in the same way  as
1177##  `PqGAPRelators' (see~"PqGAPRelators") -- are permitted; <word> is checked
1178##  for correct syntax via `PqParseWord' (see~"PqParseWord").
1179##
1180##  \item{2.}
1181##  Otherwise, <word> must be a list of generator number, exponent  pairs  of
1182##  integers, i.e.~ each pair represents a ``syllable'' so that  `[  [3,  1],
1183##  [2, 2], [1, 1] ]' represents the same word as that of the  example  given
1184##  for the first allowed form of <word>.
1185##
1186##  \endlist
1187##
1188##  *Note:* For those familiar with the  `pq'  program,  `PqCollect'  performs
1189##  menu item 1 of the Advanced $p$-Quotient menu.
1190##
1191InstallGlobalFunction( PqCollect, function( arg )
1192  return CallFuncList( PQ_COLLECT, PQ_CHK_COLLECT_COMMAND_ARGS(arg) );
1193end );
1194
1195#############################################################################
1196##
1197#F  PQ_SOLVE_EQUATION( <datarec>, <a>, <b> ) . . . . . .  A p-Q menu option 2
1198##
1199##  inputs data to the `pq' binary for option 2 of the Advanced  $p$-Quotient
1200##  menu, to solve $<a> * <x> = <b>$ for <x>.
1201##
1202InstallGlobalFunction( PQ_SOLVE_EQUATION, function( datarec, a, b )
1203  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1204  ToPQ(datarec, [ 2 ], [ "  #solve equation" ]);
1205  ToPQ(datarec, [ a, ";" ], [ "  #word a" ]);
1206  ToPQ(datarec, [ b, ";" ], [ "  #word b" ]);
1207end );
1208
1209#############################################################################
1210##
1211#F  PqSolveEquation( <i>, <a>, <b> ) . .  user version of A p-Q menu option 2
1212#F  PqSolveEquation( <a>, <b> )
1213##
1214##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1215##  binary to solve $<a> * <x> = <b>$ for <x>.
1216##
1217##  *Note:*
1218##  For those familiar  with  the  `pq'  binary,  `PqSolveEquation'  performs
1219##  menu item 2 of the Advanced $p$-Quotient menu.
1220##
1221InstallGlobalFunction( PqSolveEquation, function( arg )
1222local len, datarec;
1223  len := Length(arg);
1224  if not(len in [2,3]) then
1225    Error("expected 2 or 3 arguments\n");
1226  fi;
1227  #@need to add argument checking for a and b@
1228  datarec := CallFuncList(ANUPQDataRecord, arg{[1 .. len - 2]});
1229  PQ_SOLVE_EQUATION( datarec, arg[len - 1], arg[len] );
1230end );
1231
1232#############################################################################
1233##
1234#F  PQ_COMMUTATOR( <datarec>, <words>, <pow>, <item> ) . A p-Q menu opts 3/24
1235##
1236##  inputs data to the `pq' binary  for  option  3  or  24  of  the  Advanced
1237##  $p$-Quotient menu, to compute the left  normed  commutator  of  the  list
1238##  <words> of words in the generators raised to  the  integer  power  <pow>,
1239##  where <item> is `"3 #commutator"' for option 3  or  `"24  #commutator  of
1240##  defining genrs"' for option 24.
1241##
1242InstallGlobalFunction( PQ_COMMUTATOR, function( datarec, words, pow, item )
1243local i;
1244  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1245  ToPQ(datarec, item[1], item[2]);
1246  ToPQ(datarec, [ Length(words) ], [ "  #no. of components" ]);
1247  for i in [1..Length(words)] do
1248    ToPQ(datarec, [ words[i], ";" ], [ "  #word ", i ]);
1249  od;
1250  datarec.match := "The commutator is";
1251  ToPQ(datarec, [ pow ], [ "  #power" ]);
1252  return PQ_WORD(datarec);
1253end );
1254
1255#############################################################################
1256##
1257#F  PQ_COMMUTATOR_CHK_ARGS( <args> ) . . . . check args for commutator cmd ok
1258##
1259##  returns a list of valid arguments for a low-level commutator  command  or
1260##  generates an error.
1261##
1262InstallGlobalFunction( PQ_COMMUTATOR_CHK_ARGS, function( args )
1263local len, words, pow, item, datarec, ngens;
1264  len := Length(args);
1265  if not(len in [3, 4]) then
1266    Error("expected 3 or 4 arguments\n");
1267  fi;
1268  words := args[len - 2];
1269  pow   := args[len - 1];
1270  item  := args[len];
1271  if not IsPosInt(pow) then
1272    Error( "argument <pow> must be a positive integer\n" );
1273  fi;
1274  datarec := CallFuncList(ANUPQDataRecord, args{[1 .. len - 3]});
1275  if item[1][1] = 3 then
1276    ngens := datarec.ngens[ Length(datarec.ngens) ];
1277  else
1278    ngens := datarec.ngens[ 1 ];
1279  fi;
1280  words := List( words, w -> PQ_CHECK_WORD(datarec, w, ngens) );
1281  return [datarec, words, pow, item];
1282end );
1283
1284#############################################################################
1285##
1286#F  PqCommutator( <i>, <words>, <pow> ) . user version of A p-Q menu option 3
1287#F  PqCommutator( <words>, <pow> )
1288##
1289##  for  the  <i>th  or  default  interactive  {\ANUPQ}  process,  compute  a
1290##  user-defined commutator in the pc generators of  the  class  1  quotient,
1291##  i.e.~the pc generators that correspond to the original fp or pc group  of
1292##  the process, and return  the  result  as  a  list  of  generator  number,
1293##  exponent pairs. The form required for each word of <words> is the same as
1294##  that required for the <word> argument of  `PqCollect'  (see~"PqCollect").
1295##  The form of  the  output  word  is  also  the  same  as  for  `PqCollect'
1296##  (see~"PqCollect").
1297##
1298##  *Notes*
1299##
1300##  It is illegal for any word of <words> to contain pc generators of  weight
1301##  larger      than      1.      Except      for      this      distinction,
1302##  `PqCommutatorDefiningGenerators'   works   just    like    `PqCommutator'
1303##  (see~"PqCommutator").
1304##
1305##  For those familiar with the `pq' program, `PqCommutatorDefiningGenerators'
1306##  performs menu item 24 of the Advanced $p$-Quotient menu.
1307##
1308InstallGlobalFunction( PqCommutator, function( arg )
1309  return CallFuncList( PQ_COMMUTATOR,
1310                       PQ_COMMUTATOR_CHK_ARGS(
1311                           Concatenation( arg, [[[3], ["  #commutator"]]] ) ) );
1312end );
1313
1314#############################################################################
1315##
1316#F  PQ_SETUP_TABLES_FOR_NEXT_CLASS( <datarec> ) . . . . . A p-Q menu option 6
1317##
1318##  inputs data to the `pq' binary for option 6 of the Advanced  $p$-Quotient
1319##  menu to set up tables for next class.
1320##
1321InstallGlobalFunction( PQ_SETUP_TABLES_FOR_NEXT_CLASS, function( datarec )
1322  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1323  ToPQ(datarec, [ 6 ], [ "  #set up tables for next class" ]);
1324  datarec.match := true;
1325  PQ_SET_GRP_DATA(datarec); #Just to be sure it's up-to-date
1326  datarec.setupclass := datarec.class;
1327end );
1328
1329#############################################################################
1330##
1331#F  PqSetupTablesForNextClass( <i> ) . .  user version of A p-Q menu option 6
1332#F  PqSetupTablesForNextClass()
1333##
1334##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1335##  binary  to  set  up  tables  for  the  next  class.  As  as  side-effect,
1336##  after   `PqSetupTablesForNextClass(<i>)'   the    value    returned    by
1337##  `PqPClass(<i>)' will be one more than it was previously.
1338##
1339##  *Note:*
1340##  For those familiar  with  the  `pq'  binary,  `PqSetupTablesForNextClass'
1341##  performs menu item 6 of the Advanced $p$-Quotient menu.
1342##
1343InstallGlobalFunction( PqSetupTablesForNextClass, function( arg )
1344local datarec;
1345  datarec := CallFuncList(ANUPQDataRecord, arg);
1346  PQ_SETUP_TABLES_FOR_NEXT_CLASS( datarec );
1347end );
1348
1349#############################################################################
1350##
1351#F  PQ_INSERT_TAILS( <datarec>, <weight>, <which> )  . .  A p-Q menu option 7
1352##
1353##  inputs data to the `pq' binary for option 7 of the Advanced  $p$-Quotient
1354##  menu, to add and/or compute tails.
1355##
1356InstallGlobalFunction( PQ_INSERT_TAILS, function( datarec, weight, which )
1357local intwhich;
1358  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1359  intwhich := Position( [ "compute and add", "add", "compute" ], which ) - 1;
1360  ToPQ(datarec, [ 7 ], [ "  #", which, " tails" ]);
1361  ToPQ(datarec, [ weight ], [ " #weight of tails" ]);
1362  ToPQ(datarec, [ intwhich ], [ "  #", which ]);
1363  if intwhich <= 1 then
1364    datarec.match := true;
1365    PQ_SET_GRP_DATA(datarec);
1366  fi;
1367end );
1368
1369#############################################################################
1370##
1371#F  PQ_CHK_TAILS_ARGS( <args> ) . . . . .  check args for insert tails cmd ok
1372##
1373InstallGlobalFunction( PQ_CHK_TAILS_ARGS, function( args )
1374local weight, datarec;
1375  if IsEmpty(args) or 2 < Length(args) then
1376    Error( "1 or 2 arguments expected\n");
1377  fi;
1378  weight := args[Length(args)];
1379  datarec := CallFuncList(ANUPQDataRecord, args{[1 .. Length(args) - 1]});
1380  if not IsBound(datarec.setupclass) or datarec.class <> datarec.setupclass then
1381    Error( "tables to start next class have not been set up.\n",
1382           "Please call `PqSetupTablesForNextClass' first\n" );
1383  fi;
1384  if not(weight = 0 or weight in [2 .. datarec.class]) then
1385    Error( "argument <weight> should be an integer in [0] U [2 .. <class>],\n",
1386           "where <class> is the current class (", datarec.class, ")\n" );
1387  fi;
1388  return datarec;
1389end );
1390
1391#############################################################################
1392##
1393#F  PqAddTails( <i>, <weight> ) . . . .  adds tails using A p-Q menu option 7
1394#F  PqAddTails( <weight> )
1395##
1396##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1397##  binary to add tails of weight <weight> if  <weight>  is  in  the  integer
1398##  range `[2 .. PqPClass(<i>)]' (assuming <i> is the number of the  process)
1399##  or for all weights if `<weight> = 0'. See `PqTails' ("PqTails") for  more
1400##  details.
1401##
1402##  *Note:*
1403##  For those familiar with the `pq' binary, `PqAddTails' uses menu item 7 of
1404##  the Advanced $p$-Quotient menu.
1405##
1406InstallGlobalFunction( PqAddTails, function( arg )
1407  PQ_INSERT_TAILS( PQ_CHK_TAILS_ARGS(arg), arg[Length(arg)], "add" );
1408end );
1409
1410#############################################################################
1411##
1412#F  PqComputeTails( <i>, <weight> ) . . computes tails using A p-Q menu opt 7
1413#F  PqComputeTails( <weight> )
1414##
1415##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1416##  binary to compute tails of weight <weight> if <weight> is in the  integer
1417##  range `[2 .. PqPClass(<i>)]' (assuming <i> is the number of the  process)
1418##  or for all weights if `<weight> = 0'. See `PqTails' ("PqTails") for  more
1419##  details.
1420##
1421##  *Note:*
1422##  For those familiar with the `pq' binary, `PqComputeTails' uses menu  item
1423##  7 of the Advanced $p$-Quotient menu.
1424##
1425InstallGlobalFunction( PqComputeTails, function( arg )
1426  PQ_INSERT_TAILS( PQ_CHK_TAILS_ARGS(arg), arg[Length(arg)], "compute" );
1427end );
1428
1429#############################################################################
1430##
1431#F  PqTails( <i>, <weight> ) . computes and adds tails using A p-Q menu opt 7
1432#F  PqTails( <weight> )
1433##
1434##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1435##  binary to compute and add tails of weight <weight> if <weight> is in  the
1436##  integer range `[2 .. PqPClass(<i>)]' (assuming <i> is the number  of  the
1437##  process) or for all weights if `<weight> = 0'.
1438##
1439##  If <weight> is non-zero, then tails that  introduce  new  generators  for
1440##  only weight <weight> are computed and added, and  in  this  case  and  if
1441##  `<weight> \< PqPClass(<i>)', it is assumed that the tails that  introduce
1442##  new  generators  for  each  weight  from  `PqPClass(<i>)'  downto  weight
1443##  `<weight>  +  1'  have  already  been  added.  You  may  wish   to   call
1444##  `PqSetMetabelian' (see~"PqSetMetabelian") prior to calling `PqTails'.
1445##
1446##  *Notes*
1447##
1448##  For its use in the context of finding the next class  see  "PqNextClass";
1449##  in     particular,     a     call     to      `PqSetupTablesForNextClass'
1450##  (see~"PqSetupTablesForNextClass")  needs  to  have  been  made  prior  to
1451##  calling `PqTails'.
1452##
1453##  The single command: `PqTails(<i>, <weight>);' is equivalent to
1454##
1455##  \){\kernttindent}PqComputeTails(<i>, <weight>);
1456##  \){\kernttindent}PqAddTails(<i>, <weight>);
1457##
1458##  For those familiar with the `pq' binary, `PqTails' uses menu  item  7  of
1459##  the Advanced $p$-Quotient menu.
1460##
1461InstallGlobalFunction( PqTails, function( arg )
1462  PQ_INSERT_TAILS(PQ_CHK_TAILS_ARGS(arg), arg[Length(arg)], "compute and add");
1463end );
1464
1465#############################################################################
1466##
1467#F  PQ_DO_CONSISTENCY_CHECKS(<datarec>, <weight>, <type>) .  A p-Q menu opt 8
1468##
1469##  inputs data to the `pq' binary for option 8 of the Advanced  $p$-Quotient
1470##  menu, to do consistency checks.
1471##
1472InstallGlobalFunction( PQ_DO_CONSISTENCY_CHECKS,
1473function( datarec, weight, type )
1474  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1475  ToPQ(datarec, [ 8 ], [ "  #check consistency" ]);
1476  ToPQ(datarec, [ weight ], [ " #weight to be checked" ]);
1477  ToPQ(datarec, [ type ], [ "  #type" ]);
1478end );
1479
1480#############################################################################
1481##
1482#F  PqDoConsistencyChecks(<i>,<weight>,<type>) . user ver of A p-Q menu opt 8
1483#F  PqDoConsistencyChecks( <weight>, <type> )
1484##
1485##  for the <i>th or default interactive  {\ANUPQ}  process,  do  consistency
1486##  checks for weight <weight> if <weight> is in the  integer  range  `[3  ..
1487##  PqPClass(<i>)]' (assuming <i> is the number of the process)  or  for  all
1488##  weights if `<weight> = 0', and for type <type> if <type> is in the  range
1489##  `[1, 2, 3]' (see below) or for all types if `<type> = 0'. (For its use in
1490##  the context of finding the next class see "PqNextClass".)
1491##
1492##  The  *type*   of   a   consistency   check   is   defined   as   follows.
1493##  `PqDoConsistencyChecks(<i>, <weight>, <type>)' for  <weight>  in  `[3  ..
1494##  PqPClass(<i>)]' and the given  value  of  <type>  invokes  the  following
1495##  `PqJacobi' checks (see~"PqDoConsistencyCheck"):
1496##
1497##  \beginitems
1498##
1499##  `<type> = 1':&
1500##  `PqJacobi(<i>, <a>, <a>, <a>)' checks for  pc  generators  of  index  <a>
1501##  satisfying `2 * PqWeight(<i>, <a>) + 1 = <weight>'.
1502##
1503##  `<type> = 2':&
1504##  `PqJacobi(<i>, <b>, <b>, <a>)' checks for pc generators of  indices  <b>,
1505##  <a> satisfying `<b> > <a>' and `PqWeight(<i>, <b>) + PqWeight(<i>, <a>) +
1506##  1 = <weight>'.
1507##
1508##  `<type> = 3':&
1509##  `PqJacobi(<i>, <c>, <b>, <a>)' checks for pc generators of  indices  <c>,
1510##  <b>, <a> satisfying `<c> > <b> > <a>' and the sum of the weights of these
1511##  generators equals <weight>.
1512##
1513##  \enditems
1514##
1515##  *Notes*
1516##
1517##  `PqWeight(<i>, <j>)' returns the weight of the <j>th  pc  generator,  for
1518##  process <i> (see~"PqWeight").
1519##
1520##  It is assumed that tails for the given weight (or weights)  have  already
1521##  been added (see~"PqTails").
1522##
1523##  For those familiar with the `pq' binary, `PqDoConsistencyChecks' performs
1524##  menu item 8 of the Advanced $p$-Quotient menu.
1525##
1526InstallGlobalFunction( PqDoConsistencyChecks, function( arg )
1527local len, datarec, weight, type;
1528  len := Length(arg);
1529  if not(len in [2, 3]) then
1530    Error("expected 2 or 3 arguments\n");
1531  fi;
1532  weight := arg[len - 1];
1533  type   := arg[len];
1534  arg := arg{[1 .. len - 2]};
1535  datarec := CallFuncList(ANUPQDataRecord, arg);
1536  if not IsBound(datarec.setupclass) or datarec.class <> datarec.setupclass then
1537    Error( "tables to start next class have not been set up.\n",
1538           "Please call `PqSetupTablesForNextClass' first\n" );
1539  fi;
1540  if not(weight = 0 or weight in [3 .. datarec.class]) then
1541    Error( "argument <weight> should be an integer in [0] U [3 .. <class>],\n",
1542           "where <class> is the current class (", datarec.class, ")\n" );
1543  fi;
1544  if not(type in [0..3]) then
1545    Error( "argument <type> should be in [0,1,2,3]\n" );
1546  fi;
1547  PQ_DO_CONSISTENCY_CHECKS( datarec, weight, type );
1548end );
1549
1550#############################################################################
1551##
1552#F  PQ_COLLECT_DEFINING_RELATIONS( <datarec> ) . . . . .  A p-Q menu option 9
1553##
1554##  inputs data to the `pq' binary for option 9 of the Advanced  $p$-Quotient
1555##  menu, to collect defining relations.
1556##
1557InstallGlobalFunction( PQ_COLLECT_DEFINING_RELATIONS, function( datarec )
1558  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1559  ToPQ(datarec, [ 9 ], [ "  #collect defining relations" ]);
1560end );
1561
1562#############################################################################
1563##
1564#F  PqCollectDefiningRelations( <i> ) . . user version of A p-Q menu option 9
1565#F  PqCollectDefiningRelations()
1566##
1567##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1568##  binary to collect the images of the defining relations of the original fp
1569##  group of the process, with respect to the current pc presentation, in the
1570##  context of finding the  next  class  (see~"PqNextClass").  If  the  tails
1571##  operation  is  not  complete  then  the  relations   may   be   evaluated
1572##  incorrectly.
1573##
1574##  *Note:*
1575##  For those familiar with  the  `pq'  binary,  `PqCollectDefiningRelations'
1576##  performs menu item 9 of the Advanced $p$-Quotient menu.
1577##
1578InstallGlobalFunction( PqCollectDefiningRelations, function( arg )
1579local datarec;
1580  datarec := CallFuncList(ANUPQDataRecord, arg);
1581  PQ_COLLECT_DEFINING_RELATIONS( datarec );
1582end );
1583
1584#############################################################################
1585##
1586#F  PQ_DO_EXPONENT_CHECKS( <datarec>, <bnds> ) . . . . . A p-Q menu option 10
1587##
1588##  inputs data to the `pq' binary to do exponent checks for weights  between
1589##  <bnds> inclusive, using option 10 of the Advanced $p$-Quotient menu.
1590##
1591InstallGlobalFunction( PQ_DO_EXPONENT_CHECKS, function( datarec, bnds )
1592  #@does default only at the moment@
1593  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1594  datarec.match := "Group is complete";
1595  ToPQ(datarec, [ 10 ], [ " #do exponent checks" ]);
1596  if IsBound(datarec.matchedline) and
1597     IsMatchingSublist(datarec.matchedline, "Group is complete") then
1598    PQ_UNBIND(datarec, ["match", "matchedline"]);
1599    datarec.complete := true;
1600    return;
1601  elif IsMatchingSublist(datarec.line, "Input exponent law") then
1602    ToPQ(datarec, [ VALUE_PQ_OPTION("Exponent", 0, datarec) ],
1603                  [ "  #exponent" ]);
1604  fi;
1605  ToPQ(datarec, [ bnds[1] ], [ " #start weight" ]);
1606  ToPQ(datarec, [ bnds[2] ], [ " #end weight"   ]);
1607  ToPQ(datarec, [ 1 ], [ "  #do default check" ]);
1608  Unbind(datarec.match);
1609end );
1610
1611#############################################################################
1612##
1613#F  PqDoExponentChecks(<i>[: Bounds := <list>]) . user ver A p-Q menu opt. 10
1614#F  PqDoExponentChecks([: Bounds := <list>])
1615##
1616##  for the <i>th or default interactive {\ANUPQ} process, direct  the  `pq'
1617##  binary to do exponent checks for weights (inclusively) between the bounds
1618##  of `Bounds' or for all weights if `Bounds' is not given. The value <list>
1619##  of `Bounds' (assuming the interactive process is numbered <i>) should  be
1620##  a list of  two  integers  <low>,  <high>  satisfying  $1  \le  <low>  \le
1621##  <high> \le `PqPClass(<i>)'$ (see~"PqPClass").
1622##
1623##  *Note:*
1624##  For those familiar with the `pq'  binary,  `PqDoExponentChecks'  performs
1625##  menu item 10 of the Advanced $p$-Quotient menu.
1626##
1627InstallGlobalFunction( PqDoExponentChecks, function( arg )
1628local datarec;
1629  PQ_OTHER_OPTS_CHK("PqDoExponentChecks", true);
1630  datarec := PQ_DATA_CHK(arg);
1631  PQ_DO_EXPONENT_CHECKS( datarec, PQ_BOUNDS(datarec, datarec.class) );
1632end );
1633
1634#############################################################################
1635##
1636#F  PQ_ELIMINATE_REDUNDANT_GENERATORS( <datarec> ) . . . A p-Q menu option 11
1637##
1638##  inputs data to the `pq' binary for option 11 of the Advanced $p$-Quotient
1639##  menu, to eliminate redundant generators.
1640##
1641InstallGlobalFunction( PQ_ELIMINATE_REDUNDANT_GENERATORS, function( datarec )
1642  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1643  ToPQ(datarec, [ 11 ], [ " #eliminate redundant generators" ]);
1644  datarec.match := true;
1645  PQ_SET_GRP_DATA(datarec);
1646end );
1647
1648#############################################################################
1649##
1650#F  PqEliminateRedundantGenerators( <i> ) .  user ver of A p-Q menu option 11
1651#F  PqEliminateRedundantGenerators()
1652##
1653##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1654##  binary to eliminate redundant generators of the current $p$-quotient.
1655##
1656##  *Note:*
1657##  For those familiar with the `pq' binary, `PqEliminateRedundantGenerators'
1658##  performs menu item 11 of the Advanced $p$-Quotient menu.
1659##
1660InstallGlobalFunction( PqEliminateRedundantGenerators, function( arg )
1661local datarec;
1662  datarec := CallFuncList(ANUPQDataRecord, arg);
1663  PQ_ELIMINATE_REDUNDANT_GENERATORS( datarec );
1664end );
1665
1666#############################################################################
1667##
1668#F  PQ_REVERT_TO_PREVIOUS_CLASS( <datarec> ) . . . . . . A p-Q menu option 12
1669##
1670##  inputs data to the `pq' binary for option 12 of the Advanced $p$-Quotient
1671##  menu, to abandon the current class and revert to the previous class.
1672##
1673InstallGlobalFunction( PQ_REVERT_TO_PREVIOUS_CLASS, function( datarec )
1674  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1675  ToPQ(datarec, [ 12 ], [ " #revert to previous class" ]);
1676  Unbind( datarec.ngens[ datarec.class ] );
1677  datarec.match := true;
1678  PQ_SET_GRP_DATA(datarec); #Just to be sure it's up-to-date
1679  datarec.setupclass := datarec.class - 1;
1680end );
1681
1682#############################################################################
1683##
1684#F  PqRevertToPreviousClass( <i> ) . . . user version of A p-Q menu option 12
1685#F  PqRevertToPreviousClass()
1686##
1687##  for the <i>th or default interactive {\ANUPQ} process, direct  the  `pq'
1688##  binary to abandon the current class and revert to the previous class.
1689##
1690##  *Note:*
1691##  For  those  familiar  with  the  `pq'  binary,  `PqRevertToPreviousClass'
1692##  performs menu item 12 of the Advanced $p$-Quotient menu.
1693##
1694InstallGlobalFunction( PqRevertToPreviousClass, function( arg )
1695local datarec;
1696  datarec := CallFuncList(ANUPQDataRecord, arg);
1697  PQ_REVERT_TO_PREVIOUS_CLASS( datarec );
1698end );
1699
1700#############################################################################
1701##
1702#F  PQ_SET_MAXIMAL_OCCURRENCES( <datarec>, <noccur> ) . .  A p-Q menu opt. 13
1703##
1704##  inputs data to the  `pq'  binary,  to  set  the  maximal  occurrences  of
1705##  generators of weight 1 in generator definitions, using option 13  of  the
1706##  Advanced $p$-Quotient menu.
1707##
1708InstallGlobalFunction( PQ_SET_MAXIMAL_OCCURRENCES, function( datarec, noccur )
1709  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1710  ToPQ(datarec, [ 13 ], [ " #set maximal occurrences" ]);
1711  ToPQ(datarec, [ JoinStringsWithSeparator( List(noccur, String), " " ) ],
1712                [ " #max occurrences of weight 1 gen'rs"]);
1713end );
1714
1715#############################################################################
1716##
1717#F  PqSetMaximalOccurrences( <i>, <noccur> ) . user ver of A p-Q menu opt. 13
1718#F  PqSetMaximalOccurrences( <noccur> )
1719##
1720##  for the <i>th or default interactive {\ANUPQ} process, directs  the  `pq'
1721##  binary to set maximal occurrences of  the  weight  1  generators  in  the
1722##  definitions of pcp generators of the group of the process; <noccur>  must
1723##  be a list of non-negative integers of  length  the  number  of  weight  1
1724##  generators (i.e.~the rank of the class 1 $p$-quotient of the group of the
1725##  process). An entry of `0' for a particular generator indicates that there
1726##  is no limit on the number of occurrences for the generator.
1727##
1728##  *Note:*
1729##  For  those  familiar  with  the  `pq'  binary,  `PqSetMaximalOccurrences'
1730##  performs menu item 13 of the Advanced $p$-Quotient menu.
1731##
1732InstallGlobalFunction( PqSetMaximalOccurrences, function( arg )
1733local len, noccur, datarec;
1734  len := Length(arg);
1735  if not(len in [1, 2]) then
1736    Error( "expected 1 or 2 arguments\n");
1737  fi;
1738  noccur := arg[len];
1739  if not IsList(noccur) or not ForAll(noccur, x -> IsInt(x) and x >= 0) then
1740    Error( "<noccur> argument must be a list of non-negative integers\n" );
1741  fi;
1742  arg := arg{[1 .. len - 1]};
1743  datarec := PQ_DATA_CHK(arg);
1744  if Length(noccur) <> datarec.ngens[1] then
1745    Error( "<noccur> argument must be a list of length equal to\n",
1746           "the no. of generators of weight 1 (",  datarec.ngens[1], ")\n" );
1747  fi;
1748  PQ_SET_MAXIMAL_OCCURRENCES( datarec, noccur );
1749end );
1750
1751#############################################################################
1752##
1753#F  PQ_SET_METABELIAN( <datarec> ) . . . . . . . . . . . A p-Q menu option 14
1754##
1755##  inputs data to the `pq' binary for option 14 of the Advanced $p$-Quotient
1756##  menu, to set the metabelian flag.
1757##
1758InstallGlobalFunction( PQ_SET_METABELIAN, function( datarec )
1759  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1760  ToPQ(datarec, [ 14 ], [ " #set metabelian" ]);
1761end );
1762
1763#############################################################################
1764##
1765#F  PqSetMetabelian( <i> ) . . . . . . . user version of A p-Q menu option 14
1766#F  PqSetMetabelian()
1767##
1768##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1769##  binary to enforce metabelian-ness.
1770##
1771##  *Note:*
1772##  For those familiar  with  the  `pq'  binary,  `PqSetMetabelian'  performs
1773##  menu item 14 of the Advanced $p$-Quotient menu.
1774##
1775InstallGlobalFunction( PqSetMetabelian, function( arg )
1776local datarec;
1777  datarec := CallFuncList(ANUPQDataRecord, arg);
1778  PQ_SET_METABELIAN( datarec );
1779end );
1780
1781#############################################################################
1782##
1783#F  PQ_DO_CONSISTENCY_CHECK( <datarec>, <c>, <b>, <a> ) . A p-Q menu option 15
1784##
1785##  inputs data to the `pq' binary for option 15 of the Advanced $p$-Quotient
1786##  menu, to do a consistency check.
1787##
1788InstallGlobalFunction( PQ_DO_CONSISTENCY_CHECK, function( datarec, c, b, a )
1789  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1790  ToPQ(datarec, [ 15 ], [ " #do individual consistency check" ]);
1791  ToPQ(datarec, [ c, " ", b, " ", a ], [ "  #generator indices"]);
1792end );
1793
1794#############################################################################
1795##
1796#F  PqDoConsistencyCheck(<i>, <c>, <b>, <a>) .  user ver of A p-Q menu opt 15
1797#F  PqDoConsistencyCheck( <c>, <b>, <a> )
1798#F  PqJacobi(<i>, <c>, <b>, <a>)
1799#F  PqJacobi( <c>, <b>, <a> )
1800##
1801##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1802##  binary to do the Jacobi consistency check  for  the  pc  generators  with
1803##  indices <c>, <b>, <a> which should be non-increasing  positive  integers,
1804##  i.e.~$<c>   \ge   <b>   \ge   <a>$.   For   further   explanation,    see
1805##  `PqDoConsistencyChecks' ("PqDoConsistencyChecks").
1806##
1807##  *Note:*
1808##  For those familiar  with  the  `pq'  binary,  `PqDoConsistencyCheck'  and
1809##  `PqJacobi' perform menu item 15 of the Advanced $p$-Quotient menu.
1810##
1811InstallGlobalFunction( PqDoConsistencyCheck, function( arg )
1812local len, c, b, a, datarec;
1813  len := Length(arg);
1814  if not(len in [3, 4]) then
1815    Error( "expected 3 or 4 arguments\n" );
1816  fi;
1817  c := arg[len - 2];
1818  b := arg[len - 1];
1819  a := arg[len];
1820  arg := arg{[1 .. len - 3]};
1821  datarec := CallFuncList(ANUPQDataRecord, arg);
1822  if not IsBound(datarec.setupclass) or datarec.class <> datarec.setupclass then
1823    Error( "tables to start next class have not been set up.\n",
1824           "Please call `PqSetupTablesForNextClass' first\n" );
1825  fi;
1826  if not ForAll([c, b, a], IsPosInt) or datarec.class < c or c < b or b < a then
1827    Error( "pc generator indices must be non-increasing ",
1828           "integers in [1 .. <class>],\n",
1829           "where <class> is the current class (", datarec.class, ")\n" );
1830  fi;
1831  PQ_DO_CONSISTENCY_CHECK( datarec, c, b, a );
1832end );
1833
1834#############################################################################
1835##
1836#F  PQ_COMPACT( <datarec> ) . . . . . . . . . . . . . .  A p-Q menu option 16
1837##
1838##  inputs data to the `pq' binary for option 16 of the Advanced $p$-Quotient
1839##  menu, to do a compaction.
1840##
1841InstallGlobalFunction( PQ_COMPACT, function( datarec )
1842  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1843  ToPQ(datarec, [ 16 ], [ " #compact" ]);
1844end );
1845
1846#############################################################################
1847##
1848#F  PqCompact( <i> ) . . . . . . . . . . user version of A p-Q menu option 16
1849#F  PqCompact()
1850##
1851##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1852##  binary to do a compaction.
1853##
1854##  *Note:*
1855##  For those familiar with the `pq' binary, `PqCompact' performs  menu  item
1856##  16 of the Advanced $p$-Quotient menu.
1857##
1858InstallGlobalFunction( PqCompact, function( arg )
1859local datarec;
1860  datarec := CallFuncList(ANUPQDataRecord, arg);
1861  PQ_COMPACT( datarec );
1862end );
1863
1864#############################################################################
1865##
1866#F  PQ_ECHELONISE( <datarec> ) . . . . . . . . . . . . . A p-Q menu option 17
1867##
1868##  inputs data to the `pq' binary for option 17 of the Advanced $p$-Quotient
1869##  menu, to echelonise.
1870##
1871InstallGlobalFunction( PQ_ECHELONISE, function( datarec )
1872local line, redgen;
1873  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1874  datarec.match := "Generator";
1875  ToPQ(datarec, [ 17 ], [ " #echelonise" ]);
1876  if IsBound(datarec.matchedline) and
1877     PositionSublist(datarec.matchedline, "redundant") <> fail then
1878    line := SplitString(datarec.matchedline, "", " \n");
1879    redgen := Int( line[2] );
1880  else
1881    redgen := fail;
1882  fi;
1883  PQ_UNBIND(datarec, ["match", "matchedline"]);
1884  return redgen;
1885end );
1886
1887#############################################################################
1888##
1889#F  PqEchelonise( <i> ) . . . . . . . .  user version of A p-Q menu option 17
1890#F  PqEchelonise()
1891##
1892##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1893##  program to echelonise the word most recently collected by `PqCollect'  or
1894##  `PqCommutator' against the relations of the current pc presentation,  and
1895##  return the number of  the  generator  made  redundant  or  `fail'  if  no
1896##  generator was made redundant. A call to `PqCollect' (see~"PqCollect")  or
1897##  `PqCommutator' (see~"PqCommutator") needs to be performed prior to  using
1898##  this command.
1899##
1900##  *Note:*
1901##  For those familiar with the `pq'  binary,  `PqEchelonise'  performs  menu
1902##  item 17 of the Advanced $p$-Quotient menu.
1903##
1904InstallGlobalFunction( PqEchelonise, function( arg )
1905local datarec;
1906  datarec := CallFuncList(ANUPQDataRecord, arg);
1907  return PQ_ECHELONISE( datarec );
1908end );
1909
1910#############################################################################
1911##
1912#F  PQ_SUPPLY_OR_EXTEND_AUTOMORPHISMS(<datarec>[,<mlist>])  A p-Q menu opt 18
1913##
1914##  inputs data to the `pq' binary for option 18 of the Advanced $p$-Quotient
1915##  menu.  If  a  list  <mlist>  of  matrices   with   non-negative   integer
1916##  coefficients  is  supplied  it  is  used  to  ``supply''   automorphisms;
1917##  otherwise, previously supplied automorphisms are ``extended''.
1918##
1919InstallGlobalFunction( PQ_SUPPLY_OR_EXTEND_AUTOMORPHISMS, function( arg )
1920local datarec;
1921  datarec := arg[1];
1922  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1923  if 1 = Length(arg) then
1924    ToPQ(datarec, [ 18 ], [ " #extend auts" ]);
1925  else
1926    ToPQ(datarec, [ 18 ], [ " #supply auts" ]);
1927    CallFuncList(PQ_MANUAL_AUT_INPUT, arg);
1928  fi;
1929  datarec.hasAuts := true;
1930end );
1931
1932#############################################################################
1933##
1934#F  PqSupplyAutomorphisms(<i>, <mlist>) . . supply auts via A p-Q menu opt 18
1935#F  PqSupplyAutomorphisms( <mlist> )
1936##
1937##  for the  <i>th  or  default  interactive  {\ANUPQ}  process,  supply  the
1938##  automorphism  data  provided  by  the  list  <mlist>  of  matrices   with
1939##  non-negative integer coefficients. Each matrix in <mlist> must  have  the
1940##  same dimensions; in particular, the number of rows of each matrix must be
1941##  the number of pc generators of the  current  $p$-quotient  of  the  group
1942##  associated with the interactive {\ANUPQ} process.
1943##
1944##  *Note:*
1945##  For those familiar with the  `pq'  binary,  `PqSupplyAutomorphisms'  uses
1946##  menu item 18 of the Advanced $p$-Quotient menu.
1947##
1948InstallGlobalFunction( PqSupplyAutomorphisms, function( arg )
1949local args;
1950  args := PQ_AUT_ARG_CHK(1, arg);
1951  args[1] := ANUPQData.io[ args[1] ];
1952  if IsBound(args[1].hasAuts) and args[1].hasAuts then
1953    Error("huh! already have automorphisms.\n",
1954          "Perhaps you wanted to use `PqExtendAutomorphisms'\n");
1955  fi;
1956  CallFuncList( PQ_SUPPLY_OR_EXTEND_AUTOMORPHISMS, args );
1957end );
1958
1959#############################################################################
1960##
1961#F  PqExtendAutomorphisms( <i> ) . . . . .  extend auts via A p-Q menu opt 18
1962#F  PqExtendAutomorphisms()
1963##
1964##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
1965##  binary to extend previously-supplied automorphisms.
1966##
1967##  *Note:*
1968##  For those familiar with the  `pq'  binary,  `PqExtendAutomorphisms'  uses
1969##  menu item 18 of the Advanced $p$-Quotient menu.
1970##
1971InstallGlobalFunction( PqExtendAutomorphisms, function( arg )
1972local datarec;
1973  datarec := CallFuncList(ANUPQDataRecord, arg);
1974  if not(IsBound(datarec.hasAuts) and datarec.hasAuts) then
1975    Error("huh! don't have any automorphisms to extend.\n",
1976          "Perhaps you wanted to use `PqSupplyAutomorphisms'\n");
1977  fi;
1978  PQ_SUPPLY_OR_EXTEND_AUTOMORPHISMS( datarec );
1979end );
1980
1981#############################################################################
1982##
1983#F  PQ_CLOSE_RELATIONS( <datarec>, <qfac> ) . . . . . .  A p-Q menu option 19
1984##
1985##  inputs data to the `pq' binary for option 19 of the Advanced $p$-Quotient
1986##  menu, to apply automorphisms.
1987##
1988InstallGlobalFunction( PQ_CLOSE_RELATIONS, function( datarec, qfac )
1989  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
1990  ToPQ(datarec, [ 19 ], [ " #close relations"  ]);
1991  ToPQ(datarec, [ qfac ], [ " #queue factor" ]);
1992end );
1993
1994#############################################################################
1995##
1996#F  PqApplyAutomorphisms( <i>, <qfac> ) . .  user ver of A p-Q menu option 19
1997#F  PqApplyAutomorphisms( <qfac> )
1998##
1999##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
2000##  binary to apply automorphisms; <qfac> is the queue factor e.g. `15'.
2001##
2002##  *Note:*
2003##  For those familiar with  the  `pq'  binary,  `PqCloseRelations'  performs
2004##  menu item 19 of the Advanced $p$-Quotient menu.
2005##
2006InstallGlobalFunction( PqApplyAutomorphisms, function( arg )
2007local len, datarec, qfac;
2008  len := Length(arg);
2009  if not(len in [1, 2]) then
2010    Error("expected 1 or 2 arguments\n");
2011  fi;
2012  datarec := CallFuncList(ANUPQDataRecord, arg{[1 .. len - 1]});
2013  PQ_CLOSE_RELATIONS( datarec, arg[len] );
2014end );
2015
2016#############################################################################
2017##
2018#F  PQ_DISPLAY( <datarec>, <opt>, <type>, <bnds> ) .  A p-Q menu option 20/21
2019##
2020##  inputs data to the `pq' binary  for  Advanced  $p$-Quotient  menu  option
2021##  <opt> (<opt> should be 20 or 21) to display the generator  structure  (if
2022##  `<opt> = 20' and `<type> = "structure"') or to display automorphisms  (if
2023##  `<opt> = 21' and `<type> =  "automorphisms"'),  for  the  pcp  generators
2024##  numbered between the bounds determined by the option `Bounds' or for  all
2025##  pcp generators if `Bounds' is not set.
2026##
2027InstallGlobalFunction( PQ_DISPLAY, function( datarec, opt, type, bnds )
2028  PQ_MENU(datarec, "ApQ");
2029  if VALUE_PQ_OPTION("OutputLevel", datarec) <> fail then
2030    PQ_SET_OUTPUT_LEVEL( datarec, datarec.OutputLevel );
2031  fi;
2032  ToPQ(datarec, [ opt ],     [ " #display ", type ]);
2033  ToPQ(datarec, [ bnds[1] ], [ " #no. of first generator" ]);
2034  ToPQ(datarec, [ bnds[2] ], [ " #no. of last generator"  ]);
2035end );
2036
2037#############################################################################
2038##
2039#F  PQ_BOUNDS( <datarec>, <hibnd> ) . . provide bounds from option or default
2040##
2041##  extracts a list of two integer bounds from option  `Bounds'  if  set,  or
2042##  otherwise uses `[1 .. <hibnd>]' as default. If `Bounds' is set  they  are
2043##  checked to lie in the range `[1 .. <hibnd>]' and an error is generated if
2044##  they are not. If there is no error the list of two bounds  determined  by
2045##  the above is returned.
2046##
2047InstallGlobalFunction( PQ_BOUNDS, function( datarec, hibnd )
2048local bounds;
2049  bounds := VALUE_PQ_OPTION("Bounds");
2050  if bounds = fail then
2051    return [1, hibnd];
2052  elif bounds[2] > hibnd then
2053    # most checking has already been done by VALUE_PQ_OPTION
2054    Info(InfoWarning + InfoANUPQ, 1,
2055         "2nd bound ", bounds[2], " of `Bounds' can be at most ", hibnd);
2056    Info(InfoWarning + InfoANUPQ, 1,
2057         "... replacing this bound most with", hibnd);
2058    return [bounds[1], hibnd];
2059  else
2060    return bounds;
2061  fi;
2062end );
2063
2064#############################################################################
2065##
2066#F  PqDisplayStructure(<i>[: Bounds := <list>]) . user ver A p-Q menu opt. 20
2067#F  PqDisplayStructure([: Bounds := <list>])
2068##
2069##  for the <i>th or default interactive {\ANUPQ} process, directs  the  `pq'
2070##  binary  to  display  the  structure  for  the  pcp  generators   numbered
2071##  (inclusively) between the bounds of `Bounds' or  for  all  generators  if
2072##  `Bounds' is not  given.  The  value  <list>  of  `Bounds'  (assuming  the
2073##  interactive process is numbered <i>) should be a  list  of  two  integers
2074##  <low>,  <high>  satisfying  `1  \<=  <low>   \<=   PqNrPcGenerators(<i>)'
2075##  (see~"PqNrPcGenerators"). `PqDisplayStructure' also  accepts  the  option
2076##  `OutputLevel' (see e.g.~"Pq" where the option is listed).
2077##
2078##  *Note:*
2079##  For those familiar with the `pq'  binary,  `PqDisplayStructure'  performs
2080##  option 20 of the Advanced $p$-Quotient menu.
2081##
2082InstallGlobalFunction( PqDisplayStructure, function( arg )
2083local datarec;
2084  PQ_OTHER_OPTS_CHK("PqDisplayStructure", true);
2085  datarec := PQ_DATA_CHK(arg);
2086  PQ_DISPLAY( datarec, 20, "structure",
2087              PQ_BOUNDS(datarec, datarec.forder[2]) );
2088end );
2089
2090#############################################################################
2091##
2092#F  PqDisplayAutomorphisms(<i>[: Bounds := <list>]) . u ver A p-Q menu opt 21
2093#F  PqDisplayAutomorphisms([: Bounds := <list>])
2094##
2095##  for the <i>th or default interactive {\ANUPQ} process, directs  the  `pq'
2096##  binary to display the automorphism actions on the pcp generators numbered
2097##  (inclusively) between the bounds of `Bounds' or  for  all  generators  if
2098##  `Bounds' is not  given.  The  value  <list>  of  `Bounds'  (assuming  the
2099##  interactive process is numbered <i>) should be a  list  of  two  integers
2100##  <low>,   <high>   satisfying   $1    \le    <low>    \le    <high>    \le
2101##  `PqNrPcGenerators(<i>)'$  (see~"PqNrPcGenerators").  `PqDisplayStructure'
2102##  also accepts the option `OutputLevel' (see "option OutputLevel").
2103##
2104##  *Note:*
2105##  For  those  familiar  with  the  `pq'  binary,   `PqDisplayAutomorphisms'
2106##  performs menu item 21 of the Advanced $p$-Quotient menu.
2107##
2108InstallGlobalFunction( PqDisplayAutomorphisms, function( arg )
2109local datarec;
2110  PQ_OTHER_OPTS_CHK("PqDisplayAutomorphisms", true);
2111  datarec := PQ_DATA_CHK(arg);
2112  PQ_DISPLAY( datarec, 21, "automorphisms",
2113              PQ_BOUNDS(datarec, datarec.forder[2]) );
2114end );
2115
2116#############################################################################
2117##
2118#F  PQ_COLLECT_DEFINING_GENERATORS( <datarec>, <word> ) . . A p-Q menu opt 23
2119##
2120##  instructs the  `pq'  binary  to  do  a  collection  on  <word>  a  string
2121##  representing a word in the  weight 1  pc  generators,  e.g.  `"x2^2*x1"',
2122##  using option 23 of the interactive $p$-Quotient menu.
2123##
2124InstallGlobalFunction( PQ_COLLECT_DEFINING_GENERATORS, function( datarec, word )
2125  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
2126  ToPQ(datarec, [ 23 ], [ " #collect defining generators" ]);
2127  datarec.match := "The result of collection is";
2128  ToPQ(datarec, [ word, ";" ], [ "  #word to be collected" ]);
2129  return PQ_WORD(datarec);
2130end );
2131
2132#############################################################################
2133##
2134#F  PqCollectWordInDefiningGenerators(<i>,<word>) . u ver of A p-Q menu op 23
2135#F  PqCollectWordInDefiningGenerators( <word> )
2136##
2137##  for  the  <i>th  or  default  interactive  {\ANUPQ}  process,  collect  a
2138##  user-defined word in the pc generators of the class 1 quotient,  i.e.~the
2139##  pc generators that correspond to the original  fp  or  pc  group  of  the
2140##  process, with respect to the current pc presentation, in the  context  of
2141##  finding the next class (see~"PqNextClass"), and return the result of  the
2142##  collection as a list of generator  number,  exponent  pairs.  The  <word>
2143##  argument may be input in either of the two ways described for `PqCollect'
2144##  (see~"PqCollect"). It is not illegal for <word> to contain pc  generators
2145##  of weight larger than 1, but they are  intrepreted  as  representing  the
2146##  identity;   `PqCollectWordInDefiningGenerators'   works   exactly    like
2147##  `PqCollect' except for this distinction.
2148##
2149##  *Note:*
2150##  For those familiar with the  `pq'  program,  `PqCollectDefiningGenerators'
2151##  performs menu item 23 of the Advanced $p$-Quotient menu.
2152##
2153InstallGlobalFunction( PqCollectWordInDefiningGenerators, function( arg )
2154  return CallFuncList( PQ_COLLECT_DEFINING_GENERATORS,
2155                       PQ_CHK_COLLECT_COMMAND_ARGS(arg) );
2156end );
2157
2158#############################################################################
2159##
2160#F  PqCommutatorDefiningGenerators(<i>,<words>,<pow>) . user ver A p-Q opt 24
2161#F  PqCommutatorDefiningGenerators( <words>, <pow> )
2162##
2163##  for the <i>th or default interactive {\ANUPQ} process, directs  the  `pq'
2164##  binary to compute the left norm commutator of the list <words>  of  words
2165##  in the generators raised to the integer power <pow>.
2166##
2167##  *Note:*
2168##  For those familiar with the `pq' binary, `PqCommutatorDefiningGenerators'
2169##  performs option 24 of the Advanced $p$-Quotient menu.
2170##
2171InstallGlobalFunction( PqCommutatorDefiningGenerators, function( arg )
2172  return CallFuncList( PQ_COMMUTATOR,
2173                       PQ_COMMUTATOR_CHK_ARGS(
2174                           Concatenation(
2175                               arg,
2176                               [[[24], [" #commutator of defining genrs"]]] )
2177                           ) );
2178end );
2179
2180#############################################################################
2181##
2182#F  PQ_WRITE_PC_PRESENTATION( <datarec>, <filename> ) .  A p-Q menu option 25
2183##
2184##  tells the `pq' binary to write a pc presentation to the  file  with  name
2185##  <filename> for group `<datarec>.group'  (option  25  of  the  interactive
2186##  $p$-Quotient menu).
2187##
2188InstallGlobalFunction( PQ_WRITE_PC_PRESENTATION, function( datarec, filename )
2189  if not IsBound(datarec.setupfile) then
2190    PrintTo(filename, "");   #to ensure it's writable and empty
2191  fi;
2192  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
2193  ToPQ(datarec, [ 25 ], [ " #set output file" ]);
2194  ToPQ(datarec, [ filename ], []);
2195  ToPQ(datarec, [ 2 ], [ "  #output in GAP format" ]);
2196end );
2197
2198#############################################################################
2199##
2200#F  PqWritePcPresentation( <i>, <filename> ) . user ver. of A p-Q menu opt 25
2201#F  PqWritePcPresentation( <filename> )
2202##
2203##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
2204##  binary to write a pc presentation to the file with  name  <filename>  for
2205##  the group of that process for which a pc presentation has been previously
2206##  computed, where the group of a process is the one given as first argument
2207##  when `PqStart' was called to initiate that process (for process  <i>  the
2208##  group is stored as `ANUPQData.io[<i>].group'). If the first character  of
2209##  the string <filename> is not `/', <filename> is assumed to be the path of
2210##  a writable file relative to the directory in which {\GAP} was started. If
2211##  a pc presentation has not been previously computed by  the  `pq'  binary,
2212##  then  `pq'  is  called  to  compute  it   first,   effectively   invoking
2213##  `PqPcPresentation' (see~"PqPcPresentation").
2214##
2215##  *Note:* For those familiar with the `pq' binary,  `PqPcWritePresentation'
2216##  performs menu item 25 of the Advanced $p$-Quotient menu.
2217##
2218InstallGlobalFunction( PqWritePcPresentation, function( arg )
2219local filename, datarec;
2220  if 2 < Length(arg) or IsEmpty(arg) then
2221    Error("expected one or two arguments.\n");
2222  fi;
2223  datarec := CallFuncList(ANUPQDataRecord, arg{[1..Length(arg) - 1]});
2224  filename := PQ_CHK_PATH( arg[Length(arg)], "w", datarec );
2225  if not( IsBound(datarec.pCover) and datarec.pcoverclass = datarec.class or
2226          IsBound(datarec.pQuotient) ) then
2227    Error( "no p-quotient or p-cover has been computed\n" );
2228  fi;
2229  PQ_WRITE_PC_PRESENTATION( datarec, filename );
2230end );
2231
2232#############################################################################
2233##
2234#F  PQ_WRITE_COMPACT_DESCRIPTION( <datarec> ) . . . . .  A p-Q menu option 26
2235##
2236##  tells the `pq' binary to write a compact description to a file.
2237##
2238InstallGlobalFunction( PQ_WRITE_COMPACT_DESCRIPTION, function( datarec )
2239  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
2240  ToPQ(datarec, [ 26 ], [ " #write compact description to file" ]);
2241end );
2242
2243#############################################################################
2244##
2245#F  PqWriteCompactDescription( <i> ) . . user version of A p-Q menu option 26
2246#F  PqWriteCompactDescription()
2247##
2248##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
2249##  binary to write a compact description to a file.
2250##
2251##  *Note:*
2252##  For those familiar  with  the  `pq'  binary,  `PqWriteCompactDescription'
2253##  performs menu item 26 of the Advanced $p$-Quotient menu.
2254##
2255InstallGlobalFunction( PqWriteCompactDescription, function( arg )
2256  PQ_WRITE_COMPACT_DESCRIPTION( CallFuncList(ANUPQDataRecord, arg) );
2257end );
2258
2259#############################################################################
2260##
2261#F  PQ_EVALUATE_CERTAIN_FORMULAE( <datarec> ) . . . . .  A p-Q menu option 27
2262##
2263##  inputs data to the `pq' binary for option 27 of the Advanced $p$-Quotient
2264##  menu, to evaluate certain formulae.
2265##
2266InstallGlobalFunction( PQ_EVALUATE_CERTAIN_FORMULAE, function( datarec )
2267  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
2268  ToPQ(datarec, [ 27 ], [ " #evaluate certain formulae" ]);
2269end );
2270
2271#############################################################################
2272##
2273#F  PqEvaluateCertainFormulae( <i> ) . . user version of A p-Q menu option 27
2274#F  PqEvaluateCertainFormulae()
2275##
2276##  for the <i>th or default interactive {\ANUPQ} process, directs  the  `pq'
2277##  binary to evaluate certain formulae.
2278##
2279##  *Note:*
2280##  For those familiar  with  the  `pq'  binary,  `PqEvaluateCertainFormulae'
2281##  performs option 27 of the Advanced $p$-Quotient menu.
2282##
2283InstallGlobalFunction( PqEvaluateCertainFormulae, function( arg )
2284local datarec;
2285  datarec := CallFuncList(ANUPQDataRecord, arg);
2286  PQ_EVALUATE_CERTAIN_FORMULAE( datarec );
2287end );
2288
2289#############################################################################
2290##
2291#F  PQ_EVALUATE_ACTION( <datarec> ) . . . . . . . . . .  A p-Q menu option 28
2292##
2293##  inputs data to the `pq' binary for option 28 of the Advanced $p$-Quotient
2294##  menu, to evaluate the action.
2295##
2296InstallGlobalFunction( PQ_EVALUATE_ACTION, function( datarec )
2297  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
2298  ToPQ(datarec, [ 28 ], [ " #evaluate action" ]);
2299end );
2300
2301#############################################################################
2302##
2303#F  PqEvaluateAction( <i> ) . . . . . .  user version of A p-Q menu option 28
2304#F  PqEvaluateAction()
2305##
2306##  for the <i>th or default interactive {\ANUPQ} process, directs  the  `pq'
2307##  binary to evaluate the action.
2308##
2309##  *Note:*
2310##  For those familiar with  the  `pq'  binary,  `PqEvaluateAction'  performs
2311##  option 28 of the Advanced $p$-Quotient menu.
2312##
2313InstallGlobalFunction( PqEvaluateAction, function( arg )
2314local datarec;
2315  datarec := CallFuncList(ANUPQDataRecord, arg);
2316  PQ_EVALUATE_ACTION( datarec );
2317end );
2318
2319#############################################################################
2320##
2321#F  PQ_EVALUATE_ENGEL_IDENTITY( <datarec> ) . . . . . .  A p-Q menu option 29
2322##
2323##  inputs data to the `pq' binary for option 29 of the
2324##  Advanced $p$-Quotient menu.
2325##
2326InstallGlobalFunction( PQ_EVALUATE_ENGEL_IDENTITY, function( datarec )
2327  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
2328  ToPQ(datarec, [ 29 ], [ " #evaluate Engel identity" ]);
2329end );
2330
2331#############################################################################
2332##
2333#F  PqEvaluateEngelIdentity( <i> ) . . . user version of A p-Q menu option 29
2334#F  PqEvaluateEngelIdentity()
2335##
2336##  for the <i>th or default interactive {\ANUPQ} process, inputs data
2337##  to the `pq' binary
2338##
2339##  *Note:* For those  familiar  with  the  `pq'  binary,
2340##  `PqEvaluateEngelIdentity' performs option 29 of the
2341##  Advanced $p$-Quotient menu.
2342##
2343InstallGlobalFunction( PqEvaluateEngelIdentity, function( arg )
2344local datarec;
2345  datarec := CallFuncList(ANUPQDataRecord, arg);
2346  PQ_EVALUATE_ENGEL_IDENTITY( datarec );
2347end );
2348
2349#############################################################################
2350##
2351#F  PQ_PROCESS_RELATIONS_FILE( <datarec> ) . . . . . . . A p-Q menu option 30
2352##
2353##  inputs data to the `pq' binary for option 30 of the
2354##  Advanced $p$-Quotient menu.
2355##
2356InstallGlobalFunction( PQ_PROCESS_RELATIONS_FILE, function( datarec )
2357  PQ_MENU(datarec, "ApQ"); #we need options from the Advanced p-Q Menu
2358  ToPQ(datarec, [ 30 ], [ " #process relations file" ]);
2359end );
2360
2361#############################################################################
2362##
2363#F  PqProcessRelationsFile( <i> ) . . .  user version of A p-Q menu option 30
2364#F  PqProcessRelationsFile()
2365##
2366##  for the <i>th or default interactive {\ANUPQ} process, inputs data
2367##  to the `pq' binary
2368##
2369##  *Note:* For those  familiar  with  the  `pq'  binary,
2370##  `PqProcessRelationsFile' performs option 30 of the
2371##  Advanced $p$-Quotient menu.
2372##
2373InstallGlobalFunction( PqProcessRelationsFile, function( arg )
2374local datarec;
2375  datarec := CallFuncList(ANUPQDataRecord, arg);
2376  PQ_PROCESS_RELATIONS_FILE( datarec );
2377end );
2378
2379#############################################################################
2380##
2381#F  PqSPComputePcpAndPCover(<i> : <options>) . . . user ver of SP menu opt. 1
2382#F  PqSPComputePcpAndPCover( : <options> )
2383##
2384##  for the <i>th or default interactive {\ANUPQ} process, directs  the  `pq'
2385##  binary to compute for the group of that process a pc presentation  up  to
2386##  the $p$-quotient of maximum class or the value of the option `ClassBound'
2387##  and the $p$-cover of that  quotient,  and  sets  up  tabular  information
2388##  required for computation of a standard presentation. Here the group of  a
2389##  process is the one given as first argument when `PqStart' was  called  to
2390##  initiate  that  process  (for  process  <i>  the  group  is   stored   as
2391##  `ANUPQData.io[<i>].group').
2392##
2393##  The possible <options> are `Prime', `ClassBound', `Relators', `Exponent',
2394##  `Metabelian' and `OutputLevel' (see Chapter~"ANUPQ Options" for  detailed
2395##  descriptions of these options). The option `Prime' is normally determined
2396##  via `PrimePGroup', and so is not required unless the group  doesn't  know
2397##  it's a $p$-group and `HasPrimePGroup' returns `false'.
2398##
2399##  *Note:*
2400##  For  those  familiar  with  the  `pq'  binary,  `PqSPComputePcpAndPCover'
2401##  performs option 1 of the Standard Presentation menu.
2402##
2403InstallGlobalFunction( PqSPComputePcpAndPCover, function( arg )
2404local datarec;
2405  PQ_OTHER_OPTS_CHK("PqSPComputePcpAndPCover", true);
2406  datarec := CallFuncList(ANUPQDataRecord, arg);
2407  PQ_PC_PRESENTATION( datarec, "SP" );
2408end );
2409
2410#############################################################################
2411##
2412#F  PQ_SP_STANDARD_PRESENTATION(<datarec>[,<mlist>] :<options>) SP menu opt 2
2413##
2414##  inputs data given by <options> to the `pq' binary to compute  a  standard
2415##  presentation for group `<datarec>.group'. If argument <mlist> is given it
2416##  is assumed to be the automorphism group data required.  Otherwise  it  is
2417##  assumed that `<datarec>.pQuotient' exists and that {\GAP} can compute its
2418##  automorphism group and the  necessary  automorphism  group  data  can  be
2419##  derived from `<datarec>.pQuotient'. This uses option 2  of  the  Standard
2420##  Presentation menu.
2421##
2422InstallGlobalFunction( PQ_SP_STANDARD_PRESENTATION, function( arg )
2423local datarec, savefile;
2424  datarec := arg[1];
2425  savefile := PQ_CHK_PATH(
2426                  VALUE_PQ_OPTION( "StandardPresentationFile",
2427                                   Filename( ANUPQData.tmpdir, "SPres" ) ),
2428                  "w", datarec);
2429  PQ_MENU(datarec, "SP");
2430  ToPQ(datarec, [ 2 ], [ "  #compute standard presentation" ]);
2431  ToPQ(datarec, [ savefile ], [ "  #file for saving pres'n" ]);
2432  ToPQ(datarec, [ VALUE_PQ_OPTION("ClassBound", 63)], [ "  #class bound" ]);
2433
2434  if 1 = Length(arg) then
2435    PQ_AUT_INPUT( datarec, datarec.pQuotient );
2436  else
2437    PQ_MANUAL_AUT_INPUT( datarec, arg[2] );
2438  fi;
2439  ToPQ_BOOL(datarec, VALUE_PQ_OPTION("PcgsAutomorphisms", false, datarec),
2440                     "compute pcgs gen. seq. for auts.");
2441end );
2442
2443#############################################################################
2444##
2445#F  PqSPStandardPresentation(<i>[,<mlist>]:<options>)  user ver SP menu opt 2
2446#F  PqSPStandardPresentation([<mlist>] : <options> )
2447##
2448##  for the <i>th or default interactive {\ANUPQ} process, inputs data  given
2449##  by <options> to compute a standard presentation for  the  group  of  that
2450##  process.  If  argument  <mlist>  is  given  it  is  assumed  to  be   the
2451##  automorphism group data required. Otherwise it is assumed that a call  to
2452##  either      `Pq'      (see~"Pq!interactive")      or      `PqEpimorphism'
2453##  (see~"PqEpimorphism!interactive") has generated a $p$-quotient  and  that
2454##  {\GAP} can compute  its  automorphism  group  from  which  the  necessary
2455##  automorphism group data can be derived. The group of the process  is  the
2456##  one given as first argument when `PqStart' was  called  to  initiate  the
2457##  process (for process <i> the group is stored as `ANUPQData.io[<i>].group'
2458##  and     the     $p$-quotient     if     existent     is     stored     as
2459##  `ANUPQData.io[<i>].pQuotient').  If  <mlist>   is   not   given   and   a
2460##  $p$-quotient of the group has not been  previously  computed  a  class  1
2461##  $p$-quotient is computed.
2462##
2463##  `PqSPStandardPresentation' accepts three options, all optional:
2464##
2465##  \beginitems
2466##
2467##  `StandardPresentationFile := <filename>'&
2468##  Specifies that the file to which the standard presentation is written has
2469##  name <filename>. If the first character of the string <filename>  is  not
2470##  `/', <filename> is assumed to be the path of a writable file relative  to
2471##  the directory in which {\GAP} was started. If this option is  omitted  it
2472##  is written to the file with the name generated by the command  `Filename(
2473##  ANUPQData.tmpdir, "SPres" );', i.e.~the file with name  `"SPres"' in  the
2474##  temporary directory in which the `pq' binary executes.
2475##
2476##  `ClassBound := <n>' &
2477##  Specifies that the $p$-quotient computed has lower exponent-$p$ class  at
2478##  most <n>. If this option is omitted a default of 63 is used.
2479##
2480##  `PcgsAutomorphisms' &
2481##  Specifies that a polycyclic  generating  sequence  for  the  automorphism
2482##  group of the group of the process (which must be *soluble*), be  computed
2483##  and passed to the `pq' binary.  This  increases  the  efficiency  of  the
2484##  computation;  it  also  prevents  the  `pq'  from  calling   {\GAP}   for
2485##  orbit-stabilizer calculations. See section "Computing  Descendants  of  a
2486##  p-Group" for further explanations.
2487##
2488##  \enditems
2489##
2490##  *Note:* For those familiar with  the  `pq'  binary,  `PqSPPcPresentation'
2491##  performs option 2 of the Standard Presentation menu.
2492##
2493InstallGlobalFunction( PqSPStandardPresentation, function( arg )
2494local args, datarec;
2495  args := PQ_AUT_ARG_CHK(0, arg);
2496  datarec := ANUPQData.io[ args[1] ];
2497  if 1 = Length(args) and not IsBound(datarec.pQuotient) then
2498    PQ_EPI_OR_PCOVER( args[1] : PqEpiOrPCover := "pQuotient");
2499  fi;
2500  args[1] := datarec;
2501  CallFuncList( PQ_SP_STANDARD_PRESENTATION, args );
2502end );
2503
2504#############################################################################
2505##
2506#F  PQ_SP_SAVE_PRESENTATION( <datarec>, <filename> ) . . . . SP menu option 3
2507##
2508##  directs the `pq' binary to  save  the  standard  presentation  previously
2509##  computed for `<datarec>.group'  to  <filename>  using  option  3  of  the
2510##  Standard Presentation menu.
2511##
2512InstallGlobalFunction( PQ_SP_SAVE_PRESENTATION, function( datarec, filename )
2513  PQ_MENU(datarec, "SP");
2514  ToPQ(datarec, [ 3 ], [ "  #save standard presentation to file" ]);
2515  ToPQ(datarec, [ filename ], [ "  #filename" ]);
2516end );
2517
2518#############################################################################
2519##
2520#F  PqSPSavePresentation( <i>, <filename> ) . .  user ver of SP menu option 3
2521#F  PqSPSavePresentation( <filename> )
2522##
2523##  for the <i>th or default interactive {\ANUPQ} process, directs  the  `pq'
2524##  binary to save the standard  presentation  previously  computed  for  the
2525##  group of that process to the file with name <filename>, where  the  group
2526##  of a process is the one given as first argument when `PqStart' was called
2527##  to initiate that process. If the first character of the string <filename>
2528##  is not `/' <filename> is assumed to  be  the  path  of  a  writable  file
2529##  relative to the directory in which {\GAP} was started.
2530##
2531##  *Note:* For those familiar with the `pq'  binary,  `PqSPSavePresentation'
2532##  performs option 3 of the Standard Presentation menu.
2533##
2534InstallGlobalFunction( PqSPSavePresentation, function( arg )
2535local datarec, filename;
2536  PQ_OTHER_OPTS_CHK("PqSPSavePresentation", true);
2537  if 0 = Length(arg) or Length(arg) > 2 then
2538    Error( "expected 1 or 2 arguments\n" );
2539  fi;
2540  datarec := CallFuncList(ANUPQDataRecord, arg{[1..Length(arg) - 1]});
2541  filename := PQ_CHK_PATH( arg[Length(arg)], "w", datarec );
2542  PQ_SP_SAVE_PRESENTATION( datarec, filename );
2543end );
2544
2545#############################################################################
2546##
2547#F  PQ_SP_COMPARE_TWO_FILE_PRESENTATIONS(<datarec>,<f1>,<f2>) . SP menu opt 6
2548##
2549##  inputs data to the `pq' binary for option 6 of the Standard  Presentation
2550##  menu, to compare the presentations in the files with names <f1> and  <f2>
2551##  and returns `true' if they are identical and `false' otherwise.
2552##
2553InstallGlobalFunction( PQ_SP_COMPARE_TWO_FILE_PRESENTATIONS,
2554function( datarec, f1, f2 )
2555local line;
2556  PQ_MENU(datarec, "SP");
2557  ToPQ( datarec, [ 6 ], [ "  #compare two file presentations" ]);
2558  ToPQ( datarec, [ f1 ], [ "  #1st filename" ]);
2559  datarec.match := "Identical";
2560  datarec.filter := ["Identical"];
2561  ToPQ(datarec, [ f2 ], [ "  #2nd filename" ]);
2562  line := SplitString(datarec.matchedline, "", "? \n");
2563  PQ_UNBIND(datarec, ["match", "matchedline", "filter"]);
2564  return EvalString( LowercaseString( line[3] ) );
2565end );
2566
2567#############################################################################
2568##
2569#F  PqSPCompareTwoFilePresentations(<i>,<f1>,<f2>)  user ver of SP menu opt 6
2570#F  PqSPCompareTwoFilePresentations(<f1>,<f2>)
2571##
2572##  for the <i>th or default interactive {\ANUPQ} process, directs  the  `pq'
2573##  binary to compare the presentations in the files with names <f1> and <f2>
2574##  and returns `true' if they are identical and `false' otherwise. For  each
2575##  of the strings <f1> and <f2>, if the first character is not a `/' then it
2576##  is assumed to be the path of a readable file relative to the directory in
2577##  which {\GAP} was started.
2578##
2579##  *Notes*
2580##
2581##  The presentations in files <f1> and <f2> must have been generated by  the
2582##  `pq' binary but they do *not* need to be *standard* presentations.
2583##
2584##   For      those      familiar      with      the       `pq'       binary,
2585##   `PqSPCompareTwoFilePresentations' performs  option  6  of  the  Standard
2586##   Presentation menu.
2587##
2588InstallGlobalFunction( PqSPCompareTwoFilePresentations, function( arg )
2589local len, datarec, f1, f2;
2590  len := Length(arg);
2591  if not(len in [2, 3]) then
2592    Error( "expected 2 or 3 arguments\n" );
2593  fi;
2594  datarec := CallFuncList(ANUPQDataRecord, arg{[1..len - 2]});
2595  f1 := PQ_CHK_PATH( arg[len - 1], "r", datarec );
2596  f2 := PQ_CHK_PATH( arg[len], "r", datarec );
2597  return PQ_SP_COMPARE_TWO_FILE_PRESENTATIONS( datarec, f1, f2 );
2598end );
2599
2600#############################################################################
2601##
2602#F  PQ_SP_ISOMORPHISM( <datarec> ) . . . . . . . . . . . . . SP menu option 8
2603##
2604##  computes the mapping  from  the  automorphism  group  generators  to  the
2605##  generators of the standard presentation,  using  option  8  of  the  main
2606##  Standard Presentation menu.
2607##
2608InstallGlobalFunction( PQ_SP_ISOMORPHISM, function( datarec )
2609  PQ_MENU(datarec, "SP");
2610  ToPQ(datarec, [ 8 ], [ "  #compute isomorphism" ]);
2611end );
2612
2613#############################################################################
2614##
2615#F  PqSPIsomorphism( <i> ) . . . . . . . . . user version of SP menu option 8
2616#F  PqSPIsomorphism()
2617##
2618##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
2619##  program to compute the isomorphism mapping  from  the  $p$-group  of  the
2620##  process  to  its  standard  presentation.  This   function   provides   a
2621##  description      only;      for      a      {\GAP}      object,       use
2622##  `EpimorphismStandardPresentation'
2623##  (see~"EpimorphismStandardPresentation!interactive").
2624##
2625##  *Note:* For  those  familiar  with  the  `pq'  program,  `PqSPIsomorphism'
2626##  performs menu item 8 of the Standard Presentation menu.
2627##
2628InstallGlobalFunction( PqSPIsomorphism, function( arg )
2629local datarec;
2630  datarec := CallFuncList(ANUPQDataRecord, arg);
2631  PQ_SP_ISOMORPHISM( datarec );
2632end );
2633
2634#############################################################################
2635##
2636#F  PQ_PG_SUPPLY_AUTS( <datarec>[, <mlist>], <menu> ) .  p-G/A p-G menu opt 1
2637##
2638##  defines the automorphism group of `<datarec>.group', using  option  1  of
2639##  the main or Advanced $p$-Group Generation menu.
2640##
2641InstallGlobalFunction( PQ_PG_SUPPLY_AUTS, function( arg )
2642  local datarec;
2643
2644  CallFuncList( PQ_MENU, arg{[1, Length(arg)]});
2645  datarec := arg[1];
2646  if 2 < Length(arg) and
2647     VALUE_PQ_OPTION("NumberOfSolubleAutomorphisms", 0, datarec) > 0 and
2648     Length(VALUE_PQ_OPTION("RelativeOrders", [], datarec))
2649        <> datarec.NumberOfSolubleAutomorphisms then
2650    Error("the number of elements of option \"RelativeOrders\" should equal\n",
2651          "the value of option \"NumberOfSolubleAutomorphisms\" (",
2652          datarec.NumberOfSolubleAutomorphisms, ")\n");
2653  fi;
2654  ToPQ(datarec, [ 1 ], [ "  #supply automorphism data" ]);
2655  if 2 = Length(arg) then
2656    PQ_AUT_INPUT( datarec, datarec.group );
2657  else
2658    CallFuncList( PQ_MANUAL_AUT_INPUT, arg{[1 .. 2]} );
2659  fi;
2660end );
2661
2662#############################################################################
2663##
2664#F  PqPGSupplyAutomorphisms( <i>[, <mlist>] ) .  user ver of pG menu option 1
2665#F  PqPGSupplyAutomorphisms([<mlist>])
2666##
2667##  for the <i>th or default interactive {\ANUPQ} process,  supply  the  `pq'
2668##  binary with the automorphism group data needed  for  the  group  of  that
2669##  process    (for    process    <i>    the    group    is     stored     as
2670##  `ANUPQData.io[<i>].group'). If  the  argument  <mlist>  is  omitted  then
2671##  {\GAP} *must* be able to determine the automorphism group of the group of
2672##  the process. Otherwise the automorphism data  is  provided  from  <mlist>
2673##  which  should  be  a  list  of   matrices   with   non-negative   integer
2674##  coefficients, where  each  matrix  must  have  the  same  dimensions;  in
2675##  particular, the number of rows of each matrix must be  the  rank  of  the
2676##  group of the process.
2677##
2678##  *Note:*
2679##  For  those  familiar  with  the  `pq'  binary,  `PqPGSupplyAutomorphisms'
2680##  performs option 1 of the main $p$-Group Generation menu.
2681##
2682InstallGlobalFunction( PqPGSupplyAutomorphisms, function( arg )
2683local args;
2684  args := PQ_AUT_ARG_CHK(0, arg);
2685  args[1] := ANUPQData.io[ args[1] ];
2686  Add(args, "pG");
2687  CallFuncList( PQ_PG_SUPPLY_AUTS, args );
2688end );
2689
2690#############################################################################
2691##
2692#F  PQ_PG_EXTEND_AUTOMORPHISMS( <datarec> ) . . . . . p-G/A p-G menu option 2
2693##
2694##  inputs data to the `pq' binary for option  2  of  the  main  or  Advanced
2695##  $p$-Group Generation menu.
2696##
2697InstallGlobalFunction( PQ_PG_EXTEND_AUTOMORPHISMS, function( datarec )
2698  if not(PQ_MENU(datarec) in ["pG", "ApG"]) then
2699    PQ_MENU(datarec, "pG");
2700  fi;
2701  ToPQ(datarec, [ 2 ], [ "  #extend automorphisms" ]);
2702end );
2703
2704#############################################################################
2705##
2706#F  PqPGExtendAutomorphisms( <i> ) .  user version of p-G/A p-G menu option 2
2707#F  PqPGExtendAutomorphisms()
2708##
2709##  for the <i>th or default interactive {\ANUPQ} process, directs  the  `pq'
2710##  binary to compute the extensions of the automorphisms defined by  calling
2711##  `PqPGSupplyAutomorphisms' (see~"PqPGSupplyAutomorphisms"). You  may  wish
2712##  to set the `InfoLevel' of `InfoANUPQ' to 2 (or more) in order to see  the
2713##  output from the `pq' (see~"InfoANUPQ").
2714##
2715##  *Note:*
2716##  For  those  familiar  with  the  `pq'  binary,  `PqPGExtendAutomorphisms'
2717##  performs option 2 of the main or advanced $p$-Group Generation menu.
2718##
2719InstallGlobalFunction( PqPGExtendAutomorphisms, function( arg )
2720local datarec;
2721  datarec := CallFuncList(ANUPQDataRecord, arg);
2722  PQ_PG_EXTEND_AUTOMORPHISMS( datarec );
2723end );
2724
2725#############################################################################
2726##
2727#F  PQ_PG_RESTORE_GROUP(<datarec>, <cls>, <n>) . . . . . p-G/A p-G menu opt 3
2728##
2729##  inputs data to the `pq' binary to restore group <n> of  class  <cls>  for
2730##  option 3 of the main or Advanced $p$-Group Generation menu.
2731##
2732InstallGlobalFunction( PQ_PG_RESTORE_GROUP, function( datarec, cls, n )
2733  if not(PQ_MENU(datarec) in ["pG", "ApG"]) then
2734    PQ_MENU(datarec, "pG");
2735  fi;
2736  ToPQ(datarec, [ 3 ], [ "  #restore group from file" ]);
2737  if IsString(cls) then
2738    ToPQ(datarec, [ cls ], [ "  #filename" ]);
2739  else
2740    ToPQ(datarec, [ datarec.GroupName, "_class", cls ], [ "  #filename" ]);
2741  fi;
2742  ToPQ(datarec, [ n ], [ "  #no. of group" ]);
2743  if IsInt(cls) then
2744    datarec.match := true;
2745    PQ_SET_GRP_DATA(datarec);
2746    datarec.capable := datarec.class > cls;
2747    datarec.pcoverclass := datarec.class;
2748  fi;
2749end );
2750
2751#############################################################################
2752##
2753#F  PqPGSetDescendantToPcp( <i>, <cls>, <n> ) . u ver of p-G/A p-G menu opt 3
2754#F  PqPGSetDescendantToPcp( <cls>, <n> )
2755#F  PqPGSetDescendantToPcp( <i> [: Filename := <name> ])
2756#F  PqPGSetDescendantToPcp([: Filename := <name> ])
2757#F  PqPGRestoreDescendantFromFile(<i>, <cls>, <n>)
2758#F  PqPGRestoreDescendantFromFile( <cls>, <n> )
2759#F  PqPGRestoreDescendantFromFile( <i> [: Filename := <name> ])
2760#F  PqPGRestoreDescendantFromFile([: Filename := <name> ])
2761##
2762##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
2763##  binary to restore group <n> of class <cls> from a temporary  file,  where
2764##  <cls> and <n> are positive integers,  or  the  group  stored  in  <name>.
2765##  `PqPGSetDescendantToPcp'    and    `PqPGRestoreDescendantFromFile'    are
2766##  synonyms;  they  make  sense  only  after  a  prior  call  to   construct
2767##  descendants          by          say           `PqPGConstructDescendants'
2768##  (see~"PqPGConstructDescendants")  or  the   interactive   `PqDescendants'
2769##  (see~"PqDescendants!interactive"). In the `Filename'  option  forms,  the
2770##  option defaults to the last filename in which a presentation  was  stored
2771##  by the `pq' binary.
2772##
2773##  *Note:*
2774##  For those familiar with the  `pq'  binary,  `PqPGSetDescendantToPcp'  and
2775##  `PqPGRestoreDescendantFromFile' perform  menu  item  3  of  the  main  or
2776##  advanced $p$-Group Generation menu.
2777##
2778InstallGlobalFunction( PqPGSetDescendantToPcp, function( arg )
2779local len, datarec, cls, n;
2780  PQ_OTHER_OPTS_CHK("PqPGSetDescendantToPcp", true);
2781  len := Length(arg);
2782  if len > 3 or not(ForAll(arg, IsPosInt)) then
2783    Error("expected at most 3 positive integer arguments\n");
2784  fi;
2785  if len in [2, 3] then
2786    cls := arg[len - 1];
2787    n   := arg[len];
2788    arg := arg{[1 .. len - 2]};
2789  fi;
2790  datarec := CallFuncList(ANUPQDataRecord, arg);
2791  if len in [2, 3] then
2792    if not( IsBound(datarec.ndescendants) and
2793            IsBound( datarec.ndescendants[cls] ) ) then
2794      Error( "descendants for class ", cls, " have not been constructed\n" );
2795    elif datarec.ndescendants[cls][1] < n then
2796      Error( "there is no group ", n, " saved (<n> must be <= ",
2797             datarec.ndescendants[cls][1], ")\n" );
2798    fi;
2799    PQ_PG_RESTORE_GROUP(datarec, cls, n);
2800  else
2801    PQ_PG_RESTORE_GROUP(datarec, VALUE_PQ_OPTION("Filename", datarec.des), 1);
2802  fi;
2803end );
2804
2805#############################################################################
2806##
2807#F  PQ_PG_CONSTRUCT_DESCENDANTS( <datarec> : <options> ) .  p-G menu option 5
2808##
2809##  inputs  data  given  by  <options>  to  the  `pq'  binary  to   construct
2810##  descendants, using option 5 of the main $p$-Group Generation menu.
2811##
2812InstallGlobalFunction( PQ_PG_CONSTRUCT_DESCENDANTS, function( datarec )
2813local nodescendants, class, firstStep, expectedNsteps, optrec, line, ngroups,
2814      cls, totngroups, onestage;
2815
2816  onestage := IsBound(datarec.des) and IsBound(datarec.des.onestage) and
2817              datarec.des.onestage;
2818  if not onestage then
2819    datarec.des := rec();
2820  fi;
2821  VALUE_PQ_OPTION("CustomiseOutput", false, datarec.des);
2822  if not onestage then
2823    # deal with the easy answer
2824    if VALUE_PQ_OPTION("OrderBound", 0, datarec.des) <> 0 and
2825       HasIsFinite(datarec.group) and IsFinite(datarec.group) and
2826       IsPGroup(datarec.group) and
2827       datarec.des.OrderBound <= LogInt(Size(datarec.group),
2828                                        PrimePGroup(datarec.group)) then
2829      return 0;
2830    fi;
2831
2832    # We do these here to ensure an error doesn't occur mid-input of the menu
2833    # item data
2834    if IsBound(datarec.capable) then
2835      #group has come from a `PqPGRestoreGroupFromFile' command
2836      if not datarec.capable then
2837        Info(InfoWarning + InfoANUPQ, 1, "group restored from file is incapable");
2838        return 0;
2839      fi;
2840    fi;
2841    if not IsBound(datarec.pcoverclass) or
2842       datarec.pcoverclass <> datarec.class then
2843      Error("the p-cover of the last p-quotient has not yet been computed!\n");
2844    fi;
2845
2846    # sanity checks
2847    if VALUE_PQ_OPTION("ClassBound", datarec.pcoverclass, datarec.des)
2848       < datarec.pcoverclass then
2849      Error("option `ClassBound' must be at least ", datarec.pcoverclass, "\n");
2850    fi;
2851  fi;
2852
2853  if     VALUE_PQ_OPTION("SpaceEfficient", false, datarec.des) and
2854     not VALUE_PQ_OPTION("PcgsAutomorphisms", false, datarec) then
2855    Info(InfoWarning + InfoANUPQ, 1,
2856         "\"SpaceEfficient\" ignored since \"PcgsAutomorphisms\" is set.");
2857  fi;
2858
2859  if not onestage then
2860    if VALUE_PQ_OPTION("StepSize", datarec.des) <> fail then
2861      if datarec.des.OrderBound <> 0 then
2862        Error("\"StepSize\" and \"OrderBound\" ",
2863              "must not be set simultaneously\n");
2864      fi;
2865      expectedNsteps := datarec.des.ClassBound - datarec.pcoverclass + 1;
2866      if IsList(datarec.des.StepSize) then
2867        firstStep := datarec.des.StepSize[1];
2868        if Length(datarec.des.StepSize) <> expectedNsteps then
2869          Error( "the number of step-sizes in the \"StepSize\" list must\n",
2870                 "equal ", expectedNsteps, " (one more than the difference\n",
2871                 "of \"ClassBound\" and the class of the p-covering group)\n" );
2872        fi;
2873      else
2874        firstStep := datarec.des.StepSize;
2875      fi;
2876      if HasNuclearRank(datarec.group) and
2877         firstStep > NuclearRank(datarec.group) then
2878#          Error("the first \"StepSize\" element (= ", firstStep, ") must not be\n",
2879#                "greater than the \"Nuclear Rank\" (= ",
2880#                NuclearRank(datarec.group), ")\n");
2881          return 0;
2882      fi;
2883    fi;
2884
2885    PQ_MENU(datarec, "pG");
2886    datarec.matchlist := [" is an invalid starting group"];
2887    datarec.matchedlines := [];
2888    ToPQ(datarec, [ 5 ], [ "  #construct descendants" ]);
2889    nodescendants := not IsEmpty(datarec.matchedlines);
2890    PQ_UNBIND( datarec, ["matchlist", "matchedlines"] );
2891    if nodescendants then
2892      return 0;
2893    fi;
2894    ToPQ(datarec, [ datarec.des.ClassBound ], [ " #class bound" ]);
2895
2896    #Construct all descendants?
2897    if not IsBound(datarec.des.StepSize) then
2898      ToPQ(datarec, [ 1 ], [ "  #do construct all descendants" ]);
2899      #Set an order bound for descendants?
2900      if datarec.des.OrderBound <> 0 then
2901        ToPQ(datarec, [ 1 ], [ "  #do set an order bound" ]);
2902        ToPQ(datarec, [ datarec.des.OrderBound ], [ " #order bound" ]);
2903      else
2904        ToPQ(datarec, [ 0 ], [ "  #do not set an order bound" ]);
2905      fi;
2906    else
2907      ToPQ(datarec, [ 0 ], [ "  #do not construct all descendants" ]);
2908      if expectedNsteps = 1 then
2909        # Input step size
2910        ToPQ(datarec, [ firstStep ], [ "  #step size" ]);
2911
2912        # Constant step size?
2913      elif IsInt(datarec.des.StepSize) then
2914        ToPQ(datarec, [ 1 ], [ "  #set constant step size" ]);
2915        ToPQ(datarec, [ datarec.des.StepSize ], [ "  #step size" ]);
2916      else
2917        ToPQ(datarec, [ 0 ], [ "  #set variable step size" ]);
2918        ToPQ(datarec, [ JoinStringsWithSeparator(
2919                            List(datarec.des.StepSize, String), " ") ],
2920                      [ "  #step sizes" ]);
2921      fi;
2922    fi;
2923
2924  else
2925    PQ_MENU(datarec, "ApG");
2926    ToPQ(datarec, [ 5 ], [ "  #single stage" ]);
2927    ToPQ(datarec, [ VALUE_PQ_OPTION("StepSize", datarec.des) ],
2928                  [ " #step size" ]);
2929  fi;
2930  ToPQ_BOOL(datarec, VALUE_PQ_OPTION("PcgsAutomorphisms", false, datarec),
2931                     "compute pcgs gen. seq. for auts.");
2932  ToPQ_BOOL(datarec, VALUE_PQ_OPTION("BasicAlgorithm", false, datarec.des),
2933                     "use default algorithm");
2934  if not datarec.des.BasicAlgorithm then
2935    ToPQ(datarec, [ VALUE_PQ_OPTION(
2936                        "RankInitialSegmentSubgroups", 0, datarec.des) ],
2937                  [ "  #rank of initial segment subgrp" ]);
2938    if datarec.PcgsAutomorphisms then
2939      ToPQ_BOOL(datarec, datarec.des.SpaceEfficient, "be space efficient");
2940    fi;
2941    VALUE_PQ_OPTION("AllDescendants", true, datarec.des);
2942    ToPQ_BOOL(datarec,
2943              not VALUE_PQ_OPTION( "CapableDescendants",
2944                                   not datarec.des.AllDescendants,
2945                                   datarec.des ),
2946              "completely process terminal descendants");
2947    ToPQ(datarec, [ VALUE_PQ_OPTION("Exponent", 0, datarec) ],
2948                  [ "  #exponent" ]); # "Exponent" is a `global' option
2949    ToPQ_BOOL(datarec, VALUE_PQ_OPTION("Metabelian", false, datarec.des),
2950                       "enforce metabelian law");
2951  fi;
2952  datarec.matchlist := [ "group saved on file", "groups saved on file" ];
2953  datarec.matchedlines := [];
2954  if IsRecord(datarec.des.CustomiseOutput) and
2955     not IsEmpty( Intersection( RecNames(datarec.des.CustomiseOutput),
2956                                ["perm", "orbit", "group", "autgroup", "trace"]
2957                                ) ) then
2958    ToPQ(datarec, [ 0 ], [ "  #customise output" ]);
2959    PQ_CUSTOMISE_OUTPUT( datarec, "perm", "perm. grp output",
2960                         ["print degree",
2961                          "print extended auts",
2962                          "print aut. matrices",
2963                          "print permutations"] );
2964    PQ_CUSTOMISE_OUTPUT( datarec, "orbit", "orbit output",
2965                         ["print orbit summary",
2966                          "print complete orbit listing"] );
2967    PQ_CUSTOMISE_OUTPUT( datarec, "group", "group output",
2968                         ["print allowable subgp standard matrix",
2969                          "print pres'n of reduced p-covers",
2970                          "print pres'n of immediate descendants",
2971                          "print nuclear rank of descendants",
2972                          "print p-mult'r rank of descendants"] );
2973    PQ_CUSTOMISE_OUTPUT( datarec, "autgroup", "aut. grp output",
2974                         ["print commutator matrix",
2975                          "print aut. grp descriptions of descendants",
2976                          "print aut. grp orders of descendants"] );
2977    PQ_CUSTOMISE_OUTPUT( datarec, "trace", "provide algorithm trace", [] );
2978  else
2979    ToPQ(datarec, [ 1 ], [ "  #default output" ]);
2980  fi;
2981  if onestage then
2982    ToPQ(datarec, [ VALUE_PQ_OPTION("Filename", "onestage", datarec.des) ],
2983                  [ " #output filename" ]);
2984    Unbind(datarec.des.onestage);
2985  else
2986    if not IsBound(datarec.ndescendants) then
2987      datarec.ndescendants := [];
2988    fi;
2989    totngroups := 0;
2990    for line in datarec.matchedlines do
2991      line := SplitString(line, "", " \n");
2992      ngroups := Int( line[1] );
2993      cls := SplitString( line[ Length(line) ], "", "_" );
2994      cls := Int( cls[2]{[6 .. Length( cls[2] )]} );
2995      datarec.ndescendants[cls] := [ngroups, line[2] = "capable"];
2996      totngroups := totngroups + ngroups;
2997    od;
2998    PQ_UNBIND(datarec, ["matchlist", "matchedlines"]);
2999    return totngroups;
3000  fi;
3001end );
3002
3003#############################################################################
3004##
3005#F  PqPGConstructDescendants( <i> : <options> ) . user ver. of p-G menu op. 5
3006#F  PqPGConstructDescendants( : <options> )
3007##
3008##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
3009##  binary to construct descendants prescribed by <options>, and  return  the
3010##  number of descendants constructed. The options possible are `ClassBound',
3011##  `OrderBound',              `StepSize',               `PcgsAutomorphisms',
3012##  `RankInitialSegmentSubgroups',  `SpaceEfficient',   `CapableDescendants',
3013##  `AllDescendants',     `Exponent',     `Metabelian',     `BasicAlgorithm',
3014##  `CustomiseOutput'. (Detailed descriptions of these options may  be  found
3015##  in Chapter~"ANUPQ Options".)
3016##
3017##  `PqPGConstructDescendants' requires that the `pq' binary  has  previously
3018##  computed a pc presentation and a $p$-cover for  a  $p$-quotient  of  some
3019##  class of the group of the process.
3020##
3021##  *Note:*
3022##  For those  familiar  with  the  `pq'  binary,  `PqPGConstructDescendants'
3023##  performs menu item 5 of the main $p$-Group Generation menu.
3024##
3025InstallGlobalFunction( PqPGConstructDescendants, function( arg )
3026local datarec;
3027  PQ_OTHER_OPTS_CHK("PqPGConstructDescendants", true);
3028  datarec := CallFuncList(ANUPQDataRecord, arg);
3029  return PQ_PG_CONSTRUCT_DESCENDANTS( datarec );
3030end );
3031
3032#############################################################################
3033##
3034#F  PqAPGSupplyAutomorphisms( <i>[, <mlist>] ) . user ver of A p-G menu opt 1
3035#F  PqAPGSupplyAutomorphisms([<mlist>])
3036##
3037#T  This is implemented, but not documented in the manual. There is one line
3038#T  different in the C code between this menu item and the corresponding p-G
3039#T  menu item. I don't understand the difference. - GG
3040##  for the <i>th or default interactive {\ANUPQ} process,  supply  the  `pq'
3041##  binary with the automorphism group data needed  for  the  group  of  that
3042##  process    (for    process    <i>    the    group    is     stored     as
3043##  `ANUPQData.io[<i>].group'). If  the  argument  <mlist>  is  omitted  then
3044##  {\GAP} *must* be able to determine the automorphism group of the group of
3045##  the process. Otherwise the automorphism data  is  provided  from  <mlist>
3046##  which  should  be  a  list  of   matrices   with   non-negative   integer
3047##  coefficients, where  each  matrix  must  have  the  same  dimensions;  in
3048##  particular, the number of rows of each matrix must be  the  rank  of  the
3049##  group of the process.
3050##
3051##  *Note:*
3052##  For those  familiar  with  the  `pq'  binary,  `PqAPGSupplyAutomorphisms'
3053##  performs menu item 1 of the Advanced $p$-Group Generation menu.
3054##
3055InstallGlobalFunction( PqAPGSupplyAutomorphisms, function( arg )
3056local args;
3057  args := PQ_AUT_ARG_CHK(0, arg);
3058  args[1] := ANUPQData.io[ args[1] ];
3059  Add(args, "ApG");
3060  CallFuncList( PQ_PG_SUPPLY_AUTS, args );
3061end );
3062
3063#############################################################################
3064##
3065#F  PqAPGSingleStage( <i> : <options> ) . user version of A p-G menu option 5
3066#F  PqAPGSingleStage( : <options> )
3067##
3068##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
3069##  binary to do a single stage of the descendants construction algorithm  as
3070##  prescribed  by  <options>.   The   possible   options   are   `StepSize',
3071##  `PcgsAutomorphisms',   `RankInitialSegmentSubgroups',   `SpaceEfficient',
3072##  `CapableDescendants',   `AllDescendants',    `Exponent',    `Metabelian',
3073##  `BasicAlgorithm' and `CustomiseOutput'. (Detailed descriptions  of  these
3074##  options may be found in Chapter~"ANUPQ Options".)
3075##
3076##  *Note:*
3077##  For those familiar with  the  `pq'  binary,  `PqAPGSingleStage'  performs
3078##  option 5 of the Advanced $p$-Group Generation menu.
3079##
3080InstallGlobalFunction( PqAPGSingleStage, function( arg )
3081local datarec, ngroups;
3082  PQ_OTHER_OPTS_CHK("PqAPGSingleStage", true);
3083  datarec := CallFuncList(ANUPQDataRecord, arg);
3084  PQ_MENU(datarec, "ApG");
3085  datarec.des.onestage := true;
3086  PQ_PG_CONSTRUCT_DESCENDANTS(datarec);
3087end );
3088
3089#############################################################################
3090##
3091#F  PQ_APG_DEGREE( <datarec>, <step>, <rank> ) . . . . .  A p-G menu option 6
3092##
3093##  inputs data to the `pq' binary for option 6  of  the  Advanced  $p$-Group
3094##  Generation menu, to compute definition sets and find the degree.
3095##
3096InstallGlobalFunction( PQ_APG_DEGREE, function( datarec, step, rank )
3097local expt, line;
3098  expt := VALUE_PQ_OPTION("Exponent", 0, datarec);
3099  PQ_MENU(datarec, "ApG");
3100  ToPQ(datarec, [ 6 ], [ "  #compute defn sets and find degree" ]);
3101  ToPQ(datarec, [ step ], [ " #step size" ]);
3102  ToPQ(datarec, [ rank ], [ " #rank of initial segment subgroup" ]);
3103  datarec.match := "Degree of permutation group";
3104  ToPQ(datarec, [ expt ], [ " #exponent" ]);
3105  line := SplitString(datarec.matchedline, "", " \n");
3106  Unbind(datarec.match);
3107  return Int( line[6] );
3108end );
3109
3110#############################################################################
3111##
3112#F  PqAPGDegree(<i>,<step>,<rank>[: Exponent := <n>]) . u ver A p-G menu op 6
3113#F  PqAPGDegree( <step>, <rank> [: Exponent := <n> ])
3114##
3115##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
3116##  binary  to  compute  definition  sets  and  return  the  degree  of   the
3117##  permutation group. Here the step-size <step> and the rank <rank>  of  the
3118##  initial segment subgroup are positive integers. See~"option Exponent" for
3119##  the one recognised option `Exponent'.
3120##
3121##  *Note:* For those familiar with the `pq' binary,  `PqAPGDegree'  performs
3122##  menu item 6 of the Advanced $p$-Group Generation menu.
3123##
3124InstallGlobalFunction( PqAPGDegree, function( arg )
3125local len, datarec;
3126  PQ_OTHER_OPTS_CHK("PqAPGDegree", true);
3127  len := Length(arg);
3128  if not(len in [2, 3] or ForAll(arg, IsPosInt)) then
3129    Error("expected 2 or 3 positive integer arguments\n");
3130  fi;
3131  datarec := CallFuncList(ANUPQDataRecord, arg{[1 .. len - 2]});
3132  return PQ_APG_DEGREE( datarec, arg[len - 1], arg[len] );
3133end );
3134
3135#############################################################################
3136##
3137#F  PQ_APG_PERMUTATIONS( <datarec> ) . . . . . . . . . .  A p-G menu option 7
3138##
3139##  inputs data to the `pq' binary for option 7  of  the  Advanced  $p$-Group
3140##  Generation menu, to compute permutations of subgroups.
3141##
3142InstallGlobalFunction( PQ_APG_PERMUTATIONS, function( datarec )
3143local pcgsauts, efficient, printauts, printperms;
3144  pcgsauts  := VALUE_PQ_OPTION("PcgsAutomorphisms", false, datarec);
3145  efficient := VALUE_PQ_OPTION("SpaceEfficient", false, datarec.des);
3146  printauts := VALUE_PQ_OPTION("PrintAutomorphisms", false);
3147  printperms := VALUE_PQ_OPTION("PrintPermutations", false);
3148  PQ_MENU(datarec, "ApG");
3149  ToPQ(datarec, [ 7 ], [ "  #compute permutations" ]);
3150  ToPQ_BOOL(datarec, pcgsauts, "compute pcgs gen. seq. for auts.");
3151  ToPQ_BOOL(datarec, efficient, "be space efficient");
3152  ToPQ_BOOL(datarec, printauts, "print automorphism matrices");
3153  ToPQ_BOOL(datarec, printperms, "print permutations");
3154end );
3155
3156#############################################################################
3157##
3158#F  PqAPGPermutations( <i> : <options> ) . user version of A p-G menu optn. 7
3159#F  PqAPGPermutations( : <options> )
3160##
3161##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
3162##  binary to compute permutations of subgroups. Here the  options  <options>
3163##  recognised       are        `PcgsAutomorphisms',        `SpaceEfficient',
3164##  `PrintAutomorphisms' and `PrintPermutations' (see Chapter~"ANUPQ Options"
3165##  for details).
3166##
3167##  *Note:* For those familiar  with  the  `pq'  binary,  `PqAPGPermutations'
3168##  performs menu item 7 of the Advanced $p$-Group Generation menu.
3169##
3170InstallGlobalFunction( PqAPGPermutations, function( arg )
3171local datarec;
3172  PQ_OTHER_OPTS_CHK("PqAPGPermutations", true);
3173  datarec := CallFuncList(ANUPQDataRecord, arg);
3174  PQ_APG_PERMUTATIONS( datarec );
3175end );
3176
3177#############################################################################
3178##
3179#F  PQ_APG_ORBITS( <datarec> ) . . . . . . . . . . . . .  A p-G menu option 8
3180##
3181##  inputs data to the `pq' binary for menu item 8 of the Advanced  $p$-Group
3182##  Generation menu, to compute orbits.
3183##
3184InstallGlobalFunction( PQ_APG_ORBITS, function( datarec )
3185local pcgsauts, efficient, output, summary, listing, line, norbits;
3186  pcgsauts  := VALUE_PQ_OPTION("PcgsAutomorphisms", false, datarec);
3187  efficient := VALUE_PQ_OPTION("SpaceEfficient", false, datarec.des);
3188  output := VALUE_PQ_OPTION("CustomiseOutput", rec(orbit := []), datarec.des);
3189  if not( IsRecord(output) and IsBound(output.orbit) and
3190          IsList(output.orbit) ) then
3191    output := rec(orbit := []);
3192  fi;
3193  summary   := IsBound( output.orbit[1] ) and output.orbit[1] in [1, true];
3194  listing   := IsBound( output.orbit[2] ) and output.orbit[2] in [1, true];
3195  PQ_MENU(datarec, "ApG");
3196  ToPQ(datarec, [ 8 ], [ "  #compute orbits" ]);
3197  ToPQ_BOOL(datarec, pcgsauts, "compute pcgs gen. seq. for auts.");
3198  ToPQ_BOOL(datarec, efficient, "be space efficient");
3199  if summary then
3200    datarec.match := "Number of orbits is";
3201  elif listing then
3202    datarec.match := "Orbit ";
3203  fi;
3204  PQ_APG_CUSTOM_OUTPUT( datarec, "orbit", "orbit output",
3205                        ["print orbit summary",
3206                         "print complete orbit listing"] );
3207  if summary or listing then
3208    line := SplitString(datarec.matchedline, "", " \n");
3209    if summary then
3210      norbits := Int( line[5] );
3211    else
3212      norbits := Int( line[2] );
3213    fi;
3214    Unbind(datarec.match);
3215  else
3216    norbits := "";
3217  fi;
3218  return norbits;
3219end );
3220
3221#############################################################################
3222##
3223#F  PqAPGOrbits( <i> : <options> ) . . .  user version of A p-G menu option 8
3224#F  PqAPGOrbits( : <options> )
3225##
3226##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
3227##  binary to compute the orbit action of the automorphism group, and  return
3228##  the number of orbits, if either a summary or a complete listing (or both)
3229##  of orbit information was requested. Here the options <options> recognised
3230##  are `PcgsAutomorphisms',  `SpaceEfficient',  and  `CustomiseOutput'  (see
3231##  Chapter~"ANUPQ Options" for details). For  the  `CustomiseOutput'  option
3232##  only the setting of the `orbit' is recognised (all other  fields  if  set
3233##  are ignored).
3234##
3235##  *Note:* For those familiar with the `pq' binary,  `PqAPGOrbits'  performs
3236##  menu item 8 of the Advanced $p$-Group Generation menu.
3237##
3238InstallGlobalFunction( PqAPGOrbits, function( arg )
3239local datarec, norbits;
3240  PQ_OTHER_OPTS_CHK("PqAPGOrbits", true);
3241  datarec := CallFuncList(ANUPQDataRecord, arg);
3242  norbits := PQ_APG_ORBITS( datarec );
3243  if norbits <> "" then
3244    return norbits;
3245  fi;
3246end );
3247
3248#############################################################################
3249##
3250#F  PQ_APG_ORBIT_REPRESENTATIVES( <datarec> ) . . . . . . A p-G menu option 9
3251##
3252##  inputs data to the `pq' binary for menu item 9 of the Advanced  $p$-Group
3253##  Generation menu, to process orbit representatives.
3254##
3255InstallGlobalFunction( PQ_APG_ORBIT_REPRESENTATIVES, function( datarec )
3256local pcgsauts, efficient, exponent, metabelian, alldescend, outputfile;
3257  pcgsauts  := VALUE_PQ_OPTION("PcgsAutomorphisms", false, datarec);
3258  efficient := VALUE_PQ_OPTION("SpaceEfficient", false, datarec.des);
3259  exponent  := VALUE_PQ_OPTION("Exponent", false, datarec);
3260  metabelian := VALUE_PQ_OPTION("Metabelian", false, datarec);
3261  alldescend := not VALUE_PQ_OPTION(
3262                        "CapableDescendants",
3263                        VALUE_PQ_OPTION("AllDescendants", true),
3264                        datarec.des);
3265  outputfile := VALUE_PQ_OPTION("Filename", "redPCover", datarec.des);
3266  VALUE_PQ_OPTION("CustomiseOutput", rec(), datarec.des);
3267  PQ_MENU(datarec, "ApG");
3268  ToPQ(datarec, [ 9 ], [ "  #process orbit reps" ]);
3269  ToPQ_BOOL(datarec, pcgsauts, "compute pcgs gen. seq. for auts.");
3270  ToPQ_BOOL(datarec, efficient, "be space efficient");
3271  ToPQ_BOOL(datarec, alldescend, "completely process terminal descendants");
3272  ToPQ(datarec, [ exponent ], [ " #exponent" ]);
3273  ToPQ_BOOL(datarec, metabelian, " set metabelian");
3274  PQ_APG_CUSTOM_OUTPUT( datarec, "group", "group output",
3275                        ["print allowable subgp standard matrix",
3276                         "print pres'n of reduced p-covers",
3277                         "print pres'n of immediate descendants",
3278                         "print nuclear rank of descendants",
3279                         "print p-mult'r rank of descendants"] );
3280  PQ_APG_CUSTOM_OUTPUT( datarec, "autgroup", "aut. grp output",
3281                        ["print commutator matrix",
3282                         "print aut. grp descriptions of descendants",
3283                         "print aut. grp orders of descendants"] );
3284  ToPQ(datarec, [ outputfile ], [ " #output filename" ]);
3285end );
3286
3287#############################################################################
3288##
3289#F  PqAPGOrbitRepresentatives(<i> : <options>) . user ver of A p-G menu opt 9
3290#F  PqAPGOrbitRepresentatives(: <options>)
3291##
3292##  for the <i>th or default interactive {\ANUPQ} process,  direct  the  `pq'
3293##  binary to process  the  orbit  representatives  and  output  the  reduced
3294##  $p$-cover to a file. The options <options> may be any of  the  following:
3295##  are  `PcgsAutomorphisms',  `SpaceEfficient',  `Exponent',   `Metabelian',
3296##  `CapableDescendants' (or `AllDescendants'), `CustomiseOutput' (where only
3297##  the `group' and `autgroup' fields are  recognised)  and  `Filename'  (see
3298##  Chapter~"ANUPQ Options"  for  details).  If  `Filename'  is  omitted  the
3299##  reduced $p$-cover is written to the file `"redPCover"' in  the  temporary
3300##  directory whose name is stored in `ANUPQData.tmpdir'.
3301##
3302##  *Note:*
3303##  For those familiar  with  the  `pq'  binary,  `PqAPGOrbitRepresentatives'
3304##  performs option 9 of the Advanced $p$-Group Generation menu.
3305##
3306InstallGlobalFunction( PqAPGOrbitRepresentatives, function( arg )
3307local datarec;
3308  PQ_OTHER_OPTS_CHK("PqAPGOrbitRepresentatives", true);
3309  datarec := CallFuncList(ANUPQDataRecord, arg);
3310  PQ_APG_ORBIT_REPRESENTATIVES( datarec );
3311end );
3312
3313#############################################################################
3314##
3315#F  PQ_APG_ORBIT_REPRESENTATIVE( <datarec> ) . . . . . . A p-G menu option 10
3316##
3317##  inputs data to the `pq' binary for option 10 of the
3318##  Advanced $p$-Group Generation menu.
3319##
3320InstallGlobalFunction( PQ_APG_ORBIT_REPRESENTATIVE, function( datarec )
3321end );
3322
3323#############################################################################
3324##
3325#F  PqAPGOrbitRepresentative( <i> ) . .  user version of A p-G menu option 10
3326#F  PqAPGOrbitRepresentative()
3327##
3328##  for the <i>th or default interactive {\ANUPQ} process, inputs data
3329##  to the `pq' binary
3330##
3331##  *Note:* For those  familiar  with  the  `pq'  binary,
3332##  `PqAPGOrbitRepresentative' performs option 10 of the
3333##  Advanced $p$-Group Generation menu.
3334##
3335InstallGlobalFunction( PqAPGOrbitRepresentative, function( arg )
3336local datarec;
3337  datarec := CallFuncList(ANUPQDataRecord, arg);
3338  PQ_APG_ORBIT_REPRESENTATIVE( datarec );
3339end );
3340
3341#############################################################################
3342##
3343#F  PQ_APG_STANDARD_MATRIX_LABEL( <datarec> ) . . . . .  A p-G menu option 11
3344##
3345##  inputs data to the `pq' binary for option 11 of the
3346##  Advanced $p$-Group Generation menu.
3347##
3348InstallGlobalFunction( PQ_APG_STANDARD_MATRIX_LABEL, function( datarec )
3349end );
3350
3351#############################################################################
3352##
3353#F  PqAPGStandardMatrixLabel( <i> ) . .  user version of A p-G menu option 11
3354#F  PqAPGStandardMatrixLabel()
3355##
3356##  for the <i>th or default interactive {\ANUPQ} process, inputs data
3357##  to the `pq' binary
3358##
3359##  *Note:* For those  familiar  with  the  `pq'  binary,
3360##  `PqAPGStandardMatrixLabel' performs option 11 of the
3361##  Advanced $p$-Group Generation menu.
3362##
3363InstallGlobalFunction( PqAPGStandardMatrixLabel, function( arg )
3364local datarec;
3365  datarec := CallFuncList(ANUPQDataRecord, arg);
3366  PQ_APG_STANDARD_MATRIX_LABEL( datarec );
3367end );
3368
3369#############################################################################
3370##
3371#F  PQ_APG_MATRIX_OF_LABEL( <datarec> ) . . . . . . . .  A p-G menu option 12
3372##
3373##  inputs data to the `pq' binary for option 12 of the
3374##  Advanced $p$-Group Generation menu.
3375##
3376InstallGlobalFunction( PQ_APG_MATRIX_OF_LABEL, function( datarec )
3377end );
3378
3379#############################################################################
3380##
3381#F  PqAPGMatrixOfLabel( <i> ) . . . . .  user version of A p-G menu option 12
3382#F  PqAPGMatrixOfLabel()
3383##
3384##  for the <i>th or default interactive {\ANUPQ} process, inputs data
3385##  to the `pq' binary
3386##
3387##  *Note:* For those  familiar  with  the  `pq'  binary,
3388##  `PqAPGMatrixOfLabel' performs option 12 of the
3389##  Advanced $p$-Group Generation menu.
3390##
3391InstallGlobalFunction( PqAPGMatrixOfLabel, function( arg )
3392local datarec;
3393  datarec := CallFuncList(ANUPQDataRecord, arg);
3394  PQ_APG_MATRIX_OF_LABEL( datarec );
3395end );
3396
3397#############################################################################
3398##
3399#F  PQ_APG_IMAGE_OF_ALLOWABLE_SUBGROUP( <datarec> ) . .  A p-G menu option 13
3400##
3401##  inputs data to the `pq' binary for option 13 of the
3402##  Advanced $p$-Group Generation menu.
3403##
3404InstallGlobalFunction( PQ_APG_IMAGE_OF_ALLOWABLE_SUBGROUP, function( datarec )
3405end );
3406
3407#############################################################################
3408##
3409#F  PqAPGImageOfAllowableSubgroup( <i> ) user version of A p-G menu option 13
3410#F  PqAPGImageOfAllowableSubgroup()
3411##
3412##  for the <i>th or default interactive {\ANUPQ} process, inputs data
3413##  to the `pq' binary
3414##
3415##  *Note:* For those  familiar  with  the  `pq'  binary,
3416##  `PqAPGImageOfAllowableSubgroup' performs option 13 of the
3417##  Advanced $p$-Group Generation menu.
3418##
3419InstallGlobalFunction( PqAPGImageOfAllowableSubgroup, function( arg )
3420local datarec;
3421  datarec := CallFuncList(ANUPQDataRecord, arg);
3422  PQ_APG_IMAGE_OF_ALLOWABLE_SUBGROUP( datarec );
3423end );
3424
3425#############################################################################
3426##
3427#F  PQ_APG_RANK_CLOSURE_OF_INITIAL_SEGMENT( <datarec> )  A p-G menu option 14
3428##
3429##  inputs data to the `pq' binary for option 14 of the
3430##  Advanced $p$-Group Generation menu.
3431##
3432InstallGlobalFunction( PQ_APG_RANK_CLOSURE_OF_INITIAL_SEGMENT, function( datarec )
3433end );
3434
3435#############################################################################
3436##
3437#F  PqAPGRankClosureOfInitialSegment( <i> )  user version of A p-G menu option 14
3438#F  PqAPGRankClosureOfInitialSegment()
3439##
3440##  for the <i>th or default interactive {\ANUPQ} process, inputs data
3441##  to the `pq' binary
3442##
3443##  *Note:* For those  familiar  with  the  `pq'  binary,
3444##  `PqAPGRankClosureOfInitialSegment' performs option 14 of the
3445##  Advanced $p$-Group Generation menu.
3446##
3447InstallGlobalFunction( PqAPGRankClosureOfInitialSegment, function( arg )
3448local datarec;
3449  datarec := CallFuncList(ANUPQDataRecord, arg);
3450  PQ_APG_RANK_CLOSURE_OF_INITIAL_SEGMENT( datarec );
3451end );
3452
3453#############################################################################
3454##
3455#F  PQ_APG_ORBIT_REPRESENTATIVE_OF_LABEL( <datarec> ) .  A p-G menu option 15
3456##
3457##  inputs data to the `pq' binary for option 15 of the
3458##  Advanced $p$-Group Generation menu.
3459##
3460InstallGlobalFunction( PQ_APG_ORBIT_REPRESENTATIVE_OF_LABEL, function( datarec )
3461end );
3462
3463#############################################################################
3464##
3465#F  PqAPGOrbitRepresentativeOfLabel( <i> )  user version of A p-G menu option 15
3466#F  PqAPGOrbitRepresentativeOfLabel()
3467##
3468##  for the <i>th or default interactive {\ANUPQ} process, inputs data
3469##  to the `pq' binary
3470##
3471##  *Note:* For those  familiar  with  the  `pq'  binary,
3472##  `PqAPGOrbitRepresentativeOfLabel' performs option 15 of the
3473##  Advanced $p$-Group Generation menu.
3474##
3475InstallGlobalFunction( PqAPGOrbitRepresentativeOfLabel, function( arg )
3476local datarec;
3477  datarec := CallFuncList(ANUPQDataRecord, arg);
3478  PQ_APG_ORBIT_REPRESENTATIVE_OF_LABEL( datarec );
3479end );
3480
3481#############################################################################
3482##
3483#F  PQ_APG_WRITE_COMPACT_DESCRIPTION( <datarec> ) . . .  A p-G menu option 16
3484##
3485##  inputs data to the `pq' binary for option 16 of the
3486##  Advanced $p$-Group Generation menu.
3487##
3488InstallGlobalFunction( PQ_APG_WRITE_COMPACT_DESCRIPTION, function( datarec )
3489end );
3490
3491#############################################################################
3492##
3493#F  PqAPGWriteCompactDescription( <i> )  user version of A p-G menu option 16
3494#F  PqAPGWriteCompactDescription()
3495##
3496##  for the <i>th or default interactive {\ANUPQ} process, inputs data
3497##  to the `pq' binary
3498##
3499##  *Note:* For those  familiar  with  the  `pq'  binary,
3500##  `PqAPGWriteCompactDescription' performs option 16 of the
3501##  Advanced $p$-Group Generation menu.
3502##
3503InstallGlobalFunction( PqAPGWriteCompactDescription, function( arg )
3504local datarec;
3505  datarec := CallFuncList(ANUPQDataRecord, arg);
3506  PQ_APG_WRITE_COMPACT_DESCRIPTION( datarec );
3507end );
3508
3509#############################################################################
3510##
3511#F  PQ_APG_AUTOMORPHISM_CLASSES( <datarec> ) . . . . . . A p-G menu option 17
3512##
3513##  inputs data to the `pq' binary for option 17 of the
3514##  Advanced $p$-Group Generation menu.
3515##
3516InstallGlobalFunction( PQ_APG_AUTOMORPHISM_CLASSES, function( datarec )
3517end );
3518
3519#############################################################################
3520##
3521#F  PqAPGAutomorphismClasses( <i> ) . .  user version of A p-G menu option 17
3522#F  PqAPGAutomorphismClasses()
3523##
3524##  for the <i>th or default interactive {\ANUPQ} process, inputs data
3525##  to the `pq' binary
3526##
3527##  *Note:* For those  familiar  with  the  `pq'  binary,
3528##  `PqAPGAutomorphismClasses' performs option 17 of the
3529##  Advanced $p$-Group Generation menu.
3530##
3531InstallGlobalFunction( PqAPGAutomorphismClasses, function( arg )
3532local datarec;
3533  datarec := CallFuncList(ANUPQDataRecord, arg);
3534  PQ_APG_AUTOMORPHISM_CLASSES( datarec );
3535end );
3536
3537#E  anupqi.gi . . . . . . . . . . . . . . . . . . . . . . . . . . . ends here
3538