1#######################################################################
2##  Hecke - specht.gi : the kernel of Hecke                          ##
3##                                                                   ##
4##     A GAP package for calculating the decomposition numbers of    ##
5##     Hecke algebras of type A (over fields of characteristic       ##
6##     zero). The functions provided are primarily combinatorial in  ##
7##     nature. Many of the combinatorial tools from the (modular)    ##
8##     representation theory of the symmetric groups appear in the   ##
9##     package.                                                      ##
10##                                                                   ##
11##     These programs, and the enclosed libraries, are distributed   ##
12##     under the usual licensing agreements and conditions of GAP.   ##
13##                                                                   ##
14##     Dmitriy Traytel                                               ##
15##     (heavily using the GAP3-package SPECHT 2.4 by Andrew Mathas)  ##
16##                                                                   ##
17#######################################################################
18
19## Hecke 1.0: June 2010:
20##   - Translated to GAP4
21
22## SPECHT Change log
23## 2.4:
24##  - fixed more bugs in H.valuation; returned incorrect answers before
25##    when e=0 or e=p (symmetric group case).
26##  - fixed bug in Dq(), via Sasha Kleshchev.
27
28## 2.3:
29##  - fixed bug in H.valuation  reported by Johannes Lipp
30##  - fixed bug in Sq() reported by Johannes Lipp.
31##  - corrected FindDecompositionMatrix() so that it updates the matrices
32##    CrystalMatrices[] and DecompositionMatrices[] after calculating a
33##    crystalized decomposition matrix.
34
35## 2.2: June 1996: various changes requested by the referee.
36##  - mainly changing function names.
37##  - DecompositionMatrix changed so that it no longer attempts to
38##    calculate decomposition matrices in the finite field case; added
39##    CalculateDecompositionMatrix() to do this.
40##  - replaced Matrix() function with MatrixDecompositionMatrix() and
41##    added the function DecompositionMatrixMatix().
42
43## 2.1: April 1996:
44##  - Added a filename argument to SaveDecompositionMatrix and made it
45##    save the non-decomposition matrices under (more) sensible names; the
46##    later is done using the existence of a record component d.matname.
47##    Need to do something here about reading such matrices in (this can be
48##    done using DecompositionMatrix)..
49##  - Changed ReadDecompositionMatrix so that it automatically reads the
50##    format of version 1.0 files (and deleted ReadOldDecompositionMatrix).
51##    Also fixed a bug here which was causing confusion between Hecke algebra
52##    and Schur algebra matrices.
53##  - Renamed FindDecompositionMatrix as KnownDecompositionMatrix because it
54##    doesn't try to calculate a crytalized decomposition matrix; the new
55##    FindDecompositionMatrix will return the decomposition matrix if at all
56##    possible. In particular, this fixes a 'bug' in SimpleDimension.
57##  - Rewrote AdjustmentMatrix so that it actually works.
58##  - Changed P()->S() module conversions so that it no longer requires
59##    the projective module to have positive coefficients (and fixed bug in
60##    matrix ops).
61
62## 2.0: March 1996:
63##   - LLT algorithm implemented for calculating crystal basis of
64##     the Fock space and hence by specialization the decomposition
65##     matrices for all Hecke algebras over fields of characteristic
66##     zero; most of the work is done by the internal function Pq().
67##     This required a new set of 'module' types ("Pq", "Sq", and "Dq"),
68##     with corresponding operation sets H.operations.X. In particular,
69##     these include q-induction and q-restriction, effectively allowing
70##     computations with $U_q(\hat sl_e)$ on the Fock space.
71##   - crystallized decomposition matrices added and decomposition
72##     matrix type overhauled. d.d[c] is now a list of records with
73##     partitions replaced by references to d.rows etc. Changed format
74##     of decomposition matrix library files so as to handle polynomial
75##     entries in the matrices..
76##   - printing of Specht records changed allowing more compact and
77##     readable notation. eg. S(1,1,1,1)->S(1^4). (see SpechtPrintFn).
78##   - reversed order of parts and coeffs records in H.S(), d.d etc;
79##     these lists are now sets which improves use of Position().
80##   - reorganised the Specht function and the record H() which it returns;
81##     in particular added H.info.
82##   - extended SInducedModule() and SRestrict to allow multiple inducing and
83##     restricting (all residues).
84
85## 1.0: December 1995: initial release.
86
87######################################################################
88
89## Here is a description of the structure of the main records used
90## in SPECHT
91#### In GAP4 all "operations"-fields do not exist. They are replaced
92#### by top-level operations with some filter restrictions
93
94## 1. Specht()
95## Specht() is the main function in specht.g, it returns a record 'H'
96## which represents the family of Hecke algebras, or Schur algebras,
97## corresponding to some fixed field <R> and parameter <q>. 'H' has
98## the components:
99##   IsSpecht      : is either 'true' or 'false' depending on whether
100##                   'H' is a Hecke algebra or Schur algebra resp.
101#### This function is obsolete in the GAP4 version - it is replaced
102#### by the filter IsHecke
103##   S(), P(), D() : these three functions return records which
104##                   represent Specht modules, PIMs, and simple
105##                   'H' modules respectively. These functions exist
106##                   only when 'H' is a Hecke algebra record.
107#### Use MakeSpecht(H,...) instead of H.S(...)
108##   W(), P(), F() : these are the corresponding functions for Weyl
109##                   modules, PIMs, and simple modules of Schur algbras.
110#### Use MakeSpecht(S,...) instead of S.W(...)
111##   info          : this is a record with components
112##                     version: SPECHT version number,
113##                     Library: path to SPECHT library files
114##                     SpechtDirectory: addition directory searched by
115##                            SPECHT (defaults to current directory)
116##                     Indeterminate: the indeterminate used by SPECHT
117##                            in the LLT algorithm when H.p=0.
118##   operations    : apart from the obvious things like the Print()
119##                   function for 'H' this record also contains the
120##                   operation records for the modules S(), P() etc.
121##                   as well as functions for manipulating these records
122##                   and accessing decomposition matrix files. The most
123##                   most important of these are:
124##                     S, P, D, Pq, Sq, Dq : operations records for modules
125#### Most functions are now on toplevel
126##                     New : creation function for modules. Internally
127##                       modules are created via
128##                         H.operations.new(module,coeffs,parts)
129##                       where module is one of "S", "P", "D", "Sq", "Pq",
130##                       or "Dq" ("S" and "D" are used even for Schur
131##                       algebras), coeffs is an integer or a *set* of
132##                       integers and parts is a partition or a *set* of
133##                       partitions. In any programs the use of New is
134##                       better than H.S(mu), for example, because the
135##                       function names are different for Hecke and Schur
136##                       algebras. Note that coeffs and parts must be
137##                       ordered reverse lexicographically (ie. they are
138##                       *sets*).
139#### Use Module(H,...) instead of H.operations.New(...)
140##                     Collect: like New() except that  coeffs and parts
141##                       need not be sets (and may contain repeats).
142#### Use Collect(H,...) instead of H.operations.Collect(...)
143##                     NewDecompositionMatrix : creates a decomposition
144##                       matrix.
145#### Use ReadDecompositionMatrix(H,...) instead of H.operations.ReadDecompositionMatrix(...)
146##                     ReadDecompositionMatrix : reads, and returns, a
147##                       decomposition matrix file.
148#### Use KnownDecompositionMatrix(H,...) instead of H.operations.KnownDecompositionMatrix(...)
149##                     KnownDecompositionMatrix : returns a decomposition
150##                       matrix of a given size; will either extract this
151##                       matrix from Specht's internal lists or call
152##                       ReadDecompositionMatrix(), or try to calculate
153##                       the decomposition matrix (without using the
154##                       crystalized decomposition matrices).
155#### Use FindDecompositionMatrix(H,...) instead of H.operations.FindDecompositionMatrix(...)
156##                     FindDecompositionMatrix : like KnownDM except that
157##                       it will calculate the crystalized DM if needed.
158##   Ordering      : a function for ordering partitions; controls how
159##                   decomposition matrices for H are printed.
160#### Use SetOrdering(...) to control the output
161##   e             : order of <q> in <R>
162#### Use OrderOfQ(...) to extract the e from an algebra or a module
163#### corresponding to an algebra
164##   p             : characteristic of <R>
165##   valuation     : the valuation map of [JM2]; used primarily by
166##                   the q-Schaper theorem.D
167##   HeckeRing     : bookkeeping string used primarily in searching for
168##                   library files.
169##   Pq(), Sq()    : Functions for computing elements of the Fock space
170##                   when H.p=0 (used in LLT algorithm). Note that there is
171##                   no Dq; also unlike their counter parts S(), P(), and
172##                   D() they accept only partitions as arguments.
173#### Use MakeFockPIM(H,...) instead of H.Pq(...)
174#### Use MakeFockSpecht(H,...) instead of H.Sq(...)
175##
176## 2. The module functions S(), P() and D() (and Schur equivalents)
177## These functions return record 'x' which represents some 'H'--module.
178## 'x' is a record with the following components:
179##   H      : a pointer back to the corresponding algebra
180##   module : one of "S", "P", "D", "Sq", "Pq", or "Dq", (not "W", or "F").
181##   coeffs : a *set* of coefficients
182##   parts  : the corresponding *set* of partitions
183##   operations :
184##       + - * / : for algebraic manipulations
185##       Print : calls PrintModule
186##       Coefficient : returns the coefficient of a given partition
187#### Use Coefficient(x,...) instead of x.operations.Coefficient(...)
188##       PositiveCoefficients : true if all coefficients are non-negative
189##       IntegralCoefficients : true if all coefficients are integral
190##       InnerProduct : computes the 'Kronecker' inner product
191##       Induce, Restrict, SInduce, SRestrict : induction and restriction
192##                 functions taylored to 'x'. These functions convert 'x'
193##                 to a linear combination of Specht modules, induce and
194##                 then convert back to the type of 'x' (if possible).
195##                 Quantized versions are applied as appropriate.
196##       S, P, D : functions for rewriting 'x' into the specified type
197##                 (so, for example, S('x') rewrites 'x' as a linear
198##                 combination of Specht modules).
199## 'x'.operations is a pointer to 'H'.operations.('x'.module).
200##
201## 3. DecompositionMatrices
202## Decomposition matrices 'd' in Specht are represented as records with the
203## following components:
204##
205##   d : a list, indexed by d.cols, where each entry is a record
206##       corresponding to a column of 'd'; this record has components
207##       two * sets* coeffs and parts, where parts is the index of the
208##       corresponding partition in d.rows.
209##   rows : the *set* of the partitions which make up the rows or 'd'.
210##   cols : the *set* of the partitions which make up the rows or 'd'.
211##   inverse : a list of records containing the inverse of 'd'. These
212##          records are computed only as needed.
213##   dimensions : a list of the dimensions of the simple modules; again
214##          computed only as needed.
215##   IsDecompositionMatrix : false if 'd' is a crystallized decomposition
216##          matrix, and true otherwise.
217##   H :a pointer back to the corresponding algebra
218##   operations :
219##     = : equality.
220##     Print, TeX, Matrix : printing, TeX, and a GAP Matrix.
221##     AddIndecomposable : for adding a PIM to 'd'.
222##     Store : for updating Specht's internal record of 'd'.
223##     S, P, D: for accessing the entries of 'd' and using 'd' to
224##              convert between the various types of 'H'--modules.
225##              These are actually records, each containing three
226##              functions S(), P(), and D(); so X.Y() tells 'd' how
227##              to write an X-module as a linear combination of Y-modules.
228##     Invert : calculates D(mu) using 'd'.
229##     IsNewIndecomposable : the heart of the 'IsNewIndecomposable'
230##              function.
231##     Induce : for inducing decomposition matrices (non--crystallized).
232##   P : a short-hand for d.H.P('d',<mu>).
233
234###########################################################################
235
236## Specht() is the main function in the package, although in truth it is
237## little more than a wrapper for the functions S(), P(), and D().
238## Originally, I had these as external functions, but decided that it
239## was better to tie these functions to e=H.e as strongly as possible.
240InstallMethod(Specht_GenAlgebra,"generate a type-Algebra object",
241  [IsString,IsInt,IsInt,IsFunction,IsString],
242  function(type,e,p,valuation,HeckeRing)
243    local H;
244    if not IsPrime(p) and p<>0
245    then Error("Specht(<e>,<p>,<val>), <p> must be a prime number");
246    fi;
247
248    H := rec(
249      e:=e,
250      p:=p,
251      valuation:=valuation,
252      HeckeRing:=HeckeRing,
253      ## bits and pieces about H
254      info:=rec(version:=PackageInfo("hecke")[1].Version,
255                Library:=Directory(
256                  Concatenation(DirectoriesPackageLibrary("hecke")[1]![1],"e",
257                  String(e),"/")),
258      ## We keep a copy of SpechtDirectory in H so that we have a
259      ## chance of finding new decomposition matrices when it changes.
260                SpechtDirectory:=Directory(".")),
261
262      ## This record will hold any decomposition matrices which Specht()
263      ## (or rather its derivatives) read in. This used to be a public
264      ## record; it is now private because q-Schur algebra matrices and
265      ## Hecke algebra matrices might need to coexist.
266      DecompositionMatrices:=[],
267
268      ## for ordering the rows of the decomposition matrices
269      ## (as it is common to all decomposition matrices it lives here)
270      Ordering:=Lexicographic,
271    );
272
273    if p = 0
274    then
275      ## This list will hold the crystallized decomposition matrices (p=0)
276      H.CrystalMatrices:=[];
277      H.Indeterminate:=Indeterminate(Integers);
278      SetName(H.Indeterminate,"v");
279    else H.Indeterminate:=1;
280    fi;
281
282    if type = "Schur" then
283      Objectify(SchurType,H);
284    else
285      Objectify(HeckeType,H);
286    fi;
287
288    return H;
289  end
290);
291
292InstallMethod(Specht_GenAlgebra,"generate a type-Algebra object",
293  [IsString,IsInt,IsInt,IsFunction],
294  function(type,e,p,val) local ring;
295    if not IsPrime(p)
296    then Error("Specht(<e>,<p>,<val>), <p> must be a prime number");
297    fi;
298    if e=p then
299      ring:=Concatenation("p",String(p),"sym");
300      return Specht_GenAlgebra(type,e,p,val,ring);
301    else
302      return Specht_GenAlgebra(type,e,p,val,"unknown");
303    fi;
304  end
305);
306
307InstallMethod(Specht_GenAlgebra,"generate a type-Algebra object",
308  [IsString,IsInt,IsInt],
309  function(type,e,p) local val, ring;
310    if not IsPrime(p)
311    then Error("Specht(<e>,<p>,<val>), <p> must be a prime number");
312    fi;
313    if e=p then
314      ring:=Concatenation("p",String(p),"sym");
315      ## return the exponent of the maximum power of p dividing x
316      val:=function(x) local i;
317        i:=0;
318        while x mod p=0 do
319          i:=i+1;
320          x:=x/p;
321        od;
322        return i;
323      end;
324    else
325      ring:=Concatenation("e",String(e), "p",String(p));
326      ## return the exponent of the maximum power of p that
327      ## divides e^x-1.
328      val:=function(x) local i;
329        if x mod e=0 then return 0;
330        else
331          i:=0;
332          while x mod p=0 do
333            i:=i+1;
334            x:=x/p;
335          od;
336          return p^i;
337        fi;
338      end;
339    fi;
340    return Specht_GenAlgebra(type,e,p,val,ring);
341  end
342);
343
344InstallMethod(Specht_GenAlgebra,"generate a type-Algebra object",
345  [IsString,IsInt],
346  function(type,e) local val;
347      if e=0 then val:=x->x;
348      else
349        val:=function(x)
350          if x mod e = 0 then return 1;
351          else return 0;
352          fi;
353        end;
354      fi;
355      return Specht_GenAlgebra(type,e,0,val,Concatenation("e",String(e), "p0"));
356  end
357);
358
359InstallMethod(Specht,"generate a Hecke-Algebra object",[IsInt],
360  function(e) return Specht_GenAlgebra("Specht",e); end
361);
362InstallMethod(Specht,"generate a Hecke-Algebra object",[IsInt,IsInt],
363  function(e,p) return Specht_GenAlgebra("Specht",e,p); end
364);
365InstallMethod(Specht,"generate a Hecke-Algebra object",[IsInt,IsInt,IsFunction],
366  function(e,p,val) return Specht_GenAlgebra("Specht",e,p,val); end
367);
368InstallMethod(Specht,"generate a Hecke-Algebra object",[IsInt,IsInt,IsFunction,IsString],
369  function(e,p,val,ring) return Specht_GenAlgebra("Specht",e,p,val,ring); end
370);
371InstallMethod(Schur,"generate a Schur-Algebra object",[IsInt],
372  function(e) return Specht_GenAlgebra("Schur",e); end
373);
374InstallMethod(Schur,"generate a Schur-Algebra object",[IsInt,IsInt],
375  function(e,p) return Specht_GenAlgebra("Schur",e,p); end
376);
377InstallMethod(Schur,"generate a Schur-Algebra object",[IsInt,IsInt,IsFunction],
378  function(e,p,val) return Specht_GenAlgebra("Schur",e,p,val); end
379);
380InstallMethod(Schur,"generate a Schur-Algebra object",[IsInt,IsInt,IsFunction,IsString],
381  function(e,p,val,ring) return Specht_GenAlgebra("Schur",e,p,val,ring); end
382);
383
384InstallImmediateMethod(Characteristic, IsAlgebraObj, 0,
385  function(H) return H!.p; end
386);
387
388InstallImmediateMethod(IsZeroCharacteristic, IsAlgebraObj, 0,
389  function(H) return H!.p = 0; end
390);
391
392InstallImmediateMethod(OrderOfQ, IsAlgebraObj, 0,
393  function(H) return H!.e; end
394);
395
396InstallImmediateMethod(OrderOfQ, IsAlgebraObjModule, 0,
397  function(x) return x!.H!.e; end
398);
399
400InstallMethod(SetOrdering,"writing access to H.Ordering",
401  [IsAlgebraObj,IsFunction],
402  function(H,ord) H!.Ordering := ord; end
403);
404
405InstallMethod(SpechtCoefficients,"reading access to S.coeffs",[IsHeckeSpecht],
406  function(S) return S!.coeffs; end
407);
408
409InstallMethod(SpechtPartitions,"reading access to S.parts",[IsHeckeSpecht],
410  function(S) return S!.parts; end
411);
412
413## FORMER TOPLEVEL FUNCTIONS ###################################################
414#F Calculates the dimensions of the simple modules in d
415## Usage:  SimpleDimension(d)   -> prints all simple dimensions
416##         SimpleDimension(H,n) -> prints all again
417##         SimpleDimension(H,mu) or SimpleDimension(d,mu) -> dim D(mu)
418InstallMethod(SimpleDimensionOp,
419  "all simple dimensions from decomposition matrix",[IsDecompositionMatrix],
420  function(d) local cols, collabel, M, c, x;
421    if IsSchur(d!.H) then
422      Print("# SimpleDimension() not implemented for Schur algebras\n");
423      return fail;
424    fi;
425    cols:=StructuralCopy(d!.cols);
426    if d!.H!.Ordering=Lexicographic then
427      cols:=cols{[Length(cols),Length(cols)-1..1]};
428    else Sort(cols, d!.H!.Ordering);
429    fi;
430    cols:=List(cols, c->Position(d!.cols,c));
431    collabel:=List([1..Length(cols)], c->LabelPartition(d!.cols[cols[c]]));
432    M:=Maximum(List(collabel, Length))+1;
433
434    for c in [1..Length(cols)] do
435      Print(String(collabel[c],-M),": ");
436      if IsBound(d!.dimensions[cols[c]]) then
437        Print(d!.dimensions[cols[c]],"\n");
438      else
439        x:=MakeSimpleOp(d,d!.cols[cols[c]]);
440        if x=fail then Print("not known\n");
441        else
442          d!.dimensions[cols[c]]:=Sum([1..Length(x!.parts)],
443                             r->x!.coeffs[r]*SpechtDimension(x!.parts[r]));
444          Print(d!.dimensions[cols[c]],"\n");
445        fi;
446      fi;
447    od;
448    return true;
449  end
450);
451
452InstallMethod(SimpleDimensionOp,
453  "simple dimensions of a partition from decomposition matrix",
454  [IsDecompositionMatrix,IsList],
455  function(d,mu) local c, x;
456    c:=Position(d!.cols,mu);
457    if c=fail then
458      Print("# SimpleDimension(<d>,<mu>), <mu> is not in <d>.cols\n");
459      return fail;
460    else
461      if not IsBound(d!.dimensions[c]) then
462        x:=MakeSimpleOp(d,d!.cols[c]);
463        if x=fail then return fail;
464        else d!.dimensions[c]:=Sum([1..Length(x!.parts)],
465                            r->x!.coeffs[r]*SpechtDimension(x!.parts[r]));
466        fi;
467      fi;
468      return d!.dimensions[c];
469    fi;
470  end
471);
472
473InstallMethod(SimpleDimensionOp,
474  "all simple dimensions from algebra",[IsAlgebraObj,IsInt],
475  function(H,n) local d;
476    d:=FindDecompositionMatrix(H,n);
477    if d=fail then
478      Print("# SimpleDimension(H,n), the decomposition matrix of H_n is ",
479            "not known.\n");
480      return fail;
481    fi;
482    return SimpleDimensionOp(d);
483  end
484);
485
486InstallMethod(SimpleDimensionOp,
487  "simple dimensions of a partition from algebra",[IsAlgebraObj,IsList],
488  function(H,mu) local d;
489    d:=FindDecompositionMatrix(H,Sum(mu));
490    if d=fail then
491      Print("# SimpleDimension(H,mu), the decomposition matrix of H_Sum(mu) is",
492            " not known.\n");
493      return fail;
494    fi;
495    return SimpleDimensionOp(d,mu);
496  end
497); # SimpleDimension
498
499#P returns a list of the e-regular partitions occurring in x
500InstallMethod(ListERegulars,"e-regular partitions of a module",
501  [IsAlgebraObjModule],
502  function(x) local e,parts,coeffs,p;
503    e:=x!.H!.e;
504    parts:=x!.parts;
505    coeffs:=x!.coeffs;
506    if e=0 then return parts;
507    elif x=0*x then return [];
508    else return List(Filtered([Length(parts),Length(parts)-1..1],
509           p->IsERegular(e,parts[p])),p->[coeffs[p], parts[p]]);
510    fi;
511  end
512); # ListERegulars
513
514
515##P Print the e-regular partitions in x if IsSpecht(x); on the other hand,
516### if IsDecompositionMatrix(x) then return the e-regular part of the
517### decomposition matrix.
518InstallMethod(ERegulars,"e-regular part of the given decomposition matrix",
519  [IsDecompositionMatrix],
520  function(d) local regs, y, r, len;
521    regs:=DecompositionMatrix(d!.H,d!.rows,d!.cols,not IsCrystalDecompositionMatrix(d));
522    regs!.d:=[]; #P returns a list of the e-regular partitions occurring in x
523    for y in [1..Length(d!.cols)] do
524      if IsBound(d!.d[y]) then
525        regs!.d[y]:=rec(parts:=[], coeffs:=[]);
526        for r in [1..Length(d!.d[y].parts)] do
527          len:=Position(d!.cols,d!.rows[d!.d[y].parts[r]]);
528          if len<>fail then
529            Add(regs!.d[y].parts,len);
530            Add(regs!.d[y].coeffs,d!.d[y].coeffs[r]);
531          fi;
532        od;
533      fi;
534    od;
535    regs!.rows:=regs!.cols;
536    return regs;
537  end
538);
539
540InstallMethod(ERegulars, "print e-regular partitions of a module",
541  [IsAlgebraObjModule],
542  function(x) local len, regs, y;
543    len:=0;
544    regs:=ListERegulars(x);
545    if regs=[] or IsInt(regs[1]) then Print(regs, "\n");
546    else
547      for y in regs do
548        if (len + 5 + 4*Length(y[2])) > 75 then len:=0; Print("\n"); fi;
549        if y[1]<>1 then Print(y[1], "*"); len:=len + 3; fi;
550        Print(y[2], "  ");
551        len:=len + 5 + 4*Length(y[2]);
552      od;
553      Print("\n");
554    fi;
555  end
556); # ERegulars
557
558#F Returns true if S(mu)=D(mu) - note that this implies that mu is e-regular
559## (if mu is not e-regular, fail is returned).     -- see [JM2]
560## IsSimple(H,mu)
561##   ** uses H.valuation
562InstallMethod(IsSimpleModuleOp,
563  "test whether the given partition defines a simple module",
564  [IsAlgebraObj,IsList],
565  function(H,mu) local mud, simple, r, c, v;
566    if not IsERegular(H!.e,mu) then return false;
567    elif mu=[] then return true; fi;
568
569    mud:=ConjugatePartition(mu);
570    simple:=true; c:=1;
571    while simple and c <=mu[1] do
572      v:=H!.valuation(mu[1]+mud[c]-c);
573      simple:=ForAll([2..mud[c]], r->v=H!.valuation(mu[r]+mud[c]-c-r+1));
574      c:=c+1;
575    od;
576    return simple;
577  end
578); #IsSimpleModule
579
580#F Split an element up into components which have the same core.
581## Usage: SplitECores(x) - returns as list of all block components
582##        SplitECores(x,lambda) - returns a list with (i) core lambda,
583## (ii) the same core as lambda, or (iii) the same core as the first
584## element in lambda if IsSpecht(lambda).
585InstallMethod(SplitECoresOp,"for a single module",[IsAlgebraObjModule],
586  function(x) local cores, c, cpos, y, cmp;
587    if x=fail or x=0*x then return []; fi;
588
589    cores:=[]; cmp:=[];
590    for y in [1..Length(x!.parts)] do
591      c:=ECore(x!.H!.e, x!.parts[y]);
592      cpos:=Position(cores, c);
593      if cpos=fail then
594        Add(cores, c);
595        cpos:=Length(cores);
596        cmp[cpos]:=[[],[]];
597      fi;
598      Add(cmp[cpos][1], x!.coeffs[y]);
599      Add(cmp[cpos][2], x!.parts[y]);
600    od;
601    for y in [1..Length(cmp)] do
602      cmp[y]:=Module(x!.H,x!.module,cmp[y][1],cmp[y][2]);
603    od;
604    return cmp;
605  end
606);
607
608InstallMethod(SplitECoresOp,"for a module and a partition",
609  [IsAlgebraObjModule,IsList],
610  function(x,mu) local c, cpos, y, cmp;
611    c:=ECore(x!.H!.e, mu);
612    cmp:=[ [],[] ];
613    for y in [1..Length(x!.parts)] do
614      if ECore(x!.H!.e, x!.parts[y])=c then
615        Add(cmp[1], x!.coeffs[y]);
616        Add(cmp[2], x!.parts[y]);
617      fi;
618    od;
619    cmp:=Module(x!.H,x!.module, cmp[1], cmp[2]);
620    return cmp;
621  end
622);
623
624InstallMethod(SplitECoresOp,"for a module and a specht module",
625  [IsAlgebraObjModule,IsAlgebraObjModule],
626  function(x,s) local c, cpos, y, cmp;
627    c:=ECore(s!.H!.e, s!.parts[Length(x!.parts)]);
628    cmp:=[ [],[] ];
629    for y in [1..Length(x!.parts)] do
630      if ECore(x!.H!.e, x!.parts[y])=c then
631        Add(cmp[1], x!.coeffs[y]);
632        Add(cmp[2], x!.parts[y]);
633      fi;
634    od;
635    cmp:=Module(x!.H,x!.module, cmp[1], cmp[2]);
636    return cmp;
637  end
638); #SplitECores
639
640#F This function returns the image of <mu> under the Mullineux map using
641## the Kleshcehev(-James) algorithm, or the supplied decomposition matrix.
642## Alternatively, given a "module" x it works out the image of x under
643## Mullineux.
644## Usage:  MullineuxMap(e|H|d, mu) or MullineuxMap(x)
645InstallMethod(MullineuxMapOp,"image of x under Mullineux",[IsAlgebraObjModule],
646  function(x) local e, v;
647    e := x!.H!.e;
648    if x=fail or not IsERegular(e,x!.parts[Length(x!.parts)]) then
649      Print("# The Mullineux map is defined only for e-regular partitions\n");
650      return fail;
651    fi;
652    if x=fail or x=0*x then return fail; fi;
653    if IsHeckeSpecht(x) then
654      if Length(x!.module)=1 then
655        return Collect(x!.H,x!.module,x!.coeffs,
656                 List(x!.parts, ConjugatePartition));
657      else
658        v:=x!.H!.info.Indeterminate;
659        return Collect(x!.H,x!.module,
660             List([1..Length(x!.coeffs)],
661                mu->Value(v^-EWeight(e,x!.parts[mu])*x!.coeffs[mu],v^-1)),
662             List(x!.parts,ConjugatePartition) );
663      fi;
664    elif Length(x!.module)=1 then
665      return Sum([1..Length(x!.coeffs)],
666               mu->Module(x!.H,x!.module,x!.coeffs[mu],
667                     MullineuxMap(e,x!.parts[mu])));
668    else
669      v:=x!.H!.info.Indeterminate;
670      return Sum([1..Length(x!.coeffs)],
671               mu->Module(x!.H,x!.module,
672                     Value(v^-EWeight(e,x!.parts[mu])*x!.coeffs[mu]),
673                     MullineuxMap(e,x!.parts[mu])));
674    fi;
675  end
676);
677
678InstallMethod(MullineuxMapOp,"for ints: image of <mu> under the Mullineux map",
679  [IsInt,IsList],
680  function(e,mu)
681    if not IsERegular(e,mu) then                     ## q-Schur algebra
682      Error("# The Mullineux map is defined only for e-regular ",
683            "partitions\n");
684    fi;
685    return PartitionGoodNodeSequence(e,
686                  List(GoodNodeSequence(e,mu),x->-x mod e));
687  end
688);
689
690InstallMethod(MullineuxMapOp,
691  "for algebras: image of <mu> under the Mullineux map",
692  [IsAlgebraObj,IsList],
693  function(H,mu)
694    return MullineuxMapOp(H!.e,mu);
695  end
696);
697
698InstallMethod(MullineuxMapOp,
699  "for decomposition matrices: image of <mu> under the Mullineux map",
700  [IsDecompositionMatrix,IsList],
701  function(d,mu) local e, x;
702    e := d!.H!.e;
703    if not IsERegular(e,mu) then                     ## q-Schur algebra
704      Error("# The Mullineux map is defined only for e-regular ",
705            "partitions\n");
706    fi;
707    x:=d!.H!.P(d,mu);
708    if x=fail or x=0*x then
709      Print("MullineuxMap(<d>,<mu>), P(<d>,<mu>) not known\n");
710      return fail;
711    else return ConjugatePartition(x!.parts[1]);
712    fi;
713    return true;
714  end
715); # MullineuxMap
716
717#F Calculates the Specht modules in sum_{i>0}S^lambda(i) using the
718## q-analogue of Schaper's theorem.
719## Uses H.valuation.
720##   Usage:  Schaper(H,mu);
721InstallMethod(SchaperOp,"calculates Specht modules",[IsAlgebraObj,IsList],
722  function(H,mu)
723    local mud, schaper, hooklen, c, row, r, s, v;
724
725    Sort(mu); mu:=mu{[Length(mu),Length(mu)-1..1]};
726    mud:=ConjugatePartition(mu);
727    hooklen:=[];
728    for r in [1..Length(mu)] do
729      hooklen[r]:=[];
730      for c in [1..mu[r]] do
731        hooklen[r][c]:=mu[r] + mud[c] - r - c + 1;
732      od;
733    od;
734
735    schaper:=Module(H,"S",0,[]);
736    for c in [1..mu[1]] do
737      for row in [1..mud[1]] do
738        for r in [row+1..mud[1]] do
739          if mu[row] >=c and mu[r] >=c then
740            v:=H!.valuation(hooklen[row][c])
741                  - H!.valuation(hooklen[r][c]);
742            if v<>0 then
743              s:=AddRimHook(RemoveRimHook(mu,r,c,mud),row,hooklen[r][c]);
744              if s<>fail then
745                schaper:=schaper+Module(H,"S",
746                                    (-1)^(s[2]+mud[c]-r)*v,s[1]);
747              fi;
748            fi;
749          fi;
750        od;
751      od;
752    od;
753    return schaper;
754  end
755);  #Schaper
756
757#F returns the matrix of upper bounds on the entries in the decomposition
758## matrix <d> given by the q-Schaper theorem
759## *** undocumented
760InstallMethod(SchaperMatrix,"upper bounds of entries of a decomposition matrix",
761  [IsDecompositionMatrix],
762  function(d) local r, C, c, coeff, sh, shmat;
763    shmat:=DecompositionMatrix(d!.H,d!.rows,d!.cols,true);
764    shmat!.d:=List(shmat!.cols, c->rec(parts:=[],coeffs:=[]));
765    C:=Length(d!.cols)+1; ## this keeps track of which column we're up to
766    for r in [Length(d!.rows),Length(d!.rows)-1..1] do
767      if d!.rows[r] in d!.cols then C:=C-1; fi;
768      sh:=Schaper(d!.H,d!.rows[r]);
769      for c in [C..Length(d!.cols)] do
770        coeff:=InnerProduct(sh,MakePIMSpechtOp(d,d!.cols[c]));
771        if coeff<>fail and coeff<>0*coeff then
772          Add(shmat!.d[c].parts,r);
773          Add(shmat!.d[c].coeffs,coeff);
774        fi;
775      od;
776    od;
777    sh:=[];
778    for c in [1..Length(d!.d)] do
779      Add(shmat!.d[c].parts, Position(shmat!.rows,shmat!.cols[c]));
780      Add(shmat!.d[c].coeffs,1);
781    od;
782    shmat!.matname:="Schaper matrix";
783    return shmat;
784  end
785);
786
787## FORMER DECOMPOSITION MATRICES TOPLEVEL FUNCTIONS ############################
788##############################################################
789## Next some functions for accessing decomposition matrices ##
790##############################################################
791
792#F Returns the decomposition number d_{mu,nu}; row and column removal
793## are used if the projective P(nu) is not already known.
794## Usage: DecompositionNumber(H,mu,nu), or
795##        DecompositionNumber(d,mu,nu);
796## If unable to calculate the decomposition number we return false.
797## Note that H.IsSpecht is false if we are looking at decomposition matrices
798## of a q-Schur algebra and true for a Hecke algebra.
799InstallMethod(DecompositionNumber,
800  "for a decomposition matrix and two partitions",
801  [IsDecompositionMatrix,IsList,IsList],
802  function(d,mu,nu) local Pnu;
803    if mu=nu then return 1;
804    elif not Dominates(nu,mu) then return 0;
805    else
806      Pnu:=MakePIMSpechtOp(d,nu);
807      if Pnu<>fail then return Coefficient(Pnu,mu); fi;
808      return Specht_DecompositionNumber(d!.H,mu,nu);
809    fi;
810  end
811);
812
813InstallMethod(DecompositionNumber,"for an algebra and two partitions",
814  [IsAlgebraObj,IsList,IsList],
815  function(H,mu,nu) local Pnu;
816    Pnu:=MakeSpechtOp(Module(H,"P",1,nu),true);
817    if Pnu<>fail then return Coefficient(Pnu,mu); fi;
818    if not IsSchur(H) and not IsERegular(H!.e, nu) then
819      Error("DecompositionNumber(H,mu,nu), <nu> is not ",H!.e,"-regular");
820    fi;
821    return Specht_DecompositionNumber(H,mu,nu);
822  end
823);
824
825InstallMethod(Specht_DecompositionNumber,
826  "internal: for an algebra and two partitions",
827  [IsAlgebraObj,IsList,IsList],
828  function(H,mu,nu) local Pnu, RowAndColumnRemoval;
829
830    ## Next we try row and column removal (James, Theorem 6.18)
831    ## (here fn is either the identity or conjugation).
832    RowAndColumnRemoval:=function(fn) local m,n,i,d1,d2;
833      ## x, mu, and nu as above
834
835      mu:=fn(mu); nu:=fn(nu);
836
837      m:=0; n:=0; i:=1;
838      while i<Length(nu) and i<Length(mu) do
839        m:=m+mu[i]; n:=n+nu[i];
840        if m=n then
841          d2:=DecompositionNumber(H, fn(mu{[i+1..Length(mu)]}),
842                     fn(nu{[i+1..Length(nu)]}));
843          if d2=0 then return d2;
844          elif IsInt(d2) then
845            d1:=DecompositionNumber(H, fn(mu{[1..i]}),fn(nu{[1..i]}));
846            if IsInt(d1) then return d1*d2; fi;
847          fi;
848        fi;
849        i:=i+1;
850      od;
851      return fail;
852    end;
853
854    Pnu:=RowAndColumnRemoval(a->a);
855    if Pnu=fail then Pnu:=RowAndColumnRemoval(ConjugatePartition); fi;
856    return Pnu;
857  end
858);
859
860#F Returns a list of those e-regular partitions mu such that Px-P(mu)
861## has positive coefficients (ie. those partitions mu such that P(mu)
862## could potentially split off Px). Simple minded, but useful.
863InstallMethod(Obstructions,"for a decomposition matrix and a module",
864  [IsDecompositionMatrix,IsAlgebraObjModule],
865  function(d,Px) local obs, mu, Pmu, possibles;
866    obs:=[];
867    if not IsSchur(d!.H) then
868      possibles:=Filtered(Px!.parts, mu->IsERegular(Px!.H!.e, mu));
869    else possibles:=Px!.parts;
870    fi;
871    for mu in possibles do
872      if mu<>Px!.parts[Length(Px!.parts)] then
873        Pmu:=MakePIMSpechtOp(d,mu);
874        if Pmu=fail or PositiveCoefficients(Px-Pmu) then Add(obs,mu); fi;
875      fi;
876    od;
877    return obs{[Length(obs),Length(obs)-1..1]};
878  end
879);
880
881## Interface to d.operations.IsNewDecompositionMatrix. Returns true
882## if <Px> contains an indecomposable not listed in <d> and false
883## otherwise. Note that the value of <Px> may well be changed by
884## this function. If the argument <mu> is used then we assume
885## that all of the decomposition numbers down given by <Px> down to
886## <mu> are correct. Note also that if d is the decomposition matrix
887## for H(Sym_{r+1}) then the decomposition matrix for H(Sym_r) is passed
888## to IsNewDecompositionMatrix.
889##   Usage: IsNewIndecomposable(<d>,<Px> [,<mu>]);
890## If <mu> is not supplied then we set mu:=true; this
891## turns on the message printing in IsNewIndecomposable().
892InstallMethod(IsNewIndecomposableOp,
893  "for a decomposition matrix and a module",
894  [IsDecompositionMatrix,IsAlgebraObjModule],
895  function(d,Px) local oldd;
896    oldd:=FindDecompositionMatrix(d!.H,Sum(d!.rows[1])-1);
897    return IsNewIndecomposableOp(d!.H,d,Px,oldd,[]);
898  end
899);
900
901InstallMethod(IsNewIndecomposableOp,
902  "for a decomposition matrix, a module and a partition",
903  [IsDecompositionMatrix,IsAlgebraObjModule,IsList],
904  function(d,Px,mu) local oldd;
905    oldd:=FindDecompositionMatrix(d!.H,Sum(d!.rows[1])-1);
906    return IsNewIndecomposableOp(d!.H,d,Px,oldd,mu);
907  end
908); # IsNewIndecomposable (toplevel)
909
910##P Removes the columns for <Px> in <d>
911InstallMethod(RemoveIndecomposableOp,
912  "for a decomposition matrix and a partition",
913  [IsDecompositionMatrix,IsList],
914  function(d,mu) local r, c;
915    c:=Position(d!.cols, mu);
916    if c=fail then
917      Print("RemoveIndecomposable(<d>,<mu>), <mu> is not listed in <d>\n");
918    else Unbind(d!.d[c]);
919    fi;
920  end
921); # RemoveIndecomposable
922
923### Prints a list of the indecomposable missing from d
924InstallMethod(MissingIndecomposables,
925  "missing entries of a decomposition matrix",
926  [IsDecompositionMatrix],
927  function(d) local c, missing;
928    missing:=List([1..Length(d!.cols)], c->not IsBound(d!.d[c]) );
929    if true in missing then
930      Print("The following projectives are missing from <d>:\n  ");
931      for c in [Length(missing),Length(missing)-1..1] do
932        if missing[c] then Print("  ", d!.cols[c]); fi;
933      od;
934      Print("\n");
935    fi;
936  end
937); # MissingIndecomposables
938
939## When no ordering is supplied then rows are ordered first by length and
940## then lexicographically. The rows and columns may also be explicitly
941## assigned.
942## Usage:
943##   DecompositionMatrix(H, n [,ordering]);
944##   DecompositionMatrix(H, <file>) ** force Specht() to read <file>
945InstallOtherMethod(DecompositionMatrix,"for an algebra and an integer",
946  [IsAlgebraObj,IsInt],
947  function(H,n) local Px, d, c;
948    d:=FindDecompositionMatrix(H,n);
949
950    if d=fail then
951      if H!.p>0 and n>2*H!.e then  ## no point even trying
952        Print("# This decomposition matrix is not known; use ",
953              "CalculateDecompositionMatrix()\n# or ",
954              "InducedDecompositionMatrix() to calculate with this matrix.",
955              "\n");
956        return d;
957      fi;
958      if not IsSchur(H) then c:=ERegularPartitions(H!.e,n);
959      else c:=Partitions(n);
960      fi;
961      d:=DecompositionMatrix(H,Partitions(n),c,true);
962    fi;
963    if ForAny([1..Length(d!.cols)],c->not IsBound(d!.d[c])) then
964      for c in [1..Length(d!.cols)] do
965        if not IsBound(d!.d[c]) then
966          Px:=MakeSpechtOp(Module(H,"P",1,d!.cols[c]),true);
967          if Px<>fail then AddIndecomposable(d,Px,false);
968          else Print("# Projective indecomposable P(",
969                     TightStringList(d!.cols[c]),") not known.\n");
970          fi;
971        fi;
972      od;
973      Store(d,n);
974    fi;
975    if d<>fail then   ## can't risk corrupting the internal matrix lists
976      d:=CopyDecompositionMatrix(d);
977    fi;
978    return d;
979  end
980);
981
982InstallOtherMethod(DecompositionMatrix,
983  "for an algebra, an integer and an ordering",
984  [IsAlgebraObj,IsInt,IsFunction],
985  function(H,n,ord)
986    H!.Ordering := ord;
987    return DecompositionMatrix(H,n);
988  end
989);
990
991InstallOtherMethod(DecompositionMatrix,"for an algebra and a filename",
992  [IsAlgebraObj,IsString],
993  function(H,file) local d;
994    d:=ReadDecompositionMatrix(H,file,false);
995    if d<>fail and not IsBound(d!.matname) then ## override and copy
996      Store(d,Sum(d!.cols[1]));
997      MissingIndecomposables(d);
998    fi;
999    if d<>fail then   ## can't risk corrupting the internal matrix lists
1000      d:=CopyDecompositionMatrix(d);
1001    fi;
1002    return d;
1003  end
1004);
1005
1006InstallOtherMethod(DecompositionMatrix,
1007  "for an algebra, a filename and an ordering",
1008  [IsAlgebraObj,IsString,IsFunction],
1009  function(H,file,ord)
1010      H!.Ordering := ord;
1011    return DecompositionMatrix(H,file);
1012  end
1013); # DecompositionMatrix
1014
1015#F Tries to calculate the decomposition matrix d_{H,n} from scratch.
1016## At present will return only those column indexed by the partitions
1017## of e-weight less than 2.
1018InstallMethod(CalculateDecompositionMatrix,"for an algebra and an integer",
1019  [IsAlgebraObj,IsInt],
1020  function(H,n) local d, c, Px;
1021    if not IsSchur(H) then c:=ERegularPartitions(H!.e,n);
1022    else c:=Partitions(n);
1023    fi;
1024    d:=DecompositionMatrix(H,Partitions(n),c,true);
1025    for c in [1..Length(d!.cols)] do
1026      if not IsBound(d!.d[c]) then
1027        Px:=MakeSpechtOp(Module(H,"P",1,d!.cols[c]),true);
1028        if Px<>fail then AddIndecomposable(d,Px,false);
1029         else Print("# Projective indecomposable P(",
1030                    TightStringList(d!.cols[c]),") not known.\n");
1031        fi;
1032      fi;
1033    od;
1034    return d;
1035  end
1036); # CalculateDecompositionMatrix
1037
1038#F Returns a crystallized decomposition matrix
1039InstallMethod(CrystalDecompositionMatrix,"for an algebra and an integer",
1040  [IsAlgebraObj,IsInt],
1041  function(H,n) local d, Px, c;
1042    if not IsZeroCharacteristic(H) or IsSchur(H) then
1043      Error("Crystal decomposition matrices are defined only ",
1044		         "for Hecke algebras\n         with H!.p=0\n");
1045    fi;
1046
1047    d:=ReadDecompositionMatrix(H,n,true);
1048    if d<>fail then d:=CopyDecompositionMatrix(d);
1049    else d:=DecompositionMatrix(H,
1050                Partitions(n),ERegularPartitions(H!.e,n),false);
1051    fi;
1052    for c in [1..Length(d!.cols)] do
1053      if not IsBound(d!.d[c]) then
1054        AddIndecomposable(d,FindPq(H,d!.cols[c]),false);
1055      fi;
1056    od;
1057    return d;
1058  end
1059);
1060
1061InstallMethod(CrystalDecompositionMatrix,
1062  "for an algebra, an integer and an ordering",
1063  [IsAlgebraObj,IsInt,IsFunction],
1064  function(H,n,ord)
1065    H!.Ordering := ord;
1066    return CrystalDecompositionMatrix(H,n);
1067  end
1068); # CrystalDecompositionMatrix
1069
1070## Given a decomposition matrix induce it to find as many columns as
1071## possible of the next higher matrix using simple minded induction.
1072## Not as simple minded as it was originally, as it now tries to use
1073## Schaper's theorem [JM2] to break up troublesome projectives. The
1074## function looks deceptively simple because all of the work is now
1075## done by IsNewIndecomposable().
1076## Usage: InducedDecompositionMatrix(dn)
1077## in the second form new columns are added to d{n+1}.
1078InstallMethod(InducedDecompositionMatrix,"induce from decomposition matrix",
1079  [IsDecompositionMatrix],
1080  function(d)
1081    local newd, mu, nu, Px, Py, n,r, needNewline;
1082
1083    if IsCrystalDecompositionMatrix(d)
1084    then Error("InducedDecompositionMatrix(d): ",
1085                 "<d> must be a decomposition matrix.");
1086    fi;
1087
1088    needNewline := false;
1089    n:=Sum(d!.rows[1])+1;
1090    if n>8 then                            ## print dots to let the user
1091      PrintTo("*stdout*","# Inducing.");   ## know something is happening.
1092      needNewline := true;
1093    fi;
1094
1095    nu:=Partitions(n);
1096    if IsSchur(d!.H) then
1097      newd:=DecompositionMatrix(d!.H, nu, nu, true);
1098    else newd:=DecompositionMatrix(d!.H, nu,
1099                ERegularPartitions(d!.H!.e,n),true);
1100    fi;
1101
1102    ## add any P(mu)'s with EWeight(mu)<=1 or P(mu)=S(mu) <=> S(mu')=D(mu')
1103    for mu in newd!.cols do
1104      if EWeight(d!.H!.e,mu)<=1 then
1105       AddIndecomposable(newd,
1106           MakeSpechtOp(Module(d!.H,"P",1,mu),true),false);
1107      elif IsSimpleModule(d!.H,ConjugatePartition(mu)) then
1108        AddIndecomposable(newd, Module(d!.H,"S",1,mu),false);
1109      fi;
1110    od;
1111
1112    ## next we r-induce all of the partitions in d so we can just add
1113    ## them up as we need them later.
1114    ## (note that this InducedModule() is Specht()'s and not the generic one)
1115    d!.ind:=List(d!.rows, mu->List([0..d!.H!.e-1],
1116              r->RInducedModule(d!.H,Module(d!.H,"S",1,mu),d!.H!.e,r)));
1117
1118    if n<9 then n:=Length(d!.cols)+1; fi; ## fudge for user friendliness
1119
1120    for mu in [1..Length(d!.cols)] do
1121      if IsBound(d!.d[mu]) then
1122        for r in [1..d!.H!.e] do   ## really the e-residues; see ind above
1123          ## Here we calculate InducedModule(P(mu),H.e,r).
1124          Px:=Sum([1..Length(d!.d[mu].parts)],
1125                     nu->d!.d[mu].coeffs[nu]*d!.ind[d!.d[mu].parts[nu]][r]);
1126          if IsNewIndecomposableOp(d!.H,newd,Px,d,[fail]) then
1127            if IsERegular(Px!.H!.e,Px!.parts[Length(Px!.parts)]) then
1128              # can apply MullineuxMap
1129              nu:=ConjugatePartition(Px!.parts[1]);
1130              if nu<>MullineuxMap(d!.H!.e,Px!.parts[Length(Px!.parts)]) then
1131                ## wrong image under the Mullineux map
1132                BUG("Induce", 7, "nu = ", nu, ", Px = ", Px);
1133              else   ## place the Mullineux image of Px as well
1134                AddIndecomposable(newd,MullineuxMap(Px),false);
1135              fi;
1136            fi;
1137            AddIndecomposable(newd,Px,false);
1138          fi;
1139        od;
1140        if mu mod n = 0 then PrintTo("*stdout*","."); needNewline := true; fi;
1141      fi;
1142    od;
1143    Unbind(d!.ind); Unbind(d!.simples); ## maybe we should leave these.
1144
1145    if needNewline then Print("\n"); fi;
1146    MissingIndecomposables(newd);
1147    return newd;
1148  end
1149); # InducedDecompositionMatrix
1150
1151#F Returns the inverse of (the e-regular part of) d. We invert the matrix
1152## 'by hand' because the matrix routines can't handle polynomial entries.
1153## This should be much faster than it is???
1154InstallMethod(InvertDecompositionMatrix,"for a decomposition matrix",
1155  [IsDecompositionMatrix],
1156  function(d) local inverse, c, r;
1157    inverse:=DecompositionMatrix(d!.H,d!.cols,d!.cols,
1158                                          not IsCrystalDecompositionMatrix(d));
1159
1160    ## for some reason I can't put this inside the second loop (deleting
1161    ## the first because d.inverse is not updated this way around...).
1162    for c in [1..Length(inverse!.cols)] do
1163      Invert(d,d!.cols[c]);
1164    od;
1165    for c in [1..Length(inverse!.cols)] do
1166      if IsBound(d!.inverse[c]) then
1167        inverse!.d[c]:=rec(parts:=[], coeffs:=[]);
1168        for r in [1..c] do
1169          if IsBound(d!.inverse[r]) and c in d!.inverse[r].parts then
1170            Add(inverse!.d[c].parts,r);
1171            Add(inverse!.d[c].coeffs,
1172                d!.inverse[r].coeffs[Position(d!.inverse[r].parts,c)]);
1173          fi;
1174        od;
1175        if inverse!.d[c]=rec(parts:=[], coeffs:=[]) then Unbind(inverse!.d[c]); fi;
1176      fi;
1177    od;
1178    inverse!.matname:="Inverse matrix";
1179    return inverse;
1180  end
1181); # InvertDecompositionMatrix
1182
1183#P Saves a full decomposition matrix; actually, only the d, rows, and cols
1184## records components are saved and the rest calculated when read back in.
1185## The decomposition matrices are saved in the following format:
1186##   A_Specht_Decomposition_Matrix:=rec(
1187##   d:=[[r1,...,rk,d1,...dk],[...],...[]],rows:=[..],cols:=[...]);
1188## where r1,...,rk are the rows in the first column with corresponding
1189## decomposition numbers d1,...,dk (if di is a polynomial then it is saved
1190## as a list [di.valuation,<sequence of di.coffcients]; in particular we
1191## don't save the polynomial name).
1192## Usage: SaveDecompositionMatrix(<d>)
1193##    or  SaveDecompositionMatrix(<d>,<filename>);
1194InstallMethod(SaveDecompositionMatrix,
1195  "for a decomposition matrix and a filename",
1196  [IsDecompositionMatrix,IsString],
1197  function(d,file)
1198    local TightList,n,SaveDm,size, r, c, str, tmp;
1199
1200    n:=Sum(d!.rows[1]);
1201
1202    size:=SizeScreen();    ## SizeScreen(0 shouldn't affect PrintTo()
1203    SizeScreen([80,40]);  ## but it does; this is our protection.
1204
1205    TightList:=function(list) local l, str;
1206      str:="[";
1207      for l in list{[1..Length(list)-1]} do
1208        if IsList(l) then
1209          l:=TightList(l);
1210          str:=Concatenation(str,l);
1211        else str:=Concatenation(str,String(l));
1212        fi;
1213        str:=Concatenation(str,",");
1214      od;
1215      l:=list[Length(list)];
1216      if IsList(l) then
1217        l:=TightList(l);
1218        str:=Concatenation(str,l);
1219      else str:=Concatenation(str,String(l));
1220      fi;
1221      return Concatenation(str,"]");
1222    end;
1223
1224    if d=fail then Error("SaveDecompositionMatrix(<d>), d=fail!!!\n"); fi;
1225
1226    SaveDm:=function(file)
1227      AppendTo(file,"## This is a GAP library file generated by \n## Hecke ",
1228            d!.H!.info.version, "\n\n## This file contains ");
1229      if IsBound(d!.matname) then
1230        AppendTo(file,"a(n) ", d!.matname, " for n = ", Sum(d!.rows[1]),"\n");
1231      else
1232        if IsCrystalDecompositionMatrix(d) then AppendTo(file,"the crystallized "); fi;
1233        AppendTo(file,"the decomposition matrix\n## of the ");
1234        if not IsSchur(d!.H) then
1235          if d!.H!.e<>d!.H!.p then AppendTo(file,"Hecke algebra of ");
1236          else AppendTo(file,"symmetric group ");
1237          fi;
1238        else AppendTo(file,"q-Schur algebra of ");
1239        fi;
1240        AppendTo(file,"Sym(",n,") over a field\n## ");
1241        if d!.H!.p=0 then AppendTo(file,"of characteristic 0 with ");
1242        elif d!.H!.p=d!.H!.e then AppendTo(file,"of characteristic ",d!.H!.p,".\n\n");
1243        else AppendTo(file,"with HeckeRing = ", d!.H!.HeckeRing, ", and ");
1244        fi;
1245        if d!.H!.p<>d!.H!.e then AppendTo(file,"e=", d!.H!.e, ".\n\n");fi;
1246      fi;
1247
1248      AppendTo(file,"A_Specht_Decomposition_Matrix:=rec(\nd:=[");
1249      str:="[";
1250      for c in [1..Length(d!.cols)] do
1251        if not IsBound(d!.d[c]) then AppendTo(file,str,"]");
1252        else
1253          for r in d!.d[c].coeffs do
1254            if IsLaurentPolynomial(r) then
1255            tmp:=ShallowCopy(CoefficientsOfLaurentPolynomial(r));
1256            AppendTo(file,str,"[",tmp[2],",",TightStringList(tmp[1]),"]");
1257            else AppendTo(file,str,r);
1258            fi;
1259            str:=",";
1260          od;
1261          for r in d!.d[c].parts do
1262            AppendTo(file,str,r);
1263          od;
1264          AppendTo(file,"]");
1265          str:=",[";
1266        fi;
1267      od;
1268      AppendTo(file,"],rows:=",TightList(d!.rows));
1269      AppendTo(file,",cols:=",TightList(d!.cols));
1270      if IsCrystalDecompositionMatrix(d) then
1271        AppendTo(file,",crystal:=true");
1272      fi;
1273      if IsBound(d!.matname) then AppendTo(file,",matname:=\"",d!.matname,"\""); fi;
1274      AppendTo(file,");\n");
1275    end;
1276
1277    ## the actual saving of d
1278    SaveDm(file);
1279
1280    ## now we put d into DecompositionMatrices
1281    if not IsBound(d!.matname) then Store(d,n); fi;
1282
1283    SizeScreen(size); # restore screen.
1284  end
1285);
1286
1287InstallMethod(SaveDecompositionMatrix,"for a decomposition matrix",
1288  [IsDecompositionMatrix],
1289  function(d) local n,file;
1290    if d!.H!.HeckeRing="unknown" then
1291      Print("SaveDecompositionMatrix(d): \n     the base ring of the Hecke ",
1292            "algebra is unknown.\n     You must set <d>.H.HeckeRing in ",
1293            "order to save <d>.\n");
1294      return;
1295    fi;
1296
1297    n:=Sum(d!.rows[1]);
1298
1299    if IsBound(d!.matname) then
1300      file:=Concatenation(d!.H!.HeckeRing,".",d!.matname{[1]},String(n));
1301    elif not IsCrystalDecompositionMatrix(d) then
1302      file:=Concatenation(d!.H!.HeckeRing,".",String(n));
1303    else  ## crystallized decomposition matrix
1304      file:=Concatenation("e", String(d!.H!.e), "crys.", String(n));
1305    fi;
1306
1307    SaveDecompositionMatrix(d,file);
1308  end
1309);# SaveDecompositionMatrix()
1310
1311#F Returns the 'adjustment matrix' [J] for <d> and <dp>. ie the
1312## matrix <a> such that <dp>=<a>*<d>.
1313InstallMethod(AdjustmentMatrix,"for two decomposition matrices",
1314  [IsDecompositionMatrix,IsDecompositionMatrix],
1315  function(dp,d) local ad, c, x;
1316    if d!.cols<>dp!.cols or d!.rows<>dp!.rows then return fail; fi;
1317
1318    ad:=DecompositionMatrix(dp!.H,dp!.cols,dp!.cols,true);
1319    ad!.matname:="Adjustment matrix";
1320    c:=1;
1321    while ad<>fail and c<=Length(d!.cols) do
1322      if IsBound(dp!.cols[c]) then
1323        x:=MakePIMSpechtOp(dp, dp!.cols[c]);
1324        x!.H:=d!.H;
1325        x:=MakePIMOp(d,x);
1326        if x=fail then ad:=fail;
1327        else AddIndecomposable(ad,x,false);
1328        fi;
1329      fi;
1330      c:=c+1;
1331    od;
1332    return ad;
1333  end
1334); # AdjustmentMatrix
1335
1336## Returns the a GAP matrix for the decomposition matrix <d>. Note that
1337## the rows and columns and <d> are ordered according to H.info.Ordering.
1338InstallMethod(MatrixDecompositionMatrix,"decomposition matrix -> matrix",
1339  [IsDecompositionMatrix],
1340  function(d) local r,c, rows, cols, m;
1341    rows:=StructuralCopy(d!.rows);
1342    if d!.H!.Ordering<>Lexicographic then
1343      Sort(rows,d!.H!.Ordering);
1344      rows:=List(rows,r->Position(d!.rows,r));
1345    else rows:=[Length(rows),Length(rows)-1..1];
1346    fi;
1347    cols:=StructuralCopy(d!.cols);
1348    if d!.H!.Ordering<>Lexicographic then
1349      Sort(cols,d!.H!.Ordering);
1350      cols:=List(cols,r->Position(d!.cols,r));
1351    else cols:=[Length(cols),Length(cols)-1..1];
1352    fi;
1353    m:=[];
1354    for r in [1..Length(rows)] do
1355      m[r]:=[];
1356      for c in [1..Length(cols)] do
1357        if IsBound(d!.d[cols[c]]) and rows[r] in d!.d[cols[c]].parts then
1358          m[r][c]:=d!.d[cols[c]].coeffs[Position(d!.d[cols[c]].parts,rows[r])];
1359        else m[r][c]:=0;
1360        fi;
1361      od;
1362    od;
1363    return m;
1364  end
1365);
1366
1367## Given a GAP matrix this function returns a Specht decomposition matrix.
1368##   H = Specht() record
1369##   m = matrix: either #reg x #reg, #parts x #reg, or #parts x #parts
1370##   n = Sym(n)
1371InstallMethod(DecompositionMatrixMatrix,"matrix -> decomposition matrix",
1372  [IsAlgebraObj,IsMatrix,IsInt],
1373  function(H,m,n) local r, c, rows, cols, d;
1374    rows:=Partitions(n);
1375    cols:=ERegularPartitions(H,n);
1376    if Length(rows)<>Length(m) then rows:=cols; fi;
1377    if Length(cols)<>Length(m[1]) then cols:=rows; fi;
1378    if Length(rows)<>Length(m) or Length(cols)<>Length(m[1]) then
1379       Print("# usage: DecompositionMatrixMatrix(H, m, n)\n",
1380             "   where m is a matrix of an appropriate size.\n");
1381       return fail;
1382    fi;
1383    if ForAll(m, r->ForAll(r, c->IsInt(c) )) then
1384      d:=DecompositionMatrix(H,StructuralCopy(rows),StructuralCopy(cols),true);
1385    else  ## presumably crystalized
1386      d:=DecompositionMatrix(H,StructuralCopy(rows),StructuralCopy(cols),false);
1387    fi;
1388    ## now we order the rows and columns properly
1389    if H!.Ordering<>Lexicographic then Sort(rows, H!.Ordering);
1390    else rows:=rows{[Length(rows),Length(rows)-1..1]};
1391    fi;
1392    rows:=List(d!.rows, r->Position(rows, r) );
1393    if H!.Ordering<>Lexicographic then Sort(cols, H!.Ordering);
1394    else cols:=cols{[Length(cols),Length(cols)-1..1]};
1395    fi;
1396    cols:=List(d!.cols, c->Position(cols, c) );
1397    for c in [1..Length(cols)] do
1398       d!.d[c]:=rec(parts:=[], coeffs:=[]);
1399       for r in [1..Length(rows)] do
1400         if m[rows[r]][cols[c]]<>0*m[rows[r]][cols[c]] then ## maybe polynomial
1401           Add(d!.d[c].parts, r);
1402           Add(d!.d[c].coeffs, m[rows[r]][cols[c]]);
1403         fi;
1404       od;
1405       if d!.d[c].parts=[] then Unbind(d!.d[c]); fi;
1406    od;
1407    return d;
1408  end
1409); # DecompositionMatrixMatrix
1410
1411## OPERATIONS OF FORMER SPECHT RECORD ##########################################
1412
1413## The following two functions are used by P(), and elsewhere.
1414##   generate the hook (k,1^n-k)  - as a list - where k=arg
1415##   actually not quite a hook since if arg is a list (n,k1,k2,...)
1416##   this returns (k1,k2,...,1^(n-sum k_i))
1417InstallMethod(HookOp,"for an integer and a list of lists",[IsInt,IsList],
1418  function(n,K) local k, i;
1419    k:=Sum(K);
1420    if k < n then Append(K, List([1..(n-k)], i->1));
1421    elif k > n then Error("hook, partition ", k, " bigger than ",n, "\n");
1422    fi;
1423    return K;
1424  end
1425); #Hook
1426
1427InstallMethod(DoubleHook,"for four integers",[IsInt,IsInt,IsInt,IsInt],
1428  function(n,x,y,a) local s, i;
1429    s:=[x];
1430    if y<>0 then Add(s,y); fi;
1431    if a<>0 then Append(s, List([1..a],i->2)); fi;
1432    i:=Sum(s);
1433    if i < n then
1434      Append(s, List([1..n-i], i->1));
1435      return s;
1436    elif i=n then return s;
1437    else return [];
1438    fi;
1439  end
1440); #DoubleHook
1441
1442#### RENAMED Omega -> HeckeOmega
1443## Returns p(n) - p(n-1,1) + p(n-2,1^2) - ... + (-1)^(n-1)*p(1^n).
1444## So, S(mu)*Omega(n) is the linear combination of the S(nu)'s where
1445## nu is obtained by wrapping an n-hook onto mu and attaching the
1446## sign of the leg length.
1447InstallMethod(HeckeOmega,"for an algebra, a string and an integer",
1448  [IsAlgebraObj,IsString,IsInt],
1449  function(H,module,n)
1450    return Module(H,module,List([1..n],x->(-1)^(x)),
1451                     List([1..n],x->Hook(n,x)));
1452  end
1453); #HeckeOmega
1454
1455## MODULES #####################################################################
1456InstallMethod(Module,"create new module",[IsAlgebraObj,IsString,IsList,IsList],
1457  function(H,m,c,p)
1458    local module;
1459    module := rec(H:=H,module:=m,coeffs:=c,parts:=p);
1460
1461    if m = "S" and not IsSchur(H) then Objectify(HeckeSpechtType,module);
1462    elif m = "P" and not IsSchur(H) then Objectify(HeckePIMType,module);
1463    elif m = "D" and not IsSchur(H) then Objectify(HeckeSimpleType,module);
1464    elif m = "Sq" and not IsSchur(H) then Objectify(HeckeSpechtFockType,module);
1465    elif m = "Pq" and not IsSchur(H) then Objectify(HeckePIMFockType,module);
1466    elif m = "Dq" and not IsSchur(H) then Objectify(HeckeSimpleFockType,module);
1467    elif m = "W" or m = "S" then Objectify(SchurWeylType,module); module!.module:="W";
1468    elif m = "P" then Objectify(SchurPIMType,module);
1469    elif m = "F" or m = "D" then Objectify(SchurSimpleType,module); module!.module:="F";
1470    elif m = "Wq" or m = "Sq" then Objectify(SchurWeylFockType,module); module!.module:="Wq";
1471    elif m = "Pq" then Objectify(SchurPIMFockType,module);
1472    elif m = "Fq" or m = "Dq" then Objectify(SchurSimpleFockType,module); module!.module:="Fq";
1473    fi;
1474
1475    return module;
1476  end
1477);
1478
1479InstallMethod(Module,"create new module",[IsAlgebraObj,IsString,IsInt,IsList],
1480  function(H,m,c,p)
1481    return Module(H,m,[c],[p]);
1482  end
1483);
1484
1485InstallMethod(Module,"create new module",[IsAlgebraObj,IsString,IsLaurentPolynomial,IsList],
1486  function(H,m,c,p)
1487    return Module(H,m,[c],[p]);
1488  end
1489);
1490
1491## Takes two lists, one containing coefficients and the other the
1492## corresponding partitions, and orders them lexicographically collecting
1493## like terms on the way. We use a variation on quicksort which is
1494## induced by the lexicographic order (if parts contains partitions of
1495## different integers this can lead to an error - which we don't catch).
1496InstallMethod(Collect,"utility for module generation",
1497  [IsAlgebraObj,IsString,IsList,IsList],
1498  function(H, module, coeffs, parts)
1499    local newx, i, Place, Unplace, places;
1500
1501    ## inserting parts[i] into places. if parts[i]=[p1,p2,...] then
1502    ## we insert it into places at places[p1][[p2][...] stopping
1503    ## at the fist empty position (say places[p1], or places[p1][p2]
1504    ## etc.). Here we are trying to position parts[i] at
1505    ## places[p1]...[pd]. Actually, we just insert i rather than
1506    ## parts[i] and if we find that parts[i]=parts[j] for some j then
1507    ## we set coeffs[i]:=coeffs[i]+coeffs[j] and don't place j.
1508    Place:=function(i, places, d) local t;
1509      if IsInt(places) then
1510        t:=places;
1511        if parts[t]=parts[i] then coeffs[t]:=coeffs[t]+coeffs[i];
1512        else
1513          places:=[];
1514          places[parts[t][d]]:=t;
1515          if parts[i][d]<>parts[t][d] then places[parts[i][d]]:=i;
1516          else places:=Place(i, places, d);
1517          fi;
1518        fi;
1519      elif places=[] or not IsBound(places[parts[i][d]]) then
1520        # must be a list
1521        places[parts[i][d]]:=i;
1522      else places[parts[i][d]]:=Place(i, places[parts[i][d]], d+1);
1523      fi;
1524      return places;
1525    end;
1526
1527    Unplace:=function(places) local p, newp, np;
1528      newp:=[[],[]];
1529      for p in places do
1530        if IsInt(p) then if coeffs[p]<>0*coeffs[p] then
1531          Add(newp[1], coeffs[p]);
1532          Add(newp[2], StructuralCopy(parts[p])); fi;
1533        else
1534          np:=Unplace(p);
1535          Append(newp[1], np[1]);
1536          Append(newp[2], np[2]);
1537        fi;
1538      od;
1539      return newp;
1540    end;
1541
1542   if parts=[] then return Module(H,module,0,[]);
1543   elif Length(parts)=1 then return Module(H,module,coeffs,parts);
1544   else places:=[];
1545      for i in [1..Length(parts)] do places:=Place(i, places, 1); od;
1546      newx:=Unplace(places);
1547      if newx=[[],[]] then return Module(H,module,0,[]);
1548      else return Module(H,module,newx[1],newx[2]);
1549      fi;
1550    fi;
1551  end  ## H.operations.Collect
1552);
1553
1554## MODULE CONVERSION ###########################################################
1555
1556## Finally the conversion functions S(), P() and D(). All take
1557## a linear combination of Specht modules and return corresponding
1558## linear combinations of Specht, indecomposables, and simples resp.
1559## If they have a problem they return false and print an error
1560## message unless silent=true.
1561InstallMethod(MakeSpechtOp,"S()->S()",[IsHeckeSpecht,IsBool],
1562  function(x,silent) return x; end
1563);
1564
1565InstallMethod(MakeSpechtOp,"S[q]()->S[q]()",[IsDecompositionMatrix,IsHeckeSpecht],
1566  function(d,x) return x; end
1567);
1568
1569## Here I only allow for linear combinations of projectives which
1570## have non-negative coefficients; the reason for this is that I
1571## can't see how to do it otherwise. The problem is that in the
1572## Grothendieck ring there are many ways to write a given linear
1573## combination of Specht modules (or PIMs).
1574InstallMethod(MakePIMOp,"S()->P()",[IsHeckeSpecht,IsBool],
1575  function(x,silent) local proj, tmp;
1576    if x=fail or x=0*x then return x;
1577    elif x!.parts=[[]] then return Module(x!.H,"P",x!.coeffs[1],[]);
1578    fi;
1579
1580    proj:=Module(x!.H,"P",0,[]);
1581    while x<>fail and x<>0*x and
1582    ( IsSchur(x!.H) or IsERegular(x!.H!.e,x!.parts[Length(x!.parts)]) ) do
1583      proj:=proj+Module(x!.H,"P",x!.coeffs[Length(x!.parts)],
1584                                      x!.parts[Length(x!.parts)]);
1585      tmp:=MakeSpechtOp(
1586                Module(x!.H,"P",-x!.coeffs[Length(x!.parts)],
1587                                      x!.parts[Length(x!.parts)]),true);
1588      if tmp<>fail then x:=x+tmp; else x:=fail; fi;
1589    od;
1590    if x=fail or x<>0*x then
1591      if not silent then
1592        Print("# P(<x>), unable to rewrite <x> as a sum of projectives\n");
1593      fi;
1594    else return proj;
1595    fi;
1596    return fail;
1597  end
1598);
1599
1600InstallMethod(MakePIMOp,"S[q]()->P[q]()",[IsDecompositionMatrix,IsHeckeSpecht],
1601  function(d,x) local nx, r, c, P, S;
1602    if x=fail or x=0*x then return x; fi;
1603    if IsCrystalDecompositionMatrix(d) then P:="Pq"; S:="Sq";
1604    else P:="P"; S:="S";
1605    fi;
1606
1607    nx:=Module(x!.H,P,0,[]);
1608    while x<>fail and x<>0*x do
1609      c:=Position(d!.cols,x!.parts[Length(x!.parts)]);
1610      if c=fail or not IsBound(d!.d[c]) then return fail; fi;
1611      nx:=nx+Module(x!.H,P,x!.coeffs[Length(x!.parts)],d!.cols[c]);
1612      x:=x+Module(x!.H,S,-x!.coeffs[Length(x!.parts)]*d!.d[c].coeffs,
1613                            List(d!.d[c].parts,r->d!.rows[r]));
1614    od;
1615    return nx;
1616  end
1617);
1618
1619InstallMethod(MakeSimpleOp,"S()->D()",[IsHeckeSpecht,IsBool],
1620  function(x,silent) local y, d, simples, r, c;
1621    if x=fail or x=0*x then return x;
1622    elif x!.parts=[[]] then return Module(x!.H,"D",x!.coeffs[1],[]);
1623    fi;
1624
1625    d:=KnownDecompositionMatrix(x!.H,Sum(x!.parts[1]));
1626    if d<>fail then
1627      y:=MakeSimpleOp(d,x);
1628      if y<>fail then return y; fi;
1629    fi;
1630
1631    ## since that didn't work, we use the LLT algorithm when IsBound(H.Pq)
1632    if IsZeroCharacteristic(x!.H) and not IsSchur(x!.H) then
1633      return Sum([1..Length(x!.parts)],
1634                 r->x!.coeffs[r]*Specialized(FindSq(x!.H,x!.parts[r])));
1635    fi;
1636
1637    # next, see if we can calculate the answer.
1638    d:=Concatenation(x!.H!.HeckeRing,"D");
1639    # finally, we can hope that only partitions of e-weight<2 appear in x
1640    r:=1; simples:=Module(x!.H,"D",0,[]);
1641    while simples<>fail and r <= Length(x!.parts) do
1642      if IsSimpleModule(x!.H, x!.parts[r]) then
1643        simples:=simples+Module(x!.H,"D",x!.coeffs[r], x!.parts[r]);
1644      elif IsERegular(x!.H!.e,x!.parts[r]) and EWeight(x!.H!.e,x!.parts[r])=1
1645      then
1646        y:=Module(x!.H,"S",1,ECore(x!.H!.e,x!.parts[r]))
1647                           * HeckeOmega(x!.H,"S",x!.H!.e);
1648        c:=Position(y!.parts,x!.parts[r]); ## >1 since not IsSimpleModule
1649        simples:=simples
1650                  +Module(x!.H,"D",[1,1],[y!.parts[c],y!.parts[c-1]]);
1651      #### elif IsBound(x.operations.(d)) then ## FIXME not needed anymore?
1652      ####   simples:=simples+x.operations.(d)(x.parts[r]);
1653      else simples:=fail;
1654      fi;
1655      r:=r+1;
1656    od;
1657    if simples=fail and not silent then
1658      Print("# D(<x>), unable to rewrite <x> as a sum of simples\n");
1659      return fail;
1660    else return simples;
1661    fi;
1662  end
1663);
1664
1665InstallMethod(MakeSimpleOp,"S[q]()->D[q]()",[IsDecompositionMatrix,IsHeckeSpecht],
1666  function(d,x) local nx, y, r, rr, c, D, core;
1667    if x=fail or x=0*x then return x; fi;
1668    if IsCrystalDecompositionMatrix(d) then D:="Dq"; else D:="D"; fi;
1669
1670    nx:=Module(x!.H,D,0,[]);
1671    for y in [1..Length(x!.parts)] do
1672      r:=Position(d!.rows, x!.parts[y]);
1673      if r=fail then return fail; fi;
1674      core:=ECore(x!.H!.e,x!.parts[y]);
1675      c:=Length(d!.cols);
1676      while c>0 and d!.cols[c]>=x!.parts[y] do
1677        if IsBound(d!.d[c]) then
1678          rr:=Position(d!.d[c].parts,r);
1679          if rr<>fail then nx:=nx+Module(x!.H,D,
1680                         x!.coeffs[y]*d!.d[c].coeffs[rr],d!.cols[c]);
1681          fi;
1682        elif ECore(x!.H!.e,d!.cols[c])=core then return fail;
1683        fi;
1684        c:=c-1;
1685      od;
1686    od;
1687    return nx;
1688  end
1689);
1690
1691## The P->S functions are quite involved.
1692
1693#F Writes x, which is a sum of indecomposables, as a sum of S(nu)'s if
1694## possible. We first check to see if the decomposition matrix for x is
1695## stored somewhere, and if not we try to calculate what we need. If we
1696## can't do this we return false.
1697InstallMethod(MakeSpechtOp,"P()->S()",[IsHeckePIM,IsBool],
1698  function(x,silent) local y, c, d, mu, specht;
1699    if x=fail or x=0*x then return x;
1700    elif x!.parts=[[]] then return Module(x!.H,"S",x!.coeffs[1],[]);
1701    fi;
1702    d:=KnownDecompositionMatrix(x!.H,Sum(x!.parts[1]));
1703    if d<>fail then
1704      y:=MakeSpechtOp(d,x);
1705      if y<>fail then return y; fi;
1706    fi;
1707
1708    ## since that didn't work, we use the LLT algorithm when
1709    ## IsBound(H.Pq)
1710    if IsZeroCharacteristic(x!.H) then
1711      if not IsSchur(x!.H) or ForAll(x!.parts, c->IsERegular(x!.H!.e,c)) then
1712        return Sum([1..Length(x!.parts)],c->
1713                 x!.coeffs[c]*Specialized(FindPq(x!.H,x!.parts[c])));
1714      fi;
1715    fi;
1716
1717    d:=Concatenation(x!.H!.HeckeRing,"S");
1718    mu:=1; specht:=Module(x!.H,"S",0,[]);
1719    while specht<>fail and mu<=Length(x!.parts) do
1720      if IsSimpleModule(x!.H,ConjugatePartition(x!.parts[mu])) then
1721        specht:=specht+Module(x!.H,"S",1,x!.parts[mu]);
1722      elif EWeight(x!.H!.e,x!.parts[mu])=1 then ## wrap e-hooks onto c
1723        c:=Module(x!.H,"S",1,ECore(x!.H!.e, x!.parts[mu]))
1724                 * HeckeOmega(x!.H,"S",x!.H!.e);
1725        y:=Position(c!.parts, x!.parts[mu]);
1726        specht:=specht+Module(x!.H,"S",[1,1],
1727                                        [c!.parts[y-1],c!.parts[y]]);
1728      #### elif IsBound(H.operations.P.(d)) then ## FIXME not needed anymore?
1729      ####   specht:=specht+x.H.operations.P.(d)(x.parts[mu]);
1730      else specht:=fail;
1731      fi;
1732      mu:=mu+1;
1733    od;
1734    if specht<>fail then return specht;
1735    elif not silent then
1736      Print("# P(<x>), unable to rewrite <x> as a sum of specht modules\n");
1737    fi;
1738    return fail;
1739  end
1740);
1741
1742InstallMethod(MakeSpechtOp,"P[q]()->S[q]()",[IsDecompositionMatrix,IsHeckePIM],
1743  function(d,x) local S, nx, y, r, c;
1744    if x=fail or x=0*x then return x; fi;
1745    if IsCrystalDecompositionMatrix(d) then S:="Sq"; else S:="S"; fi;
1746
1747    nx:=Module(x!.H,S,0,[]);
1748    for y in [1..Length(x!.parts)] do
1749      c:=Position(d!.cols,x!.parts[y]);
1750      if c=fail or not IsBound(d!.d[c]) then return fail; fi;
1751      nx:=nx+Module(x!.H,S,x!.coeffs[y]*d!.d[c].coeffs,
1752                              List(d!.d[c].parts,r->d!.rows[r]));
1753    od;
1754    return nx;
1755  end
1756);
1757
1758InstallMethod(MakePIMOp,"P()->P()",[IsHeckePIM,IsBool],
1759  function(x,silent) return x; end
1760);
1761
1762InstallMethod(MakePIMOp,"P[q]()->P[q]()",[IsDecompositionMatrix,IsHeckePIM],
1763  function(d,x) return x; end
1764);
1765
1766InstallMethod(MakeSimpleOp,"P()->D()",[IsHeckePIM,IsBool],
1767    function(x,silent)
1768      x:=MakeSpechtOp(x,silent);
1769      if x=fail then return x;
1770      else return MakeSimpleOp(x,silent);
1771      fi;
1772    end
1773);
1774
1775InstallMethod(MakeSimpleOp,"P[q]()->D[q]()",[IsDecompositionMatrix,IsHeckePIM],
1776  function(d,x)
1777    x:=MakeSpechtOp(d,x);
1778    if x=fail then return x;
1779    else return MakeSimpleOp(d,x);
1780    fi;
1781  end
1782);
1783
1784#F Writes D(mu) as a sum of S(nu)'s if possible. We first check to see
1785## if the decomposition matrix for Sum(mu) is stored in the library, and
1786## then try to calculate it directly. If we are unable to do this either
1787## we return fail.
1788InstallMethod(MakeSpechtOp,"D()->S()",[IsHeckeSimple,IsBool],
1789  function(x,silent) local c, d, y, a;
1790    if x=fail or x=0*x then return x;
1791    elif x!.parts=[[]] then return Module(x!.H,"S",x!.coeffs[1],[]);
1792    fi;
1793
1794    ## look for the decomposition matrix
1795    d:=KnownDecompositionMatrix(x!.H,Sum(x!.parts[1]));
1796    if d<>fail then
1797      y:=MakeSpechtOp(d,x);
1798      if y<>fail then return y; fi;
1799    fi;
1800
1801    ## since that didn't work, we use the LLT algorithm when IsBound(H.Pq)
1802    if IsZeroCharacteristic(x!.H) and not IsSchur(x!.H) then
1803      return Sum([1..Length(x!.parts)],
1804                   c->x!.coeffs[c]*Specialized(FindDq(x!.H,x!.parts[c])));
1805    fi;
1806
1807    #### ## Next, see if we can calculate it. ## FIXME not needed anymore?
1808    #### d:=Concatenation(H.HeckeRing, "S");
1809    #### if IsBound(H.operations.D.(d)) then
1810    ####  return H.operations.D.(d)(x,silent);
1811    #### fi;
1812
1813    ## Finally, hope only e-weights<2 are involved.
1814    c:=1; d:=true; y:=Module(x!.H,"S",0,[]);
1815    while d and c<=Length(x!.parts) do
1816      if IsSimpleModule(x!.H, x!.parts[c]) then
1817        y:=y+Module(x!.H,"S",x!.coeffs[c],x!.parts[c]);
1818      elif IsERegular(x!.H!.e, x!.parts[c]) and EWeight(x!.H!.e,x!.parts[c])=1
1819      then ## wrap e-hooks onto c
1820        a:=Module(x!.H,"S",1,ECore(x!.H!.e,x!.parts[c]))
1821             * HeckeOmega(x!.H,"S",x!.H!.e);
1822        a!.parts:=a!.parts{[1..Position(a!.parts, x!.parts[c])]};
1823        a!.coeffs:=a!.coeffs{[1..Length(a!.parts)]}*(-1)^(1+Length(a!.parts));
1824        y:=y+a;
1825      else d:=fail;
1826      fi;
1827      c:=c+1;
1828    od;
1829    if d<>fail then return y;
1830    elif not silent then
1831      Print("# Unable to calculate D(mu)\n");
1832    fi;
1833    return fail;
1834  end
1835);
1836
1837InstallMethod(MakeSpechtOp,"D[q]()->S[q]()",[IsDecompositionMatrix,IsHeckeSimple],
1838  function(d,x) local S, nx, y, c, inv;
1839    if x=fail or x=0*x then return x; fi;
1840    if IsCrystalDecompositionMatrix(d) then S:="Sq"; else S:="S"; fi;
1841
1842    nx:=Module(x!.H,S,0,[]);
1843    for y in [1..Length(x!.parts)] do
1844      c:=Position(d!.cols,x!.parts[y]);
1845      if c=fail then return fail; fi;
1846      inv:=Invert(d,x!.parts[y]);
1847      if inv=fail then return inv;
1848      else nx:=nx+x!.coeffs[y]*inv;
1849      fi;
1850    od;
1851    return nx;
1852  end
1853);
1854
1855InstallMethod(MakePIMOp,"D()->P()",[IsHeckeSimple,IsBool],
1856  function(x,silent)
1857      x:=MakeSpechtOp(x,silent);
1858      if x=fail then return x;
1859      else return MakePIMOp(x,silent);
1860      fi;
1861    end
1862);
1863
1864InstallMethod(MakePIMOp,"D[q]()->P[q]()",[IsDecompositionMatrix,IsHeckeSimple],
1865  function(d,x)
1866    x:=MakeSimpleOp(d,x);
1867    if x=fail then return x;
1868    else return MakePIMOp(d,x);
1869    fi;
1870  end
1871);
1872
1873InstallMethod(MakeSimpleOp,"D()->D()",[IsHeckeSimple,IsBool],
1874  function(x,silent) return x; end
1875);
1876
1877InstallMethod(MakeSimpleOp,"D[q]()->D[q]()",[IsDecompositionMatrix,IsHeckeSimple],
1878  function(d,x) return x; end
1879);
1880
1881## Finally, change the various conversion functions X()->Y();
1882## in fact, we only have to change the four non-trivial ones:
1883##   P() <-> S() <-> D().
1884
1885InstallMethod(MakePIMOp,"Sq()->Pq()",[IsFockSpecht,IsBool],
1886  function(x,silent) local proj;
1887    if x=fail or x=0*x then return x;
1888    elif x!.parts=[[]] then return Module(x!.H,"Pq",x!.coeffs[1],[]);
1889    fi;
1890
1891    proj:=Module(x!.H,"Pq",0,[]);
1892    while x<>0*x and PositiveCoefficients(x) do
1893      proj:=proj+Module(x!.H,"Pq",x!.coeffs[Length(x!.parts)],
1894                                       x!.parts[Length(x!.parts)]);
1895      x:=x-x!.coeffs[Length(x!.parts)]*FindPq(x!.H,x!.parts[Length(x!.parts)]);
1896    od;
1897    if x=0*x then return proj;
1898    elif not silent then
1899      Print("# P(<x>), unable to rewrite <x> as a sum of projectives\n");
1900    fi;
1901    return fail;
1902  end
1903);
1904
1905InstallMethod(MakeSimpleOp,"Sq()->Dq()",[IsFockSpecht,IsBool],
1906  function(x,silent) local mu;
1907    if x=fail or x=0*x then return x;
1908    elif x!.parts=[[]] then return Module(x!.H,"Dq",x!.coeffs[1],[]);
1909    fi;
1910    return Sum([1..Length(x!.parts)],
1911      mu->x!.coeffs[mu]*FindSq(x!.H,x!.parts[mu]) );
1912  end
1913);
1914
1915InstallMethod(MakeSpechtOp,"Pq()->Sq()",[IsFockPIM,IsBool],
1916  function(x,silent) local mu;
1917    if x=fail or x=0*x then return x;
1918    elif x!.parts=[[]] then return Module(x!.H,"Sq",x!.coeffs[1],[]);
1919    fi;
1920
1921    return Sum([1..Length(x!.parts)],
1922      mu->x!.coeffs[mu]*FindPq(x!.H,x!.parts[mu]) );
1923  end
1924);
1925
1926InstallMethod(MakeSpechtOp,"Dq()->Sq()",[IsFockPIM,IsBool],
1927  function(x,silent) local mu;
1928    if x=fail or x=0*x then return x;
1929    elif x!.parts=[[]] then return Module(x!.H,"Sq",x!.coeffs[1],[]);
1930    fi;
1931
1932    return Sum([1..Length(x!.coeffs)],
1933      mu->x!.coeffs[mu]*FindDq(x!.H,x!.parts[mu]) );
1934  end
1935);
1936
1937## Make<module> now also plays the role of H.<module> functions
1938InstallMethod(MakeSpechtOp,"H.S(mu)",[IsAlgebraObj,IsList],
1939  function(H,mu) local z;
1940    if mu = [] then return Module(H,"S",1,[]);
1941    else
1942      if not ForAll(mu,z->IsInt(z)) then return fail; fi;
1943      z:=StructuralCopy(mu);
1944      Sort(mu, function(a,b) return a>b;end); # non-increasing
1945      if mu<>z then
1946        Print("## S(mu), warning <mu> is not a partition.\n");
1947      fi;
1948      if Length(mu)>0 and mu[Length(mu)]<0 then
1949        Error("## S(mu): <mu> contains negative parts.\n");
1950      fi;
1951      z:=Position(mu,0);
1952      if z<>fail then mu:=mu{[1..z-1]}; fi;  ## remove any zeros from mu
1953    fi;
1954    return Module(H,"S", 1, mu);
1955  end
1956);
1957
1958InstallMethod(MakeSpechtOp,"H.S(d,mu)",[IsDecompositionMatrix,IsList],
1959  function(d,mu) local z;
1960    if mu = [] then return Module(d!.H,"S",1,[]);
1961    else
1962      if not ForAll(mu,z->IsInt(z)) then return fail; fi;
1963      z:=StructuralCopy(mu);
1964      Sort(mu, function(a,b) return a>b;end); # non-increasing
1965      if mu<>z then
1966        Print("## S(mu), warning <mu> is not a partition.\n");
1967      fi;
1968      if Length(mu)>0 and mu[Length(mu)]<0 then
1969        Error("## S(mu): <mu> contains negative parts.\n");
1970      fi;
1971      z:=Position(mu,0);
1972      if z<>fail then mu:=mu{[1..z-1]}; fi;  ## remove any zeros from mu
1973    fi;
1974    return MakeSimpleOp(d,Module(d!.H,"S", 1, mu));
1975  end
1976);
1977
1978InstallMethod(MakePIMOp,"H.P(mu)",[IsAlgebraObj,IsList],
1979  function(H,mu) local z;
1980    if mu = [] then return Module(H,"P",1,[]);
1981    else
1982      if not ForAll(mu,z->IsInt(z)) then return fail; fi;
1983      z:=StructuralCopy(mu);
1984      Sort(mu, function(a,b) return a>b;end); # non-increasing
1985      if mu<>z then
1986        Print("## P(mu), warning <mu> is not a partition.\n");
1987      fi;
1988      if Length(mu)>0 and mu[Length(mu)]<0 then
1989        Error("## P(mu): <mu> contains negative parts.\n");
1990      fi;
1991      z:=Position(mu,0);
1992      if z<>fail then mu:=mu{[1..z-1]}; fi;  ## remove any zeros from mu
1993    fi;
1994    return Module(H,"P", 1, mu);
1995  end
1996);
1997
1998InstallMethod(MakePIMOp,"H.P(d,mu)",[IsDecompositionMatrix,IsList],
1999  function(d,mu) local z;
2000    if mu = [] then return Module(d!.H,"P",1,[]);
2001    else
2002      if not ForAll(mu,z->IsInt(z)) then return fail; fi;
2003      z:=StructuralCopy(mu);
2004      Sort(mu, function(a,b) return a>b;end); # non-increasing
2005      if mu<>z then
2006        Print("## P(mu), warning <mu> is not a partition.\n");
2007      fi;
2008      if Length(mu)>0 and mu[Length(mu)]<0 then
2009        Error("## P(mu): <mu> contains negative parts.\n");
2010      fi;
2011      z:=Position(mu,0);
2012      if z<>fail then mu:=mu{[1..z-1]}; fi;  ## remove any zeros from mu
2013    fi;
2014    if not IsSchur(d!.H) and not IsERegular(d!.H!.e,mu) then
2015      Error("P(mu): <mu>=[",TightStringList(mu),
2016              "] must be ", d!.H!.e,"-regular\n\n");
2017    fi;
2018    return MakeSpechtOp(d,Module(d!.H,"P", 1, mu));
2019  end
2020);
2021
2022InstallMethod(MakeSimpleOp,"H.D(mu)",[IsAlgebraObj,IsList],
2023  function(H,mu) local z;
2024    if mu = [] then return Module(H,"D",1,[]);
2025    else
2026      if not ForAll(mu,z->IsInt(z)) then return fail; fi;
2027      z:=StructuralCopy(mu);
2028      Sort(mu, function(a,b) return a>b;end); # non-increasing
2029      if mu<>z then
2030        Print("## D(mu), warning <mu> is not a partition.\n");
2031      fi;
2032      if Length(mu)>0 and mu[Length(mu)]<0 then
2033        Error("## D(mu): <mu> contains negative parts.\n");
2034      fi;
2035      z:=Position(mu,0);
2036      if z<>fail then mu:=mu{[1..z-1]}; fi;  ## remove any zeros from mu
2037    fi;
2038    if not IsSchur(H) and not IsERegular(H!.e,mu) then
2039      Error("D(mu): <mu>=[",TightStringList(mu),
2040              "] must be ", H!.e,"-regular\n\n");
2041    fi;
2042    return Module(H,"D", 1, mu);
2043  end
2044);
2045
2046InstallMethod(MakeSimpleOp,"H.D(d,mu)",[IsDecompositionMatrix,IsList],
2047  function(d,mu) local z;
2048    if mu = [] then return Module(d!.H,"D",1,[]);
2049    else
2050      if not ForAll(mu,z->IsInt(z)) then return fail; fi;
2051      z:=StructuralCopy(mu);
2052      Sort(mu, function(a,b) return a>b;end); # non-increasing
2053      if mu<>z then
2054        Print("## D(mu), warning <mu> is not a partition.\n");
2055      fi;
2056      if Length(mu)>0 and mu[Length(mu)]<0 then
2057        Error("## D(mu): <mu> contains negative parts.\n");
2058      fi;
2059      z:=Position(mu,0);
2060      if z<>fail then mu:=mu{[1..z-1]}; fi;  ## remove any zeros from mu
2061    fi;
2062    if not IsSchur(d!.H) and not IsERegular(d!.H!.e,mu) then
2063      Error("D(mu): <mu>=[",TightStringList(mu),
2064              "] must be ", d!.H!.e,"-regular\n\n");
2065    fi;
2066    return MakeSpechtOp(d,Module(d!.H,"D", 1, mu));
2067  end
2068);
2069
2070InstallMethod(MakeSpechtOp,"H.S(x)",[IsAlgebraObjModule],
2071  function(x) return MakeSpechtOp(x,false); end
2072);
2073
2074InstallMethod(MakePIMOp,"H.P(x)",[IsAlgebraObjModule],
2075  function(x) return MakePIMOp(x,false); end
2076);
2077
2078InstallMethod(MakeSimpleOp,"H.D(x)",[IsAlgebraObjModule],
2079  function(x) return MakeSimpleOp(x,false); end
2080);
2081
2082#a lazy helper
2083InstallMethod(MakePIMSpechtOp,"mu->P(mu)->S(mu)",[IsDecompositionMatrix,IsList],
2084  function(d,mu)
2085    return MakeSpechtOp(d,Module(d!.H,"P",1,mu));
2086  end
2087);
2088
2089InstallMethod(MakeFockSpechtOp,"H.Sq(mu)",[IsAlgebraObj,IsList],
2090  function(H,mu) local z;
2091    if not ForAll(mu,z->IsInt(z)) then
2092      Error("usage: H.Sq(<mu1,mu2,...>)\n");
2093    fi;
2094    z:=StructuralCopy(mu);
2095    Sort(mu, function(a,b) return a>b;end); # non-increasing
2096    if mu<>z then
2097      Print("## Sq(mu), warning <mu> is not a partition.\n");
2098    fi;
2099    if Length(mu)>0 and mu[Length(mu)]<0 then
2100      Error("## B Sq(mu): <mu> contains negative parts.\n");
2101    fi;
2102    z:=Position(mu,0);
2103    if z<>fail then mu:=mu{[1..z-1]}; fi;  ## remove any zeros from mu
2104    return Module(H,"Sq",1,mu);
2105  end
2106);
2107
2108InstallMethod(MakeFockPIMOp,"H.Pq(mu)",[IsAlgebraObj,IsList],
2109  function(H,mu) local z;
2110    if not ForAll(mu,z->IsInt(z)) then
2111      Error("usage: H.Pq(<mu1,mu2,...>)\n");
2112    fi;
2113    z:=StructuralCopy(mu);
2114    Sort(mu, function(a,b) return a>b;end); # non-increasing
2115    if mu<>z then
2116      Print("## Pq(mu), warning <mu> is not a partition.\n");
2117    fi;
2118    if Length(mu)>0 and mu[Length(mu)]<0 then
2119      Error("## B Pq(mu): <mu> contains negative parts.\n");
2120    fi;
2121    z:=Position(mu,0);
2122    if z<>fail then mu:=mu{[1..z-1]}; fi;  ## remove any zeros from mu
2123    if not IsERegular(H!.e,mu) then
2124          Error("Pq(mu): <mu>=[",TightStringList(mu),
2125                "] must be ", H!.e,"-regular\n\n");
2126    else return FindPq(H,mu);
2127    fi;
2128  end
2129);
2130
2131## ARITHMETICS #################################################################
2132InstallMethod(\=,"compare modules",[IsAlgebraObjModule,IsAlgebraObjModule],
2133  function(a,b) return a!.H=b!.H and a!.module=b!.module
2134    and Length(a!.parts)=Length(b!.parts) and Length(a!.coeffs)=Length(b!.coeffs)
2135    and ForAll(Zip(a!.coeffs,a!.parts),a->a in Zip(b!.coeffs,b!.parts)); end
2136);
2137
2138InstallMethod(\+,"add modules",[IsAlgebraObjModule,IsAlgebraObjModule],
2139  function(a,b)
2140    local i, j, ab, x;
2141
2142    if a=fail or b=fail then return fail;
2143    elif a=0*a then return b;
2144    elif b=0*b then return a;
2145    elif a!.H<>b!.H then
2146      Error("modules belong to different Grothendieck rings");
2147    fi;
2148
2149    if a!.module<>b!.module then # only convert to Specht modules if different
2150      if Length(a!.module) <> Length(b!.module) then
2151        Error("AddModule(<a>,<b>): can only add modules of same type.");
2152      fi;
2153      a:=MakeSpechtOp(a,false);
2154      b:=MakeSpechtOp(b,false);
2155      if a=fail or b=fail then return fail; fi;
2156    fi;
2157
2158    ## profiling shows _convincingly_ that the method used below to add
2159    ## a and b is faster than using SortParallel or H.operations.Collect.
2160    ab:=[[],[]];
2161    i:=1; j:=1;
2162    while i <=Length(a!.parts) and j <=Length(b!.parts) do
2163      if a!.parts[i]=b!.parts[j] then
2164        x:=a!.coeffs[i]+b!.coeffs[j];
2165        if x<>0*x then
2166          Add(ab[1],x);
2167          Add(ab[2], a!.parts[i]);
2168        fi;
2169        i:=i+1; j:=j+1;
2170      elif a!.parts[i] < b!.parts[j] then
2171        if a!.coeffs[i]<>0*a!.coeffs[i] then
2172          Add(ab[1], a!.coeffs[i]);
2173          Add(ab[2], a!.parts[i]);
2174        fi;
2175        i:=i+1;
2176      else
2177        if b!.coeffs[j]<>0*b!.coeffs[j] then
2178          Add(ab[1], b!.coeffs[j]);
2179          Add(ab[2], b!.parts[j]);
2180        fi;
2181        j:=j+1;
2182      fi;
2183    od;
2184    if i <=Length(a!.parts) then
2185      Append(ab[1], a!.coeffs{[i..Length(a!.coeffs)]});
2186      Append(ab[2], a!.parts{[i..Length(a!.parts)]});
2187    elif j <=Length(b!.parts) then
2188      Append(ab[1], b!.coeffs{[j..Length(b!.coeffs)]});
2189      Append(ab[2], b!.parts{[j..Length(b!.parts)]});
2190    fi;
2191    if ab=[[],[]] then ab:=[ [0],[[]] ]; fi;
2192    return Module(a!.H, a!.module, ab[1], ab[2]);
2193  end
2194); # AddModules
2195
2196InstallMethod(\-,[IsAlgebraObjModule,IsAlgebraObjModule],
2197  function(a,b)
2198    if a=fail or b=fail then return fail;
2199    else
2200      b:=Module(b!.H, b!.module, -b!.coeffs, b!.parts);
2201      return a+b;
2202    fi;
2203  end
2204); # SubModules
2205
2206InstallMethod(\*,"multiply module by scalar",[IsScalar,IsAlgebraObjModule],
2207  function(n,b)
2208    if n = 0
2209    then return Module(b!.H, b!.module, 0, []);
2210    else return Module(b!.H, b!.module, n*b!.coeffs, b!.parts);
2211    fi;
2212  end
2213);
2214
2215InstallMethod(\*,"multiply module by scalar",[IsAlgebraObjModule,IsScalar],
2216  function(a,n)
2217    if n = 0
2218    then return Module(a!.H, a!.module, 0, []);
2219    else return Module(a!.H, a!.module, n*a!.coeffs, a!.parts);
2220    fi;
2221  end
2222);
2223
2224InstallMethod(\*,"multiply specht modules",[IsHeckeSpecht,IsHeckeSpecht],
2225  function(a,b) local x, y, ab, abcoeff, xy, z;
2226    if a=fail or b=fail then return fail;
2227    elif a!.H<>b!.H then
2228      Error("modules belong to different Grothendieck rings");
2229    fi;
2230    #a:=MakeSpechtOp(a,false);
2231    ab:=[[],[]];
2232    for x in [1..Length(a!.parts)] do
2233      for y in [1..Length(b!.parts)] do
2234        abcoeff:=a!.coeffs[x]*b!.coeffs[y];
2235        if abcoeff<>0*abcoeff then
2236          z:=LittlewoodRichardsonRule(a!.parts[x], b!.parts[y]);
2237          Append(ab[1], List(z, xy->abcoeff));
2238          Append(ab[2], z);
2239        fi;
2240      od;
2241    od;
2242    if ab=[] then return Module(a!.H, a!.module, 0, []);
2243    else return Collect(b!.H, b!.module, ab[1], ab[2]);
2244    fi;
2245  end
2246);
2247
2248InstallMethod(\*,"multiply projective indecomposable modules",[IsHeckePIM,IsHeckePIM],
2249  function(a,b) local x, nx;
2250    x:=MakeSpechtOp(a,false) * MakeSpechtOp(b,false);
2251    nx:=MakePIMOp(x,true);
2252    if nx<>fail then return nx; else return x; fi;
2253  end
2254);
2255
2256InstallMethod(\*,"multiply simple modules",[IsHeckeSimple,IsHeckeSimple],
2257  function(a,b) local x, nx;
2258    x:=MakeSpechtOp(a,false) * MakeSpechtOp(b,false);
2259    nx:=MakeSimpleOp(x,true);
2260    if nx<>fail then return nx; else return x; fi;
2261  end
2262);
2263
2264InstallMethod(\*,"multiply modules",[IsAlgebraObjModule,IsAlgebraObjModule],
2265  function(a,b)
2266    return MakeSpechtOp(a,false) * MakeSpechtOp(b,false);
2267  end
2268); # MulModules
2269
2270InstallMethod(\/,"divide module by scalar",[IsAlgebraObjModule,IsScalar],
2271  function(b,n) local x;
2272    if n=0 then Error("can't divide by 0!\n");
2273    else return Module(b!.H, b!.module, b!.coeffs/n, b!.parts);
2274    fi;
2275  end
2276); # DivModules
2277
2278################################################################################
2279
2280InstallMethod(InnerProduct,"inner product of modules",
2281  [IsAlgebraObjModule,IsAlgebraObjModule],
2282  function(a,b) local pr, x, y;
2283    if a=0*a or b=0*b then return 0;
2284    elif a!.module<>b!.module then
2285      a:=MakeSpechtOp(a,true);
2286      b:=MakeSpechtOp(b,true);
2287    fi;
2288
2289    pr:=0; x:=1; y:=1;  # use the fact that a.parts and b.parts are ordered
2290    while x <=Length(a!.parts) and y <=Length(b!.parts) do
2291      if a!.parts[x]=b!.parts[y] then
2292        pr:=pr + a!.coeffs[x]*b!.coeffs[y];
2293        x:=x + 1; y:=y + 1;
2294      elif a!.parts[x]<b!.parts[y] then x:=x + 1;
2295      else y:=y + 1;
2296      fi;
2297    od;
2298    return pr;
2299  end
2300);  # InnerProduct
2301
2302#F Returns the Coefficient of p in x
2303InstallMethod(CoefficientOp, "extract coefficient of a partition from module",
2304  [IsAlgebraObjModule,IsList],
2305  function(x,p) local pos;
2306    pos:=Position(x!.parts, p);
2307    if pos=fail then return 0;
2308    else return x!.coeffs[pos];
2309    fi;
2310  end
2311);  # Coefficient
2312
2313#F Returns true if all coefficients are non-negative
2314InstallMethod(PositiveCoefficients, "test if all coefficients are non-negative",
2315  [IsAlgebraObjModule],
2316  function(x) local c;
2317    return ForAll(x!.coeffs, c->c>=0);
2318  end
2319);
2320
2321InstallMethod(PositiveCoefficients,
2322  "test if all coefficients of a Fock module are non-negative",
2323  [IsFockModule],
2324  function(x)
2325    return ForAll(x!.coeffs, p->( IsInt(p) and p>=0 ) or
2326                      ForAll(CoefficientsOfLaurentPolynomial(p)[1], c->c>=0) );
2327  end
2328); # PositiveCoefficients
2329
2330#F Returns true if all coefficients are integral
2331InstallMethod(IntegralCoefficients, "test if all coefficients are integral",
2332  [IsAlgebraObjModule],
2333  function(x) local c;
2334    return ForAll(x!.coeffs, c->IsInt(c));
2335  end
2336);
2337
2338InstallMethod(IntegralCoefficients,
2339  "test if all coefficients of a Fock module are non-negative",
2340  [IsFockModule],
2341  function(x)
2342    return ForAll(x!.coeffs, p-> ( IsInt(p) and p>=0 ) or
2343                  ForAll(CoefficientsOfLaurentPolynomial(p)[1], c->IsInt(c)) );
2344  end
2345); # IntegralCoefficients
2346
2347## INDUCTION AND RESTRICTION ###################################################
2348
2349## The next functions are for restricting and inducing Specht
2350## modules. They all assume that their arguments are indeed Specht
2351## modules; conversations are done in H.operations.X.Y() as necessary.
2352
2353## r-induction: on Specht modules:
2354InstallMethod(RInducedModuleOp, "r-induction on specht modules",
2355  [IsAlgebraObj,IsHeckeSpecht,IsInt,IsInt],
2356  function(H, a, e, r) local ind, x, i, j, np;
2357    ind:=[[],[]];
2358    for x in [1..Length(a!.parts)] do
2359      for i in [1..Length(a!.parts[x])] do
2360        if (a!.parts[x][i] + 1 - i) mod e=r then
2361          if i=1 or a!.parts[x][i-1] > a!.parts[x][i] then
2362            np:=StructuralCopy(a!.parts[x]);
2363            np[i]:=np[i]+1;
2364            Add(ind[1], a!.coeffs[x]);
2365            Add(ind[2], np);
2366          fi;
2367        fi;
2368      od;
2369      if ( -Length(a!.parts[x]) mod e)=r then
2370        np:=StructuralCopy(a!.parts[x]); Add(np, 1);
2371        Add(ind[1],a!.coeffs[x]);
2372        Add(ind[2],np);
2373      fi;
2374    od;
2375    if ind=[ [],[] ] then return Module(H,"S",0,[]);
2376    else return Collect(H,"S", ind[1], ind[2]);
2377    fi;
2378  end
2379); # RInducedModule
2380
2381## String-induction: add s r's from each partition in x (ignoring
2382## multiplicities). Does both standard and q-induction.
2383
2384## We look at the size of x.module to decide whether we want to use
2385## ordinary induction or q-induction (in the Fock space). We could
2386## write H.operations.X.SInduce to as to make this choice for us, or
2387## do q-induction always, setting v=1 afterwards, but this seems the
2388## better choice.
2389InstallMethod(SInducedModuleOp,"string-induction on specht modules",
2390  [IsAlgebraObj,IsHeckeSpecht,IsInt,IsInt,IsInt],
2391  function(H, x, e, s, r) local coeffs, parts, y, z, sinduced;
2392    # add n nodes of residue r to the partition y from the i-th row down
2393    sinduced:=function(y, n, e, r, i) local ny, j, z;
2394      ny:=[];
2395      for j in [i..Length(y)-n+1] do
2396        if r=(y[j] - j + 1) mod e then
2397          if j=1 or y[j] < y[j-1] then
2398            z:=StructuralCopy(y);
2399            z[j]:=z[j] + 1; # only one node of residue r can be added
2400            if n=1 then Add(ny, z);   # no more nodes to add
2401            else Append(ny, sinduced(z, n-1, e, r, j+1));
2402            fi;
2403          fi;
2404        fi;
2405      od;
2406      return ny;
2407    end;
2408
2409    if s=0 then return Module(x!.H,x!.module,1,[]); fi;
2410    coeffs:=[]; parts:=[];
2411    for y in [1..Length(x!.parts)] do
2412      Append(parts,sinduced(x!.parts[y], s, e, r, 1));
2413      Append(coeffs,List([1..Length(parts)-Length(coeffs)],r->x!.coeffs[y]));
2414      if r=( -Length(x!.parts[y]) mod e) then # add a node to the bottom
2415        z:=StructuralCopy(x!.parts[y]);
2416        Add(z,1);
2417        if s > 1 then                        # need to add some more nodes
2418          Append(parts,sinduced(z, s-1, e, r, 1));
2419          Append(coeffs,List([1..Length(parts)-Length(coeffs)],
2420                             r->x!.coeffs[y]));
2421        else Add(coeffs, x!.coeffs[y]); Add(parts, z);
2422        fi;
2423      fi;
2424    od;
2425
2426    if coeffs=[] then return Module(H, x!.module,0,[]);
2427    else return Collect(H, x!.module, coeffs, parts);
2428    fi;
2429  end
2430);  # SInducedModule
2431
2432## r-restriction
2433InstallMethod(RRestrictedModuleOp,"r-restriction on specht modules",
2434  [IsAlgebraObj,IsHeckeSpecht,IsInt,IsInt],
2435  function(H, a, e, r) local ind, x, i, j, np;
2436    ind:=[[],[]];
2437    for x in [1..Length(a!.parts)] do
2438      for i in [1..Length(a!.parts[x])] do
2439        if (a!.parts[x][i] - i) mod e=r then
2440          np:=StructuralCopy(a!.parts[x]);
2441          if i=Length(a!.parts[x]) or np[i] > np[i+1] then
2442            np[i]:=np[i] - 1;
2443            if np[i]=0 then Unbind(np[i]); fi;
2444            Add(ind[1], a!.coeffs[x]); Add(ind[2], np);
2445          fi;
2446        fi;
2447      od;
2448    od;
2449    if ind=[ [],[] ] then return Module(H,"S",0,[]);
2450    else return Collect(H,"S", ind[1], ind[2]);
2451    fi;
2452  end
2453); #RRestrictedModule
2454
2455## string-restriction: remove m r's from each partition in x
2456InstallMethod(SRestrictedModuleOp,"string-restriction on specht modules",
2457  [IsAlgebraObj,IsHeckeSpecht,IsInt,IsInt,IsInt],
2458  function(H,x,e,s,r) local coeffs, parts, y, i, srestricted;
2459    ## remove n nodes from y from the ith row down
2460    srestricted:=function(y, n, e, r, i) local ny, j, z;
2461      ny:=[];
2462      for j in [i..Length(y)-n+1] do
2463        if r=(y[j] - j) mod e then
2464          if j=Length(y) or y[j] > y[j+1] then
2465            z:=StructuralCopy(y);
2466            z[j]:=z[j] - 1;
2467            if z[j]=0 then   # n must be 1
2468              Unbind(z[j]);
2469              Add(ny, z);
2470            elif n=1 then Add(ny, z); # no mode nodes to remove
2471            else Append(ny, srestricted(z, n-1, e, r, j+1));
2472            fi;
2473          fi;
2474        fi;
2475      od;
2476      return ny;
2477    end;
2478
2479    coeffs:=[]; parts:=[];
2480    for y in [1..Length(x!.parts)] do
2481      Append(parts, srestricted(x!.parts[y], s, e, r, 1));
2482      Append(coeffs,List([1..Length(parts)-Length(coeffs)],i->x!.coeffs[y]));
2483    od;
2484    if parts=[] then return Module(H,"S",0,[]);
2485    else return Collect(H,"S", coeffs, parts);
2486    fi;
2487  end
2488);  # SRestrictedModule
2489
2490## Induction and restriction; for S()
2491InstallMethod(RInducedModuleOp, "r-induction for specht modules",
2492  [IsAlgebraObj, IsHeckeSpecht, IsList],
2493  function(H, x, list) local r;
2494    if x=fail or x=0*x then return x;
2495    elif list=[] then return RInducedModule(H,x,1,0);
2496    elif H!.e=0 then
2497      Error("Induce, r-induction is not defined when e=0.");
2498    elif ForAny(list,r-> r>=H!.e or r<0) then
2499      Error("Induce, r-induction is defined only when 0<=r<e.\n");
2500    else
2501      for r in list do
2502        x:=RInducedModule(H,x,H!.e,r);
2503      od;
2504      return x;
2505    fi;
2506  end
2507);
2508
2509InstallMethod(RInducedModuleOp, "r-induction for projective indecomposable modules",
2510  [IsAlgebraObj, IsHeckePIM, IsList],
2511  function(H, x, list) local nx;
2512    x:=RInducedModule(H,MakeSpechtOp(x,false),list);
2513    if x=fail or x=0*x then return x; fi;
2514    nx:=MakePIMOp(x,false);
2515    if nx<>fail then return nx; else return x; fi;
2516  end
2517);
2518
2519InstallMethod(RInducedModuleOp, "r-induction for simple modules",
2520  [IsAlgebraObj, IsHeckeSimple, IsList],
2521  function(H, x, list) local nx;
2522    x:=RInducedModule(H,MakeSpechtOp(x,false),list);
2523    if x=fail or x=0*x then return x; fi;
2524    nx:=MakeSimpleOp(x,false);
2525    if nx<>fail then return nx; else return x; fi;
2526  end
2527);
2528
2529InstallMethod(RInducedModuleOp, "r-induction for Fock space specht modules",
2530  [IsAlgebraObj,IsFockSpecht,IsList],
2531  function(H, x, list) local r;
2532    if list=[] then return Sum([0..H!.e-1],r->qSInducedModule(H,x,1,r));
2533    elif H!.e=0 then
2534      Error("Induce, r-induction is not defined when e=0.");
2535    elif ForAny(list,r-> r>=H!.e or r<0) then
2536      Error("Induce, r-induction is defined only when 0<=r<e.\n");
2537    else
2538      for r in list do   ## we could do slightly better here
2539        x:= qSInducedModule(H,x,1,r);
2540      od;
2541      return x;
2542    fi;
2543  end
2544);
2545
2546InstallMethod(RInducedModuleOp,
2547  "r-induction for Fock space projective indecomposable modules",
2548  [IsAlgebraObj,IsFockPIM,IsList],
2549  function(H,x,list)
2550    return MakePIMOp(RInducedModule(H,MakeSpechtOp(x,false),list),false);
2551  end
2552);
2553
2554InstallMethod(RInducedModuleOp,
2555  "r-induction for Fock space simple modules",
2556  [IsAlgebraObj,IsFockSimple,IsList],
2557  function(H,x,list)
2558    return MakeSimpleOp(RInducedModule(H,MakeSpechtOp(x,false),list),false);
2559  end
2560); # RInducedModule
2561
2562InstallMethod(RRestrictedModuleOp, "r-restriction for specht modules",
2563  [IsAlgebraObj, IsHeckeSpecht, IsList],
2564  function(H, x, list) local r;
2565    if x=fail or x=0*x then return x;
2566    elif list=[] then return RRestrictedModule(H,x,1,0);
2567    elif H!.e=0 then
2568      Error("Restrict, r-restriction is not defined when e=0.");
2569   elif ForAny(list,r-> r>=H!.e or r<0) then
2570      Error("Restrict, r-restriction is defined only when 0<=r<e.\n");
2571    else
2572      for r in list do
2573        x:=RRestrictedModule(H,x,H!.e,r);
2574      od;
2575      return x;
2576    fi;
2577  end
2578);
2579
2580InstallMethod(RRestrictedModuleOp, "r-restriction for projective indecomposable modules",
2581  [IsAlgebraObj, IsHeckePIM, IsList],
2582  function(H, x, list) local nx;
2583    x:=RRestrictedModule(H,MakeSpechtOp(x,false),list);
2584    if x=fail or x=0*x then return x; fi;
2585    nx:=MakePIMOp(x,false);
2586    if nx<>fail then return nx; else return x; fi;
2587  end
2588);
2589
2590InstallMethod(RRestrictedModuleOp, "r-restriction for simple modules",
2591  [IsAlgebraObj, IsHeckeSimple, IsList],
2592  function(H, x, list) local nx;
2593    x:=RRestrictedModule(H,MakeSpechtOp(x,false),list);
2594    if x=fail or x=0*x then return x; fi;
2595    nx:=MakeSimpleOp(x,false);
2596    if nx<>fail then return nx; else return x; fi;
2597  end
2598);
2599
2600InstallMethod(RRestrictedModuleOp, "r-restriction for Fock space specht modules",
2601  [IsAlgebraObj,IsFockSpecht,IsList],
2602  function(H, x, list) local r;
2603    if list=[] then return Sum([0..H!.e-1],r->qSRestrictedModule(H,x,1,r));
2604    elif H!.e=0 then
2605      Error("Restrict, r-restriction is not defined when e=0.");
2606    elif ForAny(list,r-> r>=H!.e or r<0) then
2607      Error("Restrict, r-restriction is defined only when 0<=r<e.\n");
2608    else
2609      for r in list do   ## we could do slightly better here
2610        x:= qSRestrictedModule(H,x,1,r);
2611      od;
2612      return x;
2613    fi;
2614  end
2615);
2616
2617InstallMethod(RRestrictedModuleOp,
2618  "r-restriction for Fock space projective indecomposable modules",
2619  [IsAlgebraObj,IsFockPIM,IsList],
2620  function(H,x,list)
2621    return MakePIMOp(RRestrictedModule(H,MakeSpechtOp(x,false),list),false);
2622  end
2623);
2624
2625InstallMethod(RRestrictedModuleOp,
2626  "r-restriction for Fock space simple modules",
2627  [IsAlgebraObj,IsFockSimple,IsList],
2628  function(H,x,list)
2629    return MakeSimpleOp(RRestrictedModule(H,MakeSpechtOp(x,false),list),false);
2630  end
2631); # RRestrictedModule
2632
2633InstallMethod(SInducedModuleOp,"string induction for specht modules",
2634  [IsAlgebraObj, IsHeckeSpecht, IsList],
2635  function(H, x, list) local r;
2636    if x=fail or x=0*x then return x;
2637    elif Length(list)=1 then
2638      list:=list[1];
2639      if list=0 then return Module(H,"Sq",1,[]); fi;
2640      while list > 0 do
2641        x:=SInducedModule(H,x,1,1,0);
2642        list:=list-1;
2643      od;
2644      return x;
2645    elif H!.e=0 then
2646      Error("SInduce, string induction is not defined when e=0.");
2647    elif list[2]>H!.e or list[2]<0 then
2648      Error("SInduce, string induction is defined only when 0<=r<e.\n");
2649    else return SInducedModule(H, x, H!.e, list[1], list[2]);
2650    fi;
2651  end
2652);
2653
2654InstallMethod(SInducedModuleOp, "string induction for projective indecomposable modules",
2655  [IsAlgebraObj, IsHeckePIM, IsList],
2656  function(H, x, list) local nx;
2657    x:=SInducedModule(H,MakeSpechtOp(x,false),list);
2658    if x=fail or x=0*x then return x; fi;
2659    nx:=MakePIMOp(x,false);
2660    if nx<>fail then return nx; else return x; fi;
2661  end
2662);
2663
2664InstallMethod(SInducedModuleOp, "string induction for simple modules",
2665  [IsAlgebraObj, IsHeckeSimple, IsList],
2666  function(H, x, list) local nx;
2667    x:=SInducedModule(H,MakeSpechtOp(x,false),list);
2668    if x=fail or x=0*x then return x; fi;
2669    nx:=MakeSimpleOp(x,false);
2670    if nx<>fail then return nx; else return x; fi;
2671  end
2672);
2673
2674InstallMethod(SInducedModuleOp, "string induction for Fock space specht modules",
2675  [IsAlgebraObj,IsFockSpecht,IsList],
2676  function(H, x, list) local r;
2677    if Length(list)=1 then
2678      list:=list[1];
2679      if list=0 then return Module(H,"Sq",1,[]); fi;
2680      while list > 0 do
2681        x:=Sum([0..H!.e-1],r->qSInducedModule(H,x,1,r));
2682        list:=list-1;
2683      od;
2684      return x;
2685    elif H!.e=0 then
2686      Error("SInduce, string induction is not defined when e=0.");
2687    elif list[2]>H!.e or list[2]<0 then
2688      Error("SInduce, string induction is defined only when 0<=r<e.\n");
2689    else return qSInducedModule(H, x, list[1], list[2]);
2690    fi;
2691  end
2692);
2693
2694InstallMethod(SInducedModuleOp,
2695  "string induction for Fock space projective indecomposable modules",
2696  [IsAlgebraObj,IsFockPIM,IsList],
2697  function(H,x,list)
2698    return MakePIMOp(SInducedModule(H,MakeSpechtOp(x,false),list),false);
2699  end
2700);
2701
2702InstallMethod(SInducedModuleOp,
2703  "string induction for Fock space simple modules",
2704  [IsAlgebraObj,IsFockSimple,IsList],
2705  function(H,x,list)
2706    return MakeSimpleOp(SInducedModule(H,MakeSpechtOp(x,false),list),false);
2707  end
2708); # SInducedModule
2709
2710InstallMethod(SRestrictedModuleOp,"string restriction for specht modules",
2711  [IsAlgebraObj, IsHeckeSpecht, IsList],
2712  function(H, x, list) local r;
2713    if x=fail or x=0*x then return x;
2714    elif Length(list)=1 then
2715      list:=list[1];
2716      if list=0 then return Module(H,"Sq",1,[]); fi;
2717      while list > 0 do
2718        x:=SRestrictedModule(H,x,1,1,0);
2719        list:=list-1;
2720      od;
2721      return x;
2722    elif H!.e=0 then
2723      Error("SRestrict, r-restriction is not defined when e=0.");
2724    elif list[2]>H!.e or list[2]<0 then
2725      Error("SRestrict, r-restriction is defined only when 0<=r<e.\n");
2726    else return SRestrictedModule(H, x, H!.e, list[1], list[2]);
2727    fi;
2728  end
2729);
2730
2731InstallMethod(SRestrictedModuleOp, "string restriction for projective indecomposable modules",
2732  [IsAlgebraObj, IsHeckePIM, IsList],
2733  function(H, x, list) local nx;
2734    x:=SRestrictedModule(H,MakeSpechtOp(x,false),list);
2735    if x=fail or x=0*x then return x; fi;
2736    nx:=MakePIMOp(x,false);
2737    if nx<>fail then return nx; else return x; fi;
2738  end
2739);
2740
2741InstallMethod(SRestrictedModuleOp, "string restriction for simple modules",
2742  [IsAlgebraObj, IsHeckeSimple, IsList],
2743  function(H, x, list) local nx;
2744    x:=SRestrictedModule(H,MakeSpechtOp(x,false),list);
2745    if x=fail or x=0*x then return x; fi;
2746    nx:=MakeSimpleOp(x,false);
2747    if nx<>fail then return nx; else return x; fi;
2748  end
2749);
2750
2751InstallMethod(SRestrictedModuleOp, "string restriction for Fock space specht modules",
2752  [IsAlgebraObj,IsFockSpecht,IsList],
2753  function(H, x, list) local r;
2754    if Length(list)=1 then
2755      list:=list[1];
2756      if list=0 then return Module(H,"Sq",1,[]); fi;
2757      while list > 0 do
2758        x:=Sum([0..H!.e-1],r->qSRestrictedModule(H,x,1,r));
2759        list:=list-1;
2760      od;
2761      return x;
2762    elif H!.e=0 then
2763      Error("SRestrict, string restriction is not defined when e=0.");
2764    elif list[2]>H!.e or list[2]<0 then
2765      Error("SRestrict, string restriction is defined only when 0<=r<e.\n");
2766    else return qSRestrictedModule(H, x, list[1], list[2]);
2767    fi;
2768  end
2769);
2770
2771InstallMethod(SRestrictedModuleOp,
2772  "string restriction for Fock space projective indecomposable modules",
2773  [IsAlgebraObj,IsFockPIM,IsList],
2774  function(H,x,list)
2775    return MakePIMOp(SRestrictedModule(H,MakeSpechtOp(x,false),list),false);
2776  end
2777);
2778
2779InstallMethod(SRestrictedModuleOp,
2780  "string restriction for Fock space simple modules",
2781  [IsAlgebraObj,IsFockSimple,IsList],
2782  function(H,x,list)
2783    return MakeSimpleOp(SRestrictedModule(H,MakeSpechtOp(x,false),list),false);
2784  end
2785); #SRestrictedModule
2786
2787InstallMethod(RInducedModuleOp,
2788  "toplevel r-induction",
2789  [IsAlgebraObjModule,IsList],
2790  function(x,list)
2791    return RInducedModuleOp(x!.H,x,list);
2792  end
2793); #RInducedModule
2794
2795InstallMethod(RRestrictedModuleOp,
2796  "toplevel r-restriction",
2797  [IsAlgebraObjModule,IsList],
2798  function(x,list)
2799    return RRestrictedModuleOp(x!.H,x,list);
2800  end
2801); #RRestrictedModule
2802
2803InstallMethod(SInducedModuleOp,
2804  "toplevel string induction",
2805  [IsAlgebraObjModule,IsList],
2806  function(x,list)
2807    return SInducedModuleOp(x!.H,x,list);
2808  end
2809); #SInducedModule
2810
2811InstallMethod(SRestrictedModuleOp,
2812  "toplevel string restriction",
2813  [IsAlgebraObjModule,IsList],
2814  function(x,list)
2815    return SRestrictedModuleOp(x!.H,x,list);
2816  end
2817); #SRestrictedModule
2818
2819## Q-INDUCTION AND Q-RESTRICTION ###############################################
2820
2821## notice that we can't pull the trick to induce all residues at once
2822## that we used in InducedModule() etc. as we have to keep track of the
2823## number of addable and removable nodes of each residue. Rather than
2824## do this we just call this function as many times as necessary.
2825InstallMethod(qSInducedModule,"q-induction for modules",
2826  [IsAlgebraObj,IsAlgebraObjModule,IsInt,IsInt],
2827  function(H,x,s,r) local coeffs, parts, y, z, qsinduced, v;
2828    v:=H!.Indeterminate;
2829
2830    # add n nodes of residue r to the partition y from the i-th row down
2831    # here exp is the exponent of the indeterminate
2832    qsinduced:=function(y, n, r, i, exp) local ny, j, z;
2833     ny:=[];
2834     for j in [i..Length(y)-n+1] do
2835       if y[j]>0 and r=(y[j]-j) mod H!.e and (j=Length(y) or y[j]>y[j+1])
2836       then exp:=exp-n;               ## removable node of residue r
2837       elif r=(y[j] - j + 1) mod H!.e then
2838         if j=1 or y[j] < y[j-1] then ## addable node of residue r
2839           z:=StructuralCopy(y);
2840           z[j]:=z[j] + 1; # only one node of residue r can be added
2841           if n=1 then Add(ny, [exp,z] );   # no more nodes to add
2842           else Append(ny, qsinduced(z, n-1, r, j+1, exp));
2843           fi;
2844           exp:=exp+n;
2845         fi;
2846       fi;
2847     od;
2848     return ny;
2849    end;
2850
2851    coeffs:=[]; parts:=[];
2852    for y in [1..Length(x!.parts)] do
2853      if r=( -Length(x!.parts[y]) mod H!.e) then # add a node to the bottom
2854        z:=StructuralCopy(x!.parts[y]);
2855        Add(z,0);
2856        for z in qsinduced(z,s,r,1,0)  do
2857          if z[1]=0 then Add(coeffs, x!.coeffs[y]);
2858          else Add(coeffs, x!.coeffs[y]*v^z[1]);
2859          fi;
2860          if z[2][Length(z[2])]=0 then Unbind(z[2][Length(z[2])]); fi;
2861          Add(parts, z[2]);
2862        od;
2863      else
2864        for z in qsinduced(x!.parts[y],s,r,1,0) do
2865          if z[1]=0 then Add(coeffs, x!.coeffs[y]);
2866          else Add(coeffs, x!.coeffs[y]*v^z[1]);
2867          fi;
2868          Add(parts, z[2]);
2869        od;
2870      fi;
2871    od;
2872
2873    if coeffs=[] then return Module(H,x!.module,0,[]);
2874    else return Collect(H,x!.module, coeffs, parts);
2875    fi;
2876  end
2877);  # qSInducedModule
2878
2879## string-restriction: remove m r's from each partition in x
2880## ** should allow restricting s-times also
2881InstallMethod(qSRestrictedModule,"q-restriction for modules",
2882  [IsAlgebraObj,IsAlgebraObjModule,IsInt,IsInt],
2883  function(H, x, s, r) local coeffs, parts, z, y, i, e, exp, v, qrestricted;
2884    v:=H!.Indeterminate;
2885
2886    qrestricted:=function(y, n, r, i, exp) local ny, j, z;
2887      ny:=[];
2888      for j in [i,i-1..n] do
2889        if y[j]>0 and r=(y[j]+1-j) mod H!.e and (j=1 or y[j]<y[j-1]) then
2890           exp:=exp-n;                 ## an addable node of residue r
2891        elif r=(y[j] - j) mod H!.e then   ## removable node of residue r
2892          if j=Length(y) or y[j] > y[j+1] then
2893            z:=StructuralCopy(y);
2894            z[j]:=z[j]-1;
2895            if z[j]=0 then Unbind(z[j]); fi;
2896            if n=1 then Add(ny, [exp,z]); # no mode nodes to remove
2897            else Append(ny, qrestricted(z, n-1, r, j-1, exp));
2898            fi;
2899            exp:=exp+n;
2900          fi;
2901        fi;
2902      od;
2903      return ny;
2904    end;
2905
2906    e:=x!.H!.e;
2907    coeffs:=[]; parts:=[];
2908    if s=0 then return Module(H,"Sq",1,[]); fi;
2909    for y in [1..Length(x!.parts)] do
2910      if -Length(x!.parts[y]) mod H!.e = r then exp:=-s; else exp:=0; fi;
2911      for z in qrestricted(x!.parts[y], s, r, Length(x!.parts[y]), exp) do
2912        if z[1]=0 then Add(coeffs, x!.coeffs[y]);
2913        else Add(coeffs, x!.coeffs[y]*v^z[1]);
2914        fi;
2915        Add(parts, z[2]);
2916      od;
2917    od;
2918    if parts=[] then return Module(H,"Sq",0,[]);
2919    else return Collect(H, "Sq", coeffs, parts);
2920    fi;
2921  end
2922);  # qSRestrict
2923
2924## DECOMPOSITION MATRICES ######################################################
2925
2926## The following directory is searched by ReadDecompositionMatrix()
2927## when it is looking for decomposition matrices. By default, it points
2928## to the current directory (if set, the current directory is not
2929## searched).
2930if not IsBound(SpechtDirectory) then SpechtDirectory:=Directory("."); fi;
2931
2932## This variable is what is used in the decomposition matrices files saved
2933## by SaveDecompositionMatrix() (and also the variable which contains them
2934## when they are read back in).
2935A_Specht_Decomposition_Matrix:=fail;
2936
2937## Finally, we can define the creation function for decomposition matrices
2938## (note that NewDM() does not add the partition labels to the decomp.
2939## matrix; this used to be done here but now happens in PrintDM() because
2940## crystallized matrices may never be printed and this operation is
2941## expensive).
2942## **NOTE: we assume when extracting entries from d that d.rows is
2943## ordered lexicographically. If this is not the case then addition
2944## will not work properly.
2945InstallOtherMethod(DecompositionMatrix,"creates a new decomposition matrix",
2946  [IsAlgebraObj,IsList,IsList,IsBool],
2947  function(H, rows, cols, decompmat) local d;
2948    d := rec(d:=[],      # matrix entries
2949       rows:=rows, # matrix rows
2950       cols:=cols, # matrix cols
2951       inverse:=[], dimensions:=[], ## inverse matrix and dimensions
2952       H:=H
2953    );
2954
2955    if decompmat then
2956      return Objectify(DecompositionMatrixType,d);
2957    else
2958      return Objectify(CrystalDecompositionMatrixType,d);
2959    fi;
2960  end
2961); # DecompositonMatrix
2962
2963InstallMethod(\=, "for decomposition matrices",
2964  [IsDecompositionMatrix,IsDecompositionMatrix],
2965  function(d1,d2)
2966    return d1!.d=d2!.d and d1!.cols = d2!.cols and d1!.rows = d2!.rows;
2967  end
2968); # Equal matrices
2969
2970InstallMethod(CopyDecompositionMatrix, "for decomposition matrices",
2971  [IsDecompositionMatrix],
2972  function(d) local newd;
2973    newd:=DecompositionMatrix(
2974      d!.H, StructuralCopy(d!.rows), StructuralCopy(d!.cols),
2975      not IsCrystalDecompositionMatrix(d)
2976      );
2977    newd!.d:=StructuralCopy(d!.d);
2978    newd!.inverse:=StructuralCopy(d!.inverse);
2979    newd!.dimensions:=StructuralCopy(d!.dimensions);
2980    return newd;
2981  end
2982); # CopyDecompositionMatrix
2983
2984## Used by SaveDecomposition matrix to update CrystalMatrices[]
2985InstallMethod(Store,"for crystal decomposition matrices",
2986  [IsCrystalDecompositionMatrix,IsInt],
2987  function(d,n) d!.H!.CrystalMatrices[n]:=d; end
2988);
2989
2990## Used by SaveDecomposition matrix to update DecompositionMatrices[]
2991InstallMethod(Store,"for decomposition matrices",[IsDecompositionMatrix,IsInt],
2992  function(d,n) d!.H!.DecompositionMatrices[n]:=d; end
2993);
2994
2995## This also needs to be done for crystal matrices (this wasn't
2996## put in above because normal decomposition matrices don't
2997## specialise.
2998InstallMethod(Specialized,"specialise CDM",
2999  [IsCrystalDecompositionMatrix,IsInt],
3000  function(d,a) local sd, c, p, coeffs, v;
3001    v:=d!.H!.Indeterminate;
3002    sd:=DecompositionMatrix(d!.H,d!.rows,d!.cols,true);
3003    for c in [1..Length(d!.cols)] do
3004      if IsBound(d!.d[c]) then
3005        sd!.d[c]:=rec();
3006        coeffs:=List(d!.d[c].coeffs*v^0,p->Value(p,a));
3007        p:=List(coeffs,p->p<>0);
3008        if true in p then
3009          sd!.d[c]:=rec(coeffs:=ListBlist(coeffs,p),
3010                        parts:=ListBlist(d!.d[c].parts,p) );
3011        else sd!.d[c]:=rec(coeffs:=[0], parts:=[ [] ] );
3012        fi;
3013      fi;
3014      if IsBound(d!.inverse[c]) then
3015        coeffs:=List(d!.inverse[c].coeffs*v^0,p->Value(p,a));
3016        p:=List(coeffs,p->p<>0);
3017        if true in p then
3018          sd!.inverse[c]:=rec(coeffs:=ListBlist(coeffs,p),
3019                          parts:=ListBlist(d!.inverse[c].parts,p) );
3020        else sd!.d[c]:=rec(coeffs:=[0], parts:=[ [] ] );
3021        fi;
3022      fi;
3023    od;
3024    return sd;
3025  end
3026);
3027
3028InstallMethod(Specialized,"specialise CDM",
3029  [IsCrystalDecompositionMatrix], a->Specialized(a,1)
3030);
3031
3032## Specialization taking Xq -> X
3033InstallMethod(Specialized,"specialise Fock module",
3034  [IsFockModule,IsInt],
3035  function(x,a) local coeffs, c;
3036    coeffs:=List(x!.coeffs*(x!.H!.Indeterminate)^0,c->Value(c,a));
3037    c:=List(coeffs,c->c<>0);
3038    if true in c then return Module(x!.H,x!.module{[1]},
3039                                ListBlist(coeffs,c),ListBlist(x!.parts,c));
3040    else return Module(x!.H,x!.module{[1]},0,[]);
3041    fi;
3042  end
3043);
3044
3045InstallMethod(Specialized,"specialise Fock module",
3046  [IsFockModule], x->Specialized(x,1)
3047); # Specialized
3048
3049## writes D(mu) as a linear combination of S(nu)'s if possible
3050InstallMethod(Invert, "for a decomposition matrix and a partition",
3051  [IsDecompositionMatrix,IsList],
3052  function(d,mu) local c, S, D, inv, smu, l, tmp;
3053    if IsCrystalDecompositionMatrix(d) then S:="Sq"; D:="Dq";
3054    else S:="S"; D:="D";
3055    fi;
3056
3057    c:=Position(d!.cols,mu);
3058    if c=fail then return fail;
3059    elif IsBound(d!.inverse[c]) then
3060      return Module(d!.H,S,d!.inverse[c].coeffs,
3061                    List(d!.inverse[c].parts,l->d!.cols[l]));
3062    fi;
3063
3064    inv:=Module(d!.H,S,1,mu);
3065    tmp:=MakeSimpleOp(d,inv);
3066    if tmp=fail then
3067      smu:=fail;
3068    else
3069      smu:=Module(d!.H,D,1,mu)-tmp;
3070    fi;
3071
3072    while smu<>fail and smu<>0*smu do
3073      inv:=inv+Module(d!.H,S,smu!.coeffs[1],smu!.parts[1]);
3074      tmp:=MakeSimpleOp(d, Module(d!.H,S,-smu!.coeffs[1],smu!.parts[1]));
3075      if tmp=fail then
3076        smu:=fail;
3077      else
3078        smu:=smu+tmp;
3079      fi;
3080    od;
3081    if smu=fail then return fail; fi;
3082
3083    d!.inverse[c]:=rec(coeffs:=inv!.coeffs,
3084                  parts:=List(inv!.parts,l->Position(d!.cols,l)));
3085    return inv;
3086  end
3087);
3088
3089#P This function adds the column for Px to the decomposition matrix <d>.
3090## if <checking>=true then Px is checked against its image under the
3091## Mullineux map; if this image is not there then we also insert it
3092## into <d>.
3093InstallMethod(AddIndecomposable,"fill out entries of decomposition matrix",
3094  [IsDecompositionMatrix,IsAlgebraObjModule,IsBool],
3095  function(d,Px,checking) local mPx, r, c;
3096    c:=Position(d!.cols, Px!.parts[Length(Px!.parts)]);
3097    if checking then
3098      ## first look to see if <Px> already exists in <d>
3099      if IsBound(d!.d[c]) then ## Px already exists
3100        Print("# AddIndecomposable: overwriting old value of P(",
3101              TightStringList(Px!.parts[Length(Px!.parts)]),") in <d>\n");
3102        Unbind(d!.inverse);       # just in case these were bound
3103        Unbind(d!.dimensions);
3104      fi;
3105      ## now looks at the image of <Px> under Mullineux
3106      if (not IsSchur(Px!.H) and IsERegular(Px!.H!.e,Px!.parts[Length(Px!.parts)]))
3107      and Px!.parts[Length(Px!.parts)]<>ConjugatePartition(Px!.parts[1]) then
3108        mPx:=MullineuxMap(Px);
3109        if IsBound(d!.d[Position(d!.cols,mPx!.parts[Length(Px!.parts)])])
3110        and MakePIMSpechtOp(d,mPx!.parts[Length(Px!.parts)]) <> mPx then
3111          Print("# AddIndecomposable(<d>,<Px>), WARNING: P(",
3112                TightStringList(Px!.parts[Length(Px!.parts)]), ") and P(",
3113                TightStringList(mPx!.parts[Length(Px!.parts)]),
3114                ") in <d> are incompatible\n");
3115        else
3116          Print("# AddIndecomposable(<d>,<Px>): adding MullineuxMap(<Px>) ",
3117                "to <d>\n");
3118          AddIndecomposable(d,mPx,false);
3119        fi;
3120      fi;
3121    fi;      # end of check
3122    d!.d[c]:=rec(coeffs:=Px!.coeffs,
3123                parts:=List(Px!.parts,r->Position(d!.rows,r)) );
3124  end
3125);
3126
3127#F This function checks to see whether Px is indecomposable using the
3128## decomposition matrix d. The basic idea is to loop through all of the
3129## (e-regular, unless IsSpecht=false) projectives Py in Px such that Px-Py
3130## has non-negative coefficients and to then apply the q-Schaper theorem
3131## and induce simples, together with a few other tricks to decide
3132## whether ir not Py slits off. If yes, then we move on; if we can't
3133## decide (or don't know the value of Py), we spit the dummy and return
3134## false, printing a "message from our sponsor" explaining why we failed
3135## if called from outside InducedModule(). If we can count for all
3136## projectives then we return true. Note that in this case the value
3137## of Px may have changed, but we update the original value of px=Px
3138## before leaving (whether we return false or true).
3139InstallMethod(IsNewIndecomposableOp, "checks whether the given module is indecomposable",
3140  [IsAlgebraObj, IsDecompositionMatrix,IsAlgebraObjModule,IsDecompositionMatrix,IsList],
3141  function(H,d,px,oldd,Mu)
3142    local Px,nu,regs,Py,y,z,a,b,n,mu,m,M,Message;
3143
3144    if px=fail and px=0*px then return false; fi;
3145
3146    if Mu=[fail] then Message:=Ignore;
3147    else Message:=Print;
3148    fi;
3149
3150    Px:=px; Py:=true; # strip PIMs from the top of Px
3151    while Py<>fail and Px<>0*Px do
3152      Py:=MakePIMSpechtOp(d,Px!.parts[Length(Px!.parts)]);
3153      if Py<>fail then Px:=Px-Px!.coeffs[Length(Px!.parts)]*Py; fi;
3154    od;
3155    if Px=0*Px then
3156      Message("# This module is a sum of known indecomposables.\n");
3157      return false;
3158    fi;
3159    if IntegralCoefficients(Px / Px!.coeffs[Length(Px!.parts)]) then
3160      Px:=Px / Px!.coeffs[Length(Px!.parts)];
3161   fi;
3162
3163    regs:=Obstructions(d,Px);
3164
3165    if Mu<>[] then regs:=Filtered(regs,mu->mu<Mu); fi;
3166    regs:=Obstructions(d,Px);
3167    for y in regs do   ## loop through projectives that might split
3168
3169      if not IsSchur(H) and MullineuxMap(H!.e,ConjugatePartition(Px!.parts[1]))
3170      <>Px!.parts[Length(Px!.parts)] then
3171        Py:=true;  ## strip any known indecomposables off the bottom of Px
3172        while Py<>fail and Px<>0*Px do
3173          Py:=MakePIMSpechtOp(d,ConjugatePartition(Px!.parts[1]));
3174          if Py<>fail and IsERegular(Py!.H!.e,Py!.parts[Length(Py!.parts)]) then
3175            Px:=Px-Px!.coeffs[1]*MullineuxMap(Py);
3176          else Py:=fail;
3177          fi;
3178        od;
3179      fi;
3180
3181      m:=0;            ## lower and upper bounds on decomposition the number
3182      if Px=0*Px then M:=0;
3183      else M:=Coefficient(Px,y)/Px!.coeffs[Length(Px!.parts)];
3184      fi;
3185      if M<>0 then Py:=MakePIMSpechtOp(d,y); fi;
3186      if not ( m=M or Px!.parts[Length(Px!.parts)]>=y ) then
3187        if Py=fail then
3188          Message("# The multiplicity of S(", TightStringList(y),
3189            ") in <Px> is zero; however, S(", TightStringList(y),
3190            ") is not known\n");
3191          px!.coeffs:=Px!.coeffs; px!.parts:=Px!.parts; return false;
3192        else
3193          Px:=Px-Coefficient(Px,y)*Py;
3194          if not PositiveCoefficients(Px) then BUG("IsNewIndecomposable",1);fi;
3195          M:=0;
3196        fi;
3197      fi;
3198
3199      if Px<>0*Px and IntegralCoefficients(Px/Px!.coeffs[Length(Px!.parts)]) then
3200        Px:=Px/Px!.coeffs[Length(Px!.parts)];
3201      fi;
3202
3203      ## remember that Px.coeffs[Length(Px.parts)] could be greater than 1
3204      if m<>M and (Coefficient(Px,y) mod Px!.coeffs[Length(Px!.parts)])<>0 then
3205        if Py=fail then
3206          Message("# <Px> is not indecomposable, as at least ",
3207            Coefficient(Px,y) mod Px!.coeffs[Length(Px!.parts)], " copies of P(",
3208            TightStringList(y), ") split off.\n# However, P(",
3209            TightStringList(y), ") is not known\n");
3210          px!.coeffs:=Px!.coeffs; px!.parts:=Px!.parts; return false;
3211        else
3212          ## this is at least projective; perhaps more still come off though
3213          Px:=Px-(Coefficient(Px,y) mod Px!.coeffs[Length(Px!.parts)])*Py;
3214          if not PositiveCoefficients(Px) then BUG("IsNewIndecomposable",2);fi;
3215          if IntegralCoefficients(Px/Px!.coeffs[Length(Px!.parts)]) then
3216            Px:=Px/Px!.coeffs[Length(Px!.parts)];
3217          fi;
3218        fi;
3219      fi;
3220
3221      ## At this point the coefficient of Sx in Px divides the coefficient of
3222      ## Sy in Px. If Py splits off then it does so in multiples of
3223      ## (Px:Sx)=Px.coeffs[Length(Px.parts)].
3224      if m<>M and (Py=fail
3225        or PositiveCoefficients(Px-Px!.coeffs[Length(Px!.parts)]*Py))
3226      then
3227        ## use the q-Schaper theorem to test whether Sy is contained in Px
3228        M:=Minimum(M,InnerProduct(Px/Px!.coeffs[Length(Px!.parts)],
3229                                  Schaper(H, y)));
3230        if M=0 then # NO!
3231          ## Px-(Px:Sy)Py is still projective so subtract Py if it is
3232          ## known. If Py=false (ie. not known), then at least we know
3233          ## that Px is not indecomposable, even though we couldn't
3234          ## calculate Py.
3235          if Py=fail then
3236            Message("# The multiplicity of S(", TightStringList(y),
3237              ") in P(", TightStringList(Px!.parts[Length(Px!.parts)]),
3238             ") is zero;\n#  however, P(", TightStringList(y),
3239             ") is not known.\n");
3240            px!.coeffs:=Px!.coeffs; px!.parts:=Px!.parts; return false;
3241          else
3242            Px:=Px-Coefficient(Px,y)*Py;
3243            if not PositiveCoefficients(Px) then BUG("IsNewIndecomposable",3);
3244            fi;
3245          fi;
3246        elif Px!.coeffs[Length(Px!.parts)]<>Coefficient(Px,y) then
3247          ## We know that (Px:Sy)>=m>0, but perhaps some Py's still split off
3248
3249          m:=1;
3250          if m=M then
3251            if Coefficient(Px,y)<>m*Px!.coeffs[Length(Px!.parts)] then
3252              if Py=fail then
3253                Message("# The multiplicity of S(", TightStringList(y),
3254                    ") in P(",TightStringList(Px!.parts[Length(Px!.parts)]),
3255                    ") is ", m, "however, P(",TightStringList(y),
3256                    ") is unknown.\n");
3257                px!.coeffs:=Px!.coeffs; px!.parts:=Px!.parts;
3258                return false;
3259              else
3260                Px:=Px-(Coefficient(Px,y)-Px!.coeffs[Length(Px!.parts)]*m)*Py;
3261                if not PositiveCoefficients(Px) then
3262                  BUG("IsNewIndecomposable",4);
3263                fi;
3264              fi;
3265            fi;
3266          fi;
3267
3268          if m<>M then
3269            ## see if we can calculate this decomposition number (this uses
3270            ## row and column removal)
3271            a:=DecompositionNumber(Px!.H, y, Px!.parts[Length(Px!.parts)]);
3272            if a<>fail then
3273              if Px!.coeffs[Length(Px!.parts)]*a=Coefficient(Px,y) then m:=a; M:=a;
3274              elif Py<>fail then
3275                ## precisely this many Py's come off
3276                Px:=Px-(Coefficient(Px,y)-Px!.coeffs[Length(Px!.parts)]*a)*Py;
3277                m:=a; M:=a; # upper and lower bounds are equal
3278                if not PositiveCoefficients(Px) then
3279                  BUG("IsNewIndecomposable",5);
3280                fi;
3281              fi;
3282            fi;
3283          fi;
3284
3285          if m<>M and Py=fail then ## nothing else we can do
3286            Message("# The multiplicity of S(", TightStringList(y),
3287                    ") in P(",TightStringList(Px!.parts[Length(Px!.parts)]),
3288                    ") is at least ", m, " and at most ", M,
3289                    ";\n# however, P(",TightStringList(y),") is unknown.\n");
3290            px!.coeffs:=Px!.coeffs; px!.parts:=Px!.parts;
3291            return false;
3292          fi;
3293
3294          if m<>M then
3295            ## Maybe the Mullineux map can lower M...
3296            M:=Minimum(M,Coefficient(Px,
3297                 Py!.parts[Length(Py!.parts)]/Px!.coeffs[Length(Px!.parts)]));
3298            if Coefficient(Px,y)>M*Px!.coeffs[Length(Px!.parts)] then
3299              Px:=Px-(Coefficient(Px,y)-M*Px!.coeffs[Length(Px!.parts)])*Py;
3300            fi;
3301            while m<M and not
3302            PositiveCoefficients(Px-(Px!.coeffs[Length(Px!.parts)]*(M-m))*Py) do
3303              m:=m+1;
3304            od;
3305          fi;
3306
3307          ## finally, we take a look at inducing the simples in oldd
3308          if m<>M and oldd<>fail then
3309            if not IsBound(oldd!.simples) then ## we have to first induce them
3310              oldd!.simples:=[];
3311              if IsBound(oldd!.ind) then       ## defined in InducedModule()
3312               for mu in [1..Length(oldd!.cols)] do
3313                  a:=Invert(oldd,oldd!.cols[mu]);
3314                  if a<>fail then
3315                    for n in [1..H!.e] do  ## induce simples of oldd
3316                      z:=Sum([1..Length(a!.coeffs)],b->a!.coeffs[b]
3317                           *oldd!.ind[Position(oldd!.rows,a!.parts[b])][n]);
3318                      if z<>0*z then Add(oldd!.simples,z);fi;
3319                    od;
3320                  fi;
3321                od;
3322              else   ## do everything by hand
3323                for mu in [1..Length(oldd!.cols)] do
3324                  a:=Invert(oldd,oldd!.cols[mu]);
3325                  if a<>fail then
3326                    for n in [0..H!.e-1] do
3327                      z:=RInducedModule(H,a,H!.e,n);
3328                      if z<>0*z then Add(oldd!.simples,z); fi;
3329                    od;
3330                  fi;
3331                od;
3332              fi;
3333            fi;
3334            mu:=Length(oldd!.simples);
3335            while mu >0 and m<M do
3336              z:=oldd!.simples[mu];
3337              if y=regs[Length(regs)]
3338              or Lexicographic(z!.parts[1],Py!.parts[Length(Py!.parts)]) then
3339                a:=InnerProduct(z,Py);
3340                if a<>0 then
3341                  b:=InnerProduct(z,Px)/Px!.coeffs[Length(Px!.parts)];
3342                  m:=Maximum(m,M-Int(b/a));
3343                fi;
3344              fi;
3345              mu:=mu-1;
3346            od;
3347            if Coefficient(Px,y)>M*Px!.coeffs[Length(Px!.parts)] then
3348              Px:=Px-(Coefficient(Px,y)-M*Px!.coeffs[Length(Px!.parts)])*Py;
3349            fi;
3350          fi;
3351          if m<>M then ## nothing else we can do
3352            px!.coeffs:=Px!.coeffs; px!.parts:=Px!.parts;
3353            Message("# The multiplicity of S(", TightStringList(y),
3354                ") in P(",TightStringList(Px!.parts[Length(Px!.parts)]),
3355                ") is at least ", m, " and at most ", M, ".\n");
3356            return false;
3357          fi;
3358        fi;   ## q-Schaper test
3359      fi;
3360    od;
3361    if Px=0*Px then
3362      Message("# This module is a sum of known indecomposables.\n");
3363      return false;
3364    elif Px!.coeffs[Length(Px!.parts)]<>1 then BUG("IsNewIndecomposable",6);
3365    else px!.coeffs:=Px!.coeffs; px!.parts:=Px!.parts; return true;
3366   fi;
3367  end
3368);  # IsNewIndecomposable
3369
3370#P A front end to d.operations.AddIndecomposable. This function adds <Px>
3371## into the decomposition matrix <d> and checks that it is compatible with
3372## its image under the Mullineux map, if this is already in <d>, and
3373## inserts it if it is not.
3374InstallMethod(AddIndecomposable,"fill out entries of decomposition matrix",
3375  [IsDecompositionMatrix,IsHeckeSpecht],
3376  function(d, Px)
3377    if Position(d!.cols, Px!.parts[Length(Px!.parts)])=fail then
3378      Print("# The projective P(",TightStringList(Px!.parts[Length(Px!.parts)]),
3379            ") is not listed in <D>\n");
3380    else AddIndecomposable(d,Px,true);
3381    fi;
3382  end
3383);# AddIndecomposable
3384
3385## This function will read the file "n" if n is a string; otherwise
3386## it will look for the relevant file for H(Sym_n). If crystal=true
3387## this will be a crystal decomposition matrix, otherwise it will be
3388## a 'normal' decomposition matrix. When IsInt(n) the lists
3389## CrystalMatrices[] and DecompositionMatrices[] are also checked, and
3390## the crystal decomposition matrix is calculated if it is not found
3391## and crystal=true (and IsInt(n)).
3392## Question: if crystal=false but IsBound(CrystalMatrices[n]) should
3393## we still try and read e<H.e>p0.n or specialize CrystalMatrices[n]
3394## immediately. We try and read the file first...
3395InstallMethod(ReadDecompositionMatrix, "load matrix from library",
3396  [IsAlgebraObj,IsInt,IsBool],
3397  function(H, n, crystal) local d, file, SpechtDirectory;
3398
3399    if not IsBound(SpechtDirectory) then SpechtDirectory:=""; fi;
3400
3401    if crystal then
3402      if IsBound(H!.CrystalMatrices[n]) then
3403        d:=H!.CrystalMatrices[n];
3404        if d=fail and H!.info.SpechtDirectory=SpechtDirectory then
3405          return fail;
3406        elif d<>fail and ForAll([1..Length(d!.cols)],c->IsBound(d!.d[c]))
3407        then return d;
3408        fi;
3409      fi;
3410      file:=Concatenation("e",String(H!.e),"crys.",String(n));
3411    else
3412      file:=Concatenation(H!.HeckeRing,".",String(n));
3413    fi;
3414    d:=ReadDecompositionMatrix(H,file,crystal);
3415    if crystal then H!.CrystalMatrices[n]:=d; fi;
3416    return d;
3417  end
3418);
3419
3420InstallMethod(ReadDecompositionMatrix, "load matrix from library",
3421  [IsAlgebraObj,IsString,IsBool],
3422  function(H, str, crystal)
3423    local msg, file, M, d, c, parts, coeffs, p, x, r, cm, rm;
3424
3425    A_Specht_Decomposition_Matrix:=fail; ## just in case
3426
3427    file:=Filename([Directory("."),SpechtDirectory,H!.info.Library],str);
3428    if crystal then
3429      msg:="ReadCrystalMatrix-";
3430    else
3431      msg:="ReadDecompositionMatrix-";
3432    fi;
3433
3434    d:=fail;
3435
3436    if file <> fail then Read(file); fi;
3437
3438    if A_Specht_Decomposition_Matrix<>fail then   ## extract matrix from M
3439      M:=A_Specht_Decomposition_Matrix;
3440      A_Specht_Decomposition_Matrix:=fail;
3441      r:=Set(M.rows); c:=Set(M.cols);
3442      if not IsSchur(H) and r=c then
3443        d:=DecompositionMatrix(H,r,
3444              Filtered(c,x->IsERegular(H!.e,x)),not IsBound(M.crystal));
3445      elif not IsSchur(H) then
3446        d:=DecompositionMatrix(H,r,c,not IsBound(M.crystal));
3447      else
3448        d:=DecompositionMatrix(H,r,r,not IsBound(M.crystal));
3449      fi;
3450      if IsSet(M.rows) and IsSet(M.cols) then ## new format
3451        if IsBound(M.matname) then d!.matname:=M.matname; fi;
3452        for c in [1..Length(d!.cols)] do
3453          cm:=Position(M.cols, d!.cols[c]);
3454          if cm<>fail and IsBound(M.d[cm]) then
3455            x:=M.d[cm];
3456            parts:=[]; coeffs:=[];
3457            for rm in [1..Length(x)/2] do
3458              r:=Position(d!.rows,M.rows[x[rm+Length(x)/2]]);
3459              if r<>fail then
3460                Add(parts,r);
3461                if IsInt(x[rm]) then Add(coeffs,x[rm]);
3462                else
3463                  p:=LaurentPolynomialByCoefficients(
3464                    FamilyObj(1),
3465                    x[rm]{[2..Length(x[rm])]},x[rm]);
3466                  Add(coeffs,p);
3467                fi;
3468              fi;
3469            od;
3470            if parts<>[] then   ## paranoia
3471              SortParallel(parts,coeffs);
3472              d!.d[c]:=rec(parts:=parts,coeffs:=coeffs);
3473           fi;
3474          fi;
3475        od;
3476      else  ## old format
3477        d!.d:=List(c, r->rec(coeffs:=[], parts:=[]));
3478        ## next, we unravel the decomposition matrix
3479        for rm in [1..Length(M.rows)] do
3480          r:=Position(d!.rows,M.rows[rm]);
3481          if r<>fail then
3482            x:=1;
3483            while x<Length(M.d[rm]) do
3484              c:=Position(d!.cols,M.cols[M.d[rm][x]]);
3485              if c<>fail then
3486                Add(d!.d[c].coeffs, M.d[rm][x+1]);
3487                Add(d!.d[c].parts, r);
3488              fi;
3489              x:=x+2;
3490            od;
3491          fi;
3492        od;
3493        for c in [1..Length(d!.d)] do
3494          if d!.d[c].parts=[] then Unbind(d!.d[c]);
3495          else SortParallel(d!.d[c].parts, d!.d[c].coeffs);
3496          fi;
3497        od;
3498      fi;
3499    fi;
3500    return d;
3501  end
3502); # ReadDecompositionMatrix
3503
3504## Look up the decomposition matrix in the library files and in the
3505## internal lists and return it if it is known.
3506## NOTE: this function does not use the crystal basis to calculate the
3507## decomposition matrix because it is called by the various conversion
3508## functions X->Y which will only need a small part of the matrix in
3509## general. The function FindDecompositionMatrix() also uses the crystal
3510## basis.
3511InstallMethod(KnownDecompositionMatrix,"looks for a known decomposition matrix",
3512  [IsAlgebraObj,IsInt],
3513  function(H,n)
3514    local d, x, r, c;
3515
3516    if IsBound(H!.DecompositionMatrices[n]) then
3517      d:=H!.DecompositionMatrices[n];
3518      if ( d<>fail and ForAll([1..Length(d!.cols)],c->IsBound(d!.d[c])) )
3519      or H!.info.SpechtDirectory=SpechtDirectory then return d;
3520      elif H!.info.SpechtDirectory<>SpechtDirectory then
3521        for x in [1..Length(H!.DecompositionMatrices)] do
3522          if IsBound(H!.DecompositionMatrices[x]) and
3523          H!.DecompositionMatrices[x]=fail then
3524            Unbind(H!.DecompositionMatrices[x]);
3525          fi;
3526        od;
3527      fi;
3528    fi;
3529    d:=ReadDecompositionMatrix(H,n,false);
3530
3531    ## next we look for crystal matrices
3532    if d=fail and not IsSchur(H) and IsZeroCharacteristic(H) then
3533      d:=ReadDecompositionMatrix(H,n,true);
3534      if d<>fail then d:=Specialized(d); fi;
3535    fi;
3536
3537    if d=fail and n<2*H!.e then
3538      ## decomposition matrix can be calculated
3539      r:=Partitions(n);
3540      if not IsSchur(H) then c:=ERegularPartitions(H!.e,n);
3541      else c:=r;
3542      fi;
3543      d:=DecompositionMatrix(H, r, c, true);
3544
3545      for x in [1..Length(d!.cols)] do
3546        if IsECore(H,d!.cols[x]) then    ## an e-core
3547          AddIndecomposable(d,
3548            Module(H,"S",1,d!.cols[x]),false);
3549        elif IsSimpleModule(H,d!.cols[x]) then ## first e-weight 1 partition
3550          c:=Module(H,"S",1,ECore(H,d!.cols[x]) )
3551                   *HeckeOmega(H,"S",H!.e);
3552          for r in [2..Length(c!.parts)] do
3553            AddIndecomposable(d,
3554                  Module(H,"S",[1,1],c!.parts{[r-1,r]}),false);
3555          od;
3556          if IsSchur(H) then
3557            AddIndecomposable(d,
3558              Module(H,"S",1,c!.parts[1]),false);
3559          fi;
3560        fi;
3561      od;
3562    elif IsBound(H!.DecompositionMatrices[n]) then ## partial answer only
3563      return H!.DecompositionMatrices[n];
3564    fi;
3565    H!.DecompositionMatrices[n]:=d;
3566    return d;
3567  end
3568);  # KnownDecompositionMatrix
3569
3570## almost identical to KnownDecompositionMatrix except that if this function
3571## fails then the crystalized decomposition matrix is calculated.
3572InstallMethod(FindDecompositionMatrix,"find or calculate CDM",
3573  [IsAlgebraObj,IsInt],
3574  function(H,n) local d,c;
3575    d:=KnownDecompositionMatrix(H,n);
3576    if d=fail and not IsSchur(H) and IsZeroCharacteristic(H) then
3577      d:=DecompositionMatrix(H,
3578              Partitions(n),ERegularPartitions(H!.e,n),false);
3579      for c in [1..Length(d!.cols)] do
3580        if not IsBound(d!.d[c]) then
3581          AddIndecomposable(d,FindPq(H,d!.cols[c]),false);
3582        fi;
3583      od;
3584      H!.CrystalMatrices[n]:=d;
3585      d:=Specialized(d);
3586      H!.DecompositionMatrices[n]:=d;
3587    fi;
3588    return d;
3589  end
3590); # FindDecompositionMatrix
3591
3592## Crystal basis elements ######################################################
3593
3594#########################################################################
3595## Next, for fields of characteristic 0, we implement the LLT algorithm.
3596## Whenever a crystal basis element of the Fock space is calculated we
3597## store it in the relevant decomposition matrix n CrystalMatrices[].
3598## The actual LLT algorithm is contained in the function Pq (should
3599## really be called Pv...), but there are also functions Sq and Dq as
3600## well. These functions work as follows:
3601##   FindPq(mu) -> sum_nu d_{nu,mu} S(nu)
3602##   FindSq(mu) -> sum_nu d_{mu,nu} D(nu)
3603##   FindDq(mu) -> sum_nu d_{mu,nu}^{-1} S(nu)
3604## The later two functions will call Pq() as needed. The "modules" x
3605## returned by these functions have x.module equal to "Pq", "Sq" and
3606## "Dq" respectively to distinguish them from the specialized versions.
3607## Accordingly we need H.operations.Xq for X = S, P, and D; these are
3608## defined after Pq(), Sq(), and Dq() (which they make use of).
3609
3610## Retrieves or calculates the crystal basis element Pq(mu)
3611InstallMethod(FindPq,"finds the crystal basis element Pq(mu)",
3612  [IsAlgebraObj,IsList],
3613  function(H,mu) local  n, c, CDM, i, r, s, x, v, val,coeffs,tmp;
3614    v:=H!.Indeterminate;
3615
3616    if mu=[] then return Module(H,"Sq",v^0,[]); fi;
3617    n:=Sum(mu);
3618
3619    ## first we see if we have already calculated Pq(mu)
3620    if not IsBound(H!.CrystalMatrices[n]) or H!.CrystalMatrices[n]=fail then
3621      x:=ReadDecompositionMatrix(H,n,true);
3622      if x=fail then
3623        H!.CrystalMatrices[n]:=DecompositionMatrix(H,
3624          Partitions(n), ERegularPartitions(H!.e,n), false);
3625      fi;
3626    fi;
3627    CDM:=H!.CrystalMatrices[n];
3628    c:=Position(CDM!.cols,mu);
3629    if IsBound(CDM!.d[c]) then
3630      return Module(H,"Sq",CDM!.d[c].coeffs,
3631                 List(CDM!.d[c].parts, s->CDM!.rows[s]) );
3632    fi;
3633
3634    if IsECore(H!.e,mu) then
3635      x:=Module(H,"Sq",v^0,mu);
3636    elif EWeight(H!.e,mu)=1 then
3637      x:=Module(H,"Sq",v^0,ECore(H!.e,mu))
3638                 * HeckeOmega(H,"Sq",H!.e);
3639      r:=Position(x!.parts,mu);
3640      if r=1 then
3641        x!.parts:=x!.parts{[1]};
3642        x!.coeffs:=[v^0];
3643      else
3644        x!.parts:=x!.parts{[r-1,r]};
3645        x!.coeffs:=[v,v^0];
3646      fi;
3647    else  ## we calculate Pq(mu) recursively using LLT
3648
3649      ## don't want to change the original mu
3650      mu:=StructuralCopy(mu);
3651      i:=1;
3652      while i<Length(mu) and mu[i]=mu[i+1] do
3653        i:=i+1;
3654      od;
3655      r:=(mu[i]-i) mod H!.e;
3656      mu[i]:=mu[i]-1;
3657      s:=1;
3658      i:=i+1;
3659      while i<=Length(mu) do
3660        while i<>Length(mu) and mu[i]=mu[i+1] do
3661          i:=i+1;
3662        od;
3663        if r=(mu[i]-i) mod H!.e then
3664          s:=s+1;
3665          mu[i]:=mu[i]-1;
3666          i:=i+1;
3667        else i:=Length(mu)+1;
3668        fi;
3669      od;
3670      if mu[Length(mu)]=0  then Unbind( mu[Length(mu)] ); fi;
3671      x:=qSInducedModule(H, FindPq(H,mu), s, r);
3672      n:=1;
3673      while n<Length(x!.parts) do
3674        tmp:=CoefficientsOfLaurentPolynomial(x!.coeffs[Length(x!.parts)-n]);
3675        if tmp[2]>0 then n:=n+1;
3676        else
3677          r := StructuralCopy( x!.coeffs[Length(x!.parts)-n] );
3678          tmp:=ShallowCopy(CoefficientsOfLaurentPolynomial(r));
3679          mu:=x!.parts[Length(x!.parts)-n];
3680          if Length(tmp[1]) < 1-tmp[1] then
3681            tmp[1]:=Concatenation(tmp[1],
3682              List([1..Length(tmp[1])-1-tmp[2]], i->0));
3683          fi;
3684          tmp[1]:=tmp[1]{[1..1-tmp[2]]};
3685          tmp[1]:=Concatenation(tmp[1], Reversed(tmp[1]{[1..-tmp[2]]}));
3686          r:=LaurentPolynomialByCoefficients(FamilyObj(1),tmp[1],tmp[2]);
3687          x := x-r*FindPq(H,mu);
3688          if mu in x!.parts then n:= n+1; fi;
3689        fi;
3690      od;
3691      r := List(x!.coeffs, s->s <> 0 * v ^ 0);
3692      if false in r then
3693        x!.coeffs := ListBlist( x!.coeffs, r );
3694        x!.parts := ListBlist( x!.parts, r );
3695      fi;
3696    fi;
3697
3698    ## having found x we add it to CDM
3699    CDM!.d[c]:=rec(coeffs:=x!.coeffs,
3700                  parts:=List(x!.parts, r->Position(CDM!.rows,r)) );
3701
3702    ## for good measure we also add the Mullineux image of Pq(mu) to CDM
3703    ## (see LLT Theorem 7.2)
3704    n:=Position(CDM!.cols,ConjugatePartition(x!.parts[1]));
3705    if c<>n then             ## not self-image under MullineuxMap
3706      r:=List(x!.coeffs*v^0, i->Value(i,v^-1));     ## v -> v^-1
3707      for i in [Length(r),Length(r)-1..1] do   ## multiply by r[1]
3708        tmp:=ShallowCopy(CoefficientsOfLaurentPolynomial(r[i]));
3709        tmp[2]:=tmp[2]-CoefficientsOfLaurentPolynomial(r[1])[2];
3710        r[i]:=LaurentPolynomialByCoefficients(FamilyObj(1),tmp[1],tmp[2]);
3711      od;
3712      s:=List(x!.parts, mu->Position(CDM!.rows,ConjugatePartition(mu)));
3713      SortParallel(s,r);
3714      CDM!.d[n]:=rec(coeffs:=r,parts:=s);
3715    fi;
3716    return x;
3717  end
3718); # FindPq
3719
3720## Strictly speaking the functions Sq() and Dq() are superfluous as
3721## these functions could be carried out by the decomposition matrix
3722## operations; however the point is that the crystal matrices are
3723## allowed to have missing columns, and if any needed columns missing
3724## these functions calculate them on the fly via using Pq().
3725
3726## writes S(mu), from the Fock space, as a sum of D(nu)
3727InstallMethod(FindSq,"write Sq(mu) as sum of Dq(mu)",
3728  [IsAlgebraObj,IsList],
3729  function(H,mu) local x, r, CDM, n;
3730    n:=Sum(mu);
3731
3732    ## we need the list of e-regular partitions. as we will have to
3733    ## create CrystalMatrices[n] anyway, we get the columns from there.
3734    if not IsBound(H!.CrystalMatrices[n]) or H!.CrystalMatrices[n]=fail then
3735      r:=Partitions(n);
3736      H!.CrystalMatrices[n]:=DecompositionMatrix(H,
3737        r, ERegularPartitions(H!.e,n), false);
3738    fi;
3739    CDM:=H!.CrystalMatrices[n];
3740
3741    x:=Module(H,"Dq",0,[]);
3742    r:=Length(CDM!.cols);
3743    mu:=Position(CDM!.rows,mu);
3744    while r>0 and CDM!.cols[r]>=CDM!.rows[mu] do
3745      if not IsBound(CDM!.d[r]) then FindPq(H,CDM!.cols[r]); fi;
3746      n:=Position(CDM!.d[r].parts,mu);
3747      if n<>fail then
3748        x:=x+Module(H,"Dq",CDM!.d[r].coeffs[n],CDM!.cols[r]);
3749      fi;
3750      r:=r-1;
3751    od;
3752    return x;
3753  end
3754);
3755
3756## write D(mu), from the Fock space, as a sum of S(nu)
3757InstallMethod(FindDq, "write Dq(mu) as sum of Sq(mu)",
3758  [IsAlgebraObj,IsList],
3759  function(H,mu) local inv, x, c, CDM;
3760    inv:=Module(H,"Sq",1,mu);
3761    x:=Module(H,"Dq",1,mu)-FindSq(H,mu);
3762    CDM:=H!.CrystalMatrices[Sum(mu)];
3763    c:=Position(CDM!.cols,mu);
3764
3765    if IsBound(CDM!.inverse[c]) then
3766      return Module(H,"Sq",CDM!.inverse[c].coeffs,
3767                                List(CDM!.inverse[c].parts,c->CDM!.cols[c]));
3768    fi;
3769
3770    while x<>0*x do
3771      c:=Length(x!.parts);
3772      inv:=inv+Module(H,"Sq",x!.coeffs[c],x!.parts[c]);
3773      x:=x-x!.coeffs[c]*FindSq(H,x!.parts[c]);
3774    od;
3775
3776    ## now place answer back in CDM
3777    CDM!.inverse[Position(CDM!.cols,mu)]:=rec(coeffs:=inv!.coeffs,
3778             parts:=List(inv!.parts,c->Position(CDM!.cols,c)) );
3779    return inv;
3780  end
3781); # FindDq
3782
3783