source: git/Singular/LIB/normal.lib @ d2ea299

spielwiese
Last change on this file since d2ea299 was d2ea299, checked in by Frank Seelisch <seelisch@…>, 13 years ago
new LIB versions and debugging in code for matrix minors git-svn-id: file:///usr/local/Singular/svn/trunk@13339 2c84dea3-7e68-4137-9b89-c4e89433aadc
  • Property mode set to 100644
File size: 222.5 KB
Line 
1///////////////////////////////////////////////////////////////////////////////
2version="$Id$";
3category="Commutative Algebra";
4info="
5LIBRARY:  normal.lib     Normalization of Affine Rings
6AUTHORS:  G.-M. Greuel,  greuel@mathematik.uni-kl.de,
7@*        S. Laplagne,   slaplagn@dm.uba.ar,
8@*        G. Pfister,    pfister@mathematik.uni-kl.de
9
10
11MAIN PROCEDURES:
12 normal(I,[...]);    normalization of an affine ring
13 normalP(I,[...]);   normalization of an affine ring in positive characteristic
14 normalC(I,[...]);   normalization of an affine ring through a chain of rings
15 HomJJ(L);           presentation of End_R(J) as affine ring, J an ideal
16 genus(I);           computes the geometric genus of a projective curve
17 primeClosure(L);    integral closure of R/p, p a prime ideal
18 closureFrac(L);     writes a poly in integral closure as element of Quot(R/p)
19 iMult(L);           intersection multiplicity of the ideals of the list L
20
21AUXILIARY PROCEDURES:
22 deltaLoc(f,S);      sum of delta invariants at conjugated singular points
23 locAtZero(I);       checks whether the zero set of I is located at 0
24 norTest(I,nor);     checks the output of normal, normalP, normalC
25 getSmallest(J);     computes the polynomial of smallest degree of J
26 getOneVar(J, vari); computes a polynomial of J in the variable vari
27 changeDenominator(U1, c1, c2, I); computes ideal U2 such that 1/c1*U1=1/c2*U2
28";
29
30LIB "general.lib";
31LIB "poly.lib";
32LIB "sing.lib";
33LIB "primdec.lib";
34LIB "elim.lib";
35LIB "presolve.lib";
36LIB "inout.lib";
37LIB "ring.lib";
38LIB "hnoether.lib";
39LIB "reesclos.lib";
40LIB "algebra.lib";
41
42///////////////////////////////////////////////////////////////////////////////
43
44proc normal(ideal id, list #)
45"USAGE:  normal(id [,choose]); id = radical ideal, choose = list of options. @*
46         Optional parameters in list choose (can be entered in any order):@*
47         Decomposition:@*
48         - \"equidim\" -> computes first an equidimensional decomposition,
49         and then the normalization of each component (default).@*
50         - \"prim\" -> computes first the minimal associated primes, and then
51         the normalization of each prime. @*
52         - \"noDeco\" -> no preliminary decomposition is done. If the ideal is
53         not equidimensional radical, output might be wrong.@*
54         - \"isPrim\" -> assumes that the ideal is prime. If this assumption
55         does not hold, the output might be wrong.@*
56         - \"noFac\" -> factorization is avoided in the computation of the
57         minimal associated primes;
58         Other:@*
59         - \"useRing\" -> uses the original ring ordering.@*
60         If this option is set and if the ring ordering is not global, normal
61         will change to a global ordering only for computing radicals and prime
62         or equidimensional decompositions.@*
63         If this option is not set, normal changes to dp ordering and performs
64         all computations with respect to this ordering.@*
65         - \"withDelta\" (or \"wd\") -> returns also the delta invariants.@*
66         If the optional parameter choose is not given or empty, only
67         \"equidim\" but no other option is used.@*
68         - list(\"inputJ\", ideal inputJ) -> takes as initial test ideal the
69         ideal inputJ. This option is only for use in other procedures. Using
70         this option, the result might not be the normalization.@*
71         (Option only valid for global algorithm.)@*         
72         - list(\"inputC\", ideal inputC) -> takes as initial conductor the
73         ideal inputC. This option is only for use in other procedures. Using
74         this option, the result might not be the normalization.@*
75         (Option only valid for global algorithm.)@*
76         Options used for computing integral basis (over rings of two
77         variables):@*
78         - \"var1\" -> uses a polynomial in the first variable as
79         universal denominator.@*
80         - \"var2\" -> uses a polynomial in the second variable as universal
81         denominator.@*
82         If the optional parameter choose is not given or empty, only
83         \"equidim\" but no other option is used.@*
84ASSUME:  The ideal must be radical, for non-radical ideals the output may
85         be wrong (id=radical(id); makes id radical). However, when using the
86         \"prim\" option the minimal associated primes of id are computed first
87         and hence normal computes the normalization of the radical of id.@*
88NOTE:    \"isPrim\" should only be used if id is known to be prime.
89RETURN:  a list, say nor, of size 2 (resp. 3 with option \"withDelta\").
90@format  Let R denote the basering and id the input ideal.
91         * nor[1] is a list of r rings, where r is the number of associated
92         primes P_i with option \"prim\" (resp. >= no of equidimenensional
93         components P_i with option \"equidim\").@*
94         Each ring Ri := nor[1][i], i=1..r, contains two ideals with given
95         names @code{norid} and @code{normap} such that: @*
96         - Ri/norid is the normalization of the i-th component, i.e. the
97          integral closure of R/P_i in its field of fractions (as affine ring);
98         - @code{normap} gives the normalization map from R/id to
99           Ri/norid for each i.@*
100         - the direct sum of the rings Ri/norid, i=1,..r, is the normalization
101           of R/id as affine algebra; @*
102         * nor[2] is a list of size r with information on the normalization of
103         the i-th component as module over the basering R:@*
104         nor[2][i] is an ideal, say U, in R such that the integral closure
105         of basering/P_i is generated as module over R by 1/c * U, with c
106         the last element U[size(U)] of U.@*
107         * nor[3] (if option \"withDelta\" is set) is a list of an intvec
108         of size r, the delta invariants of the r components, and an integer,
109         the total delta invariant of basering/id (-1 means infinite, and 0
110         that R/P_i resp. R/id is normal).
111@end format
112THEORY:  We use here a general algorithm described in [G.-M.Greuel, S.Laplagne,
113         F.Seelisch: Normalization of Rings (2009)].@*
114         The procedure computes the R-module structure, the algebra structure
115         and the delta invariant of the normalization of R/id:@*
116         The normalization of R/id is the integral closure of R/id in its total
117         ring of fractions. It is a finitely generated R-module and nor[2]
118         computes R-module generators of it. More precisely: If U:=nor[2][i]
119         and c:=U[size(U)], then c is a non-zero divisor and U/c is an R-module
120         in the total ring of fractions, the integral closure of R/P_i. Since
121         U[size(U)]/c is equal to 1, R/P_i resp. R/id is contained in the
122         integral closure.@*
123         The normalization is also an affine algebra over the ground field
124         and nor[1] presents it as such. For geometric considerations nor[1] is
125         relevant since the variety of the ideal norid in Ri is the
126         normalization of the variety of the ideal P_i in R.@*
127         The delta invariant of a reduced ring A is dim_K(normalization(A)/A).
128         For A=K[x1,...,xn]/id we call this number also the delta invariant of
129         id. nor[3] returns the delta invariants of the components P_i and of
130         id.
131NOTE:    To use the i-th ring type e.g.: @code{def R=nor[1][i]; setring R;}.
132@*       Increasing/decreasing printlevel displays more/less comments
133         (default: printlevel=0).
134@*       Implementation works also for local rings.
135@*       Not implemented for quotient rings.
136@*       If the input ideal id is weighted homogeneous a weighted ordering may
137         be used together with the useRing-option (qhweight(id); computes
138         weights).
139KEYWORDS: normalization; integral closure; delta invariant.
140SEE ALSO: normalC, normalP.
141EXAMPLE: example normal; shows an example
142"
143{
144  intvec opt = option(get);     // Save current options
145
146  int i,j;
147  int decomp;   // Preliminary decomposition:
148                // 0 -> no decomposition (id is assumed to be prime)
149                // 1 -> no decomposition
150                //      (id is assumed to be equidimensional radical)
151                // 2 -> equidimensional decomposition
152                // 3 -> minimal associated primes
153  int noFac, useRing, withDelta;
154  int dbg = printlevel - voice + 2;
155  int nvar = nvars(basering);
156  int chara  = char(basering);
157  int denomOption;   // Method for choosing the conductor
158
159  ideal inputJ = 0;      // Test ideal given in the input (if any).
160  ideal inputC = 0;      // Conductor ideal given in the input (if any).
161
162  list result, resultNew;
163  list keepresult;
164  list ringStruc;
165  ideal U;
166  poly c;
167  int sp;            // Number of components.
168
169  // Default methods:
170  noFac = 0;         // Use facSTD when computing minimal associated primes
171  decomp = 2;        // Equidimensional decomposition
172  useRing = 0;       // Change first to dp ordering, and perform all
173                     // computations there.
174  withDelta = 0;     // Do not compute the delta invariant.
175  denomOption = 0;   // The default universal denominator is the smallest
176                     // degree polynomial.
177
178//--------------------------- define the method ---------------------------
179  for ( i=1; i <= size(#); i++ )
180  {
181    if ( typeof(#[i]) == "string" )
182    {
183//--------------------------- choosen methods -----------------------
184      if ( (#[i]=="isprim") or (#[i]=="isPrim") )
185      {decomp = 0;}
186
187      if ( (#[i]=="nodeco") or (#[i]=="noDeco") )
188      {decomp = 1;}
189
190      if (#[i]=="prim")
191      {decomp = 3;}
192
193      if (#[i]=="equidim")
194      {decomp = 2;}
195
196      if ( (#[i]=="nofac") or (#[i]=="noFac") )
197      {noFac=1;}
198
199      if ( ((#[i]=="useRing") or (#[i]=="usering")) and (ordstr(basering) != "dp("+string(nvars(basering))+"),C"))
200      {useRing = 1;}
201
202      if ( (#[i]=="withDelta") or (#[i]=="wd") or (#[i]=="withdelta"))
203      {
204        if((decomp == 0) or (decomp == 3))
205        {
206          withDelta = 1;
207        }
208        else
209        {
210          decomp = 3;
211          withDelta = 1;
212          //Note: the delta invariants cannot be computed with an equidimensional
213          //decomposition, hence we compute first the minimal primes
214        }
215      }
216      if (#[i]=="var1")
217      {denomOption = 1;}
218      if (#[i]=="var2")
219      {denomOption = 2;}
220    }
221    if(typeof(#[i]) == "list"){
222      if(size(#[i]) == 2){
223        if (#[i][1]=="inputJ"){
224          if(typeof(#[i][2]) == "ideal"){
225            inputJ = #[i][2];
226          }
227        }
228      }
229      if (#[i][1]=="inputC"){
230        if(size(#[i]) == 2){
231          if(typeof(#[i][2]) == "ideal"){
232            inputC = #[i][2];
233          }
234        }
235      }
236    }
237  }
238  kill #;
239
240//------------------------ change ring if required ------------------------
241// If the ordering is not global, we change to dp ordering for computing the
242// min ass primes.
243// If the ordering is global, but not dp, and useRing = 0, we also change to
244// dp ordering.
245
246  int isGlobal = ord_test(basering);      // Checks if the original ring has
247                                          // global ordering.
248
249  def origR = basering;   // origR is the original ring
250                          // R is the ring where computations will be done
251
252  if((useRing  == 1) and (isGlobal == 1))
253  {
254    def globR = basering;
255  }
256  else
257  {
258    // We change to dp ordering.
259    list rl = ringlist(origR);
260    list origOrd = rl[3];
261    list newOrd = list("dp", intvec(1:nvars(origR))), list("C", 0);
262    rl[3] = newOrd;
263    def globR = ring(rl);
264    setring globR;
265    ideal id = fetch(origR, id);
266  }
267
268//------------------------ trivial checkings ------------------------
269  id = groebner(id);
270  if((size(id) == 0) or (id[1] == 1))
271  {
272    // The original ring R/I was normal. Nothing to do.
273    // We define anyway a new ring, equal to R, to be able to return it.
274    setring origR;
275    list lR = ringlist(origR);
276    def ROut = ring(lR);
277    setring ROut;
278    ideal norid = fetch(origR, id);
279    ideal normap = maxideal(1);
280    export norid;
281    export normap;
282    setring origR;
283    if(withDelta)
284    {
285      result = list(list(ROut), list(ideal(1)), list(intvec(0), 0));
286    }
287    else
288    {
289      result = list(list(ROut), list(ideal(1)));
290    }
291    sp = 1;      // number of rings in the output
292    option(set, opt);
293    normalOutputText(dbg, withDelta, sp);
294    return(result);
295  }
296//------------------------ preliminary decomposition-----------------------
297  list prim;
298  if(decomp == 2)
299  {
300    dbprint(dbg, "// Computing the equidimensional decomposition...");
301    prim = equidim(id);
302  }
303  if((decomp == 0) or (decomp == 1))
304  {
305    prim = id;
306  }
307  if(decomp == 3)
308  {
309    dbprint(dbg, "// Computing the minimal associated primes...");
310    if( noFac )
311    { prim = minAssGTZ(id,1); }
312    else
313    { prim = minAssGTZ(id); }
314  }
315  sp = size(prim);
316  if(dbg>=1)
317  {
318    prim; "";
319    "// number of components is", sp;
320    "";
321  }
322
323
324//----------------- back to the original ring if required ------------------
325// if ring was not global and useRing is on, we go back to the original ring
326  if((useRing == 1) and (isGlobal != 1))
327  {
328    setring origR;
329    def R = basering;
330    list prim = fetch(globR, prim);
331  }
332  else
333  {
334    def R = basering;
335    ideal inputJ = fetch(origR, inputJ);
336    ideal inputC = fetch(origR, inputC);
337    if(useRing == 0)
338    {
339      ideal U;
340      poly c;
341    }
342  }
343
344// ---------------- normalization of the components-------------------------
345// calls normalM to compute the normalization of each component.
346
347  list norComp;       // The normalization of each component.
348  int delt;
349  int deltI = 0;
350  int totalComps = 0;
351
352  setring origR;
353  def newROrigOrd;
354  list newRListO;
355  setring R;
356  def newR;
357  list newRList;
358
359  for(i=1; i<=size(prim); i++)
360  {
361    if(dbg>=2){pause();}
362    if(dbg>=1)
363    {
364      "// start computation of component",i;
365      "   --------------------------------";
366    }
367    if(groebner(prim[i])[1] != 1)
368    {
369      if(dbg>=2)
370      {
371        "We compute the normalization in the ring"; basering;
372      }
373      printlevel = printlevel + 1;
374      norComp = normalM(prim[i], decomp, withDelta, denomOption, inputJ, inputC);
375      printlevel = printlevel - 1;
376      for(j = 1; j <= size(norComp); j++)
377      {
378        newR = norComp[j][3];
379        newRList = ringlist(newR);
380        U = norComp[j][1];
381        c = norComp[j][2];
382        if(withDelta)
383        {
384          delt = norComp[j][4];
385          if((delt >= 0) and (deltI >= 0))
386          {
387            deltI = deltI + delt;
388          }
389          else
390          {
391            deltI = -1;
392          }
393        }
394        // -- incorporate result for this component to the list of results ---
395        if(useRing == 0)
396        {
397          // We go back to the original ring.
398          setring origR;
399          U = fetch(R, U);
400          c = fetch(R, c);
401          newRListO = imap(R, newRList);
402          // We change the ordering in the new ring.
403          if(nvars(newR) > nvars(origR))
404          {
405            newRListO[3]=insert(origOrd, newRListO[3][1]);
406          }
407          else
408          {
409            newRListO[3] = origOrd;
410          }
411          newROrigOrd = ring(newRListO);
412          setring newROrigOrd;
413          ideal norid = imap(newR, norid);
414          ideal normap = imap(newR, normap);
415          export norid;
416          export normap;
417          setring origR;
418          totalComps++;
419          result[totalComps] = list(U, c, newROrigOrd);
420          if(withDelta)
421          {
422            result[totalComps] = insert(result[totalComps], delt, 3);
423          }
424          setring R;
425        }
426        else
427        {
428          setring R;
429          totalComps++;
430          result[totalComps] = norComp[j];
431        }
432      }
433    }
434  }
435
436// -------------------------- delta computation ----------------------------
437  if(withDelta == 1)
438  {
439    // Intersection multiplicities of list prim, sp=size(prim).
440    if ( dbg >= 1 )
441    {
442      "// Sum of delta for all components: ", deltI;
443    }
444    if(size(prim) > 1)
445    {
446      dbprint(dbg, "// Computing the sum of the intersection multiplicities of the components...");
447      int mul = iMult(prim);
448      if ( mul < 0 )
449      {
450        deltI = -1;
451      }
452      else
453      {
454        deltI = deltI + mul;
455      }
456      if ( dbg >= 1 )
457      {
458        "// Intersection multiplicity is : ", mul;
459      }
460    }
461  }
462
463// -------------------------- prepare output ------------------------------
464  setring origR;
465
466  list RL;      // List of rings
467  list MG;      // Module generators
468  intvec DV;    // Vector of delta's of each component
469  for(i = 1; i <= size(result); i++)
470  {
471    RL[i] = result[i][3];
472    MG[i] = lineUpLast(result[i][1], result[i][2]);
473    if(withDelta)
474    {
475      DV[i] = result[i][4];
476    }
477  }
478  if(withDelta)
479  {
480    resultNew = list(RL, MG, list(DV, deltI));
481  }
482  else
483  {
484    resultNew = list(RL, MG);
485  }
486  sp = size(RL);              //RL = list of rings
487
488  option(set, opt);
489  normalOutputText(dbg, withDelta, sp);
490  return(resultNew);
491}
492
493example
494{ "EXAMPLE:";
495  printlevel = printlevel+1;
496  echo = 2;
497  ring s = 0,(x,y),dp;
498  ideal i = (x2-y3)*(x2+y2)*x;
499  list nor = normal(i, "withDelta", "prim");
500  nor;
501
502  // 2 branches have delta = 1, and 1 branch has delta = 0
503  // the total delta invariant is 13
504
505  def R2 = nor[1][2];  setring R2;
506  norid; normap;
507
508  echo = 0;
509  printlevel = printlevel-1;
510  pause("   hit return to continue"); echo=2;
511
512  ring r = 2,(x,y,z),dp;
513  ideal i = z3-xy4;
514  list nor = normal(i, "withDelta", "prim");  nor;
515  // the delta invariant is infinite
516  // xy2z/z2 and xy3/z2 generate the integral closure of r/i as r/i-module
517  // in its quotient field Quot(r/i)
518
519  // the normalization as affine algebra over the ground field:
520  def R = nor[1][1]; setring R;
521  norid; normap;
522}
523
524///////////////////////////////////////////////////////////////////////////////
525// Prints the output text in proc normal.
526//
527static proc normalOutputText(int dbg, int withDelta, int sp)
528// int dbg: printlevel
529// int withDelta: output contains information about the delta invariant
530// int sp: number of output rings.
531{
532  if ( dbg >= 0 )
533  {
534    "";
535    if(!withDelta)
536    {
537      "// 'normal' created a list, say nor, of two elements.";
538    }
539    else
540    {
541      "// 'normal' created a list, say nor, of three elements.";
542    }
543    "// To see the list type";
544    "      nor;";
545    "";
546    "// * nor[1] is a list of", sp, "ring(s).";
547    "// To access the i-th ring nor[1][i], give it a name, say Ri, and type";
548    "     def R1 = nor[1][1]; setring R1; norid; normap;";
549    "// For the other rings type first (if R is the name of your base ring)";
550    "     setring R;";
551    "// and then continue as for R1.";
552    "// Ri/norid is the affine algebra of the normalization of R/P_i where";
553    "// P_i is the i-th component of a decomposition of the input ideal id";
554    "// and normap the normalization map from R to Ri/norid.";
555    "";
556    "// * nor[2] is a list of", sp, "ideal(s). Let ci be the last generator";
557    "// of the ideal nor[2][i]. Then the integral closure of R/P_i is";
558    "// generated as R-submodule of the total ring of fractions by";
559    "// 1/ci * nor[2][i].";
560
561    if(withDelta)
562    { "";
563      "// * nor[3] is a list of an intvec of size", sp, "the delta invariants ";
564      "// of the components, and an integer, the total delta invariant ";
565      "// of R/id (-1 means infinite, and 0 that R/P_i resp. R/id is normal).";
566    }
567  }
568}
569
570
571///////////////////////////////////////////////////////////////////////////////
572
573proc HomJJ (list Li)
574"USAGE:   HomJJ (Li);  Li = list: ideal SBid, ideal id, ideal J, poly p
575ASSUME:  R    = P/id,  P = basering, a polynomial ring, id an ideal of P,
576@*       SBid = standard basis of id,
577@*       J    = ideal of P containing the polynomial p,
578@*       p    = nonzero divisor of R
579COMPUTE: Endomorphism ring End_R(J)=Hom_R(J,J) with its ring structure as
580         affine ring, together with the map R --> Hom_R(J,J) of affine rings,
581         where R is the quotient ring of P modulo the standard basis SBid.
582RETURN:  a list l of three objects
583@format
584         l[1] : a polynomial ring, containing two ideals, 'endid' and 'endphi'
585               such that l[1]/endid = Hom_R(J,J) and
586               endphi describes the canonical map R -> Hom_R(J,J)
587         l[2] : an integer which is 1 if phi is an isomorphism, 0 if not
588         l[3] : an integer, = dim_K(Hom_R(J,J)/R) (the contribution to delta)
589                if the dimension is finite, -1 otherwise
590@end format
591NOTE:    printlevel >=1: display comments (default: printlevel=0)
592EXAMPLE: example HomJJ;  shows an example
593"
594{
595//---------- initialisation ---------------------------------------------------
596   int isIso,isPr,isHy,isCo,isRe,isEq,oSAZ,ii,jj,q,y;
597   intvec rw,rw1;
598   list L;
599   y = printlevel-voice+2;  // y=printlevel (default: y=0)
600   def P = basering;
601   ideal SBid, id, J = Li[1], Li[2], Li[3];
602   poly p = Li[4];
603   int noRed = 0;
604   if(size(Li) > 4)
605   {
606     if(Li[5] == 1) { noRed = 1; }
607   }
608
609   attrib(SBid,"isSB",1);
610   int homo = homog(Li[2]);               //is 1 if id is homogeneous, 0 if not
611
612//---- set attributes for special cases where algorithm can be simplified -----
613   if( homo==1 )
614   {
615      rw = ringweights(P);
616   }
617   if( typeof(attrib(id,"isPrim"))=="int" )
618   {
619      if(attrib(id,"isPrim")==1)  { isPr=1; }
620   }
621   if( typeof(attrib(id,"onlySingularAtZero"))=="int" )
622   {
623      if(attrib(id,"onlySingularAtZero")==1){oSAZ=1; }
624   }
625   if( typeof(attrib(id,"isIsolatedSingularity"))=="int" )
626   {
627      if(attrib(id,"isIsolatedSingularity")==1) { isIso=1; }
628   }
629   if( typeof(attrib(id,"isCohenMacaulay"))=="int" )
630   {
631      if(attrib(id,"isCohenMacaulay")==1) { isCo=1; }
632   }
633   if( typeof(attrib(id,"isRegInCodim2"))=="int" )
634   {
635      if(attrib(id,"isRegInCodim2")==1) { isRe=1; }
636   }
637   if( typeof(attrib(id,"isEquidimensional"))=="int" )
638   {
639      if(attrib(id,"isEquidimensional")==1) { isEq=1; }
640   }
641//-------------------------- go to quotient ring ------------------------------
642   qring R  = SBid;
643   ideal id = fetch(P,id);
644   ideal J  = fetch(P,J);
645   poly p   = fetch(P,p);
646   ideal f,rf,f2;
647   module syzf;
648//---------- computation of p*Hom(J,J) as R-ideal -----------------------------
649   if ( y>=1 )
650   {
651     "// compute p*Hom(J,J) = p*J:J";
652     "//   the ideal J:";J;
653   }
654   f  = quotient(p*J,J);
655
656   //### (neu GMG 4.10.08) divide by the greatest common divisor:
657   poly gg = gcd( f[1],p );
658   for(ii=2; ii <=ncols(f); ii++)
659   {
660      gg=gcd(gg,f[ii]);
661   }
662   for(ii=1; ii<=ncols(f); ii++)
663   {
664      f[ii]=f[ii]/gg;
665   }
666   p = p/gg;
667
668   if ( y>=1 )
669   {
670      "//   the non-zerodivisor p:"; p;
671      "//   the module p*Hom(J,J) = p*J:J :"; f;
672      "";
673   }
674   f2 = std(p);
675
676//---------- Test: Hom(J,J) == R ?, if yes, go home ---------------------------
677
678   //rf = interred(reduce(f,f2));
679   //### interred hier weggelassen, unten zugefuegt
680   rf = reduce(f,f2);       //represents p*Hom(J,J)/p*R = Hom(J,J)/R
681   if ( size(rf) == 0 )
682   {
683      if ( homog(f) && find(ordstr(basering),"s")==0 )
684      {
685         ring newR1 = char(P),(X(1..nvars(P))),(a(rw),dp);
686      }
687      else
688      {
689         ring newR1 = char(P),(X(1..nvars(P))),dp;
690      }
691      ideal endphi = maxideal(1);
692      ideal endid = fetch(P,id);
693      endid = simplify(endid,2);
694      L = substpart(endid,endphi,homo,rw);   //## hier substpart
695      def lastRing = L[1];
696      setring lastRing;
697
698      attrib(endid,"onlySingularAtZero",oSAZ);
699      attrib(endid,"isCohenMacaulay",isCo);
700      attrib(endid,"isPrim",isPr);
701      attrib(endid,"isIsolatedSingularity",isIso);
702      attrib(endid,"isRegInCodim2",isRe);
703      attrib(endid,"isEqudimensional",isEq);
704      attrib(endid,"isHypersurface",0);
705      attrib(endid,"isCompleteIntersection",0);
706      attrib(endid,"isRadical",0);
707      L=lastRing;
708      L = insert(L,1,1);
709      dbprint(y,"// case R = Hom(J,J)");
710      if(y>=1)
711      {
712         "//   R=Hom(J,J)";
713         lastRing;
714         "//   the new ideal";
715         endid;
716         "   ";
717         "//   the old ring";
718         P;
719         "//   the old ideal";
720         setring P;
721         id;
722         "   ";
723         setring lastRing;
724         "//   the map to the new ring";
725         endphi;
726         "   ";
727         pause();
728         "";
729      }
730      setring P;
731      L[3]=0;
732      return(L);
733   }
734   if(y>=1)
735   {
736      "// R is not equal to Hom(J,J), we have to try again";
737      pause();
738      "";
739   }
740//---------- Hom(J,J) != R: create new ring and map from old ring -------------
741// the ring newR1/SBid+syzf will be isomorphic to Hom(J,J) as R-module
742// f2=p (i.e. ideal generated by p)
743
744   //f = mstd(f)[2];              //### geaendert GMG 04.10.08
745   //ideal ann = quotient(f2,f);  //### f durch rf ersetzt
746   rf = mstd(rf)[2];              //rf = NF(f,p), hence <p,rf> = <p,f>
747   ideal ann = quotient(f2,rf);   //p:f = p:rf
748
749   //------------- compute the contribution to delta ----------
750   //delt=dim_K(Hom(JJ)/R (or -1 if infinite)
751
752   int delt=vdim(std(modulo(f,ideal(p))));
753
754   f = p,rf;          // generates pJ:J mod(p), i.e. p*Hom(J,J)/p*R as R-module
755   q = size(f);
756   syzf = syz(f);
757
758   if ( homo==1 )
759   {
760      rw1 = rw,0;
761      for ( ii=2; ii<=q; ii++ )
762      {
763         rw  = rw, deg(f[ii])-deg(f[1]);
764         rw1 = rw1, deg(f[ii])-deg(f[1]);
765      }
766      ring newR1 = char(R),(X(1..nvars(R)),T(1..q)),(a(rw1),dp);
767   }
768   else
769   {
770      ring newR1 = char(R),(X(1..nvars(R)),T(1..q)),dp;
771   }
772
773   //map psi1 = P,maxideal(1);          //### psi1 durch fetch ersetzt
774   //ideal SBid = psi1(SBid);
775   ideal SBid = fetch(P,SBid);
776   attrib(SBid,"isSB",1);
777
778   qring newR = std(SBid);
779
780   //map psi = R,ideal(X(1..nvars(R)));  //### psi durch fetch ersetzt
781   //ideal id = psi(id);
782   //ideal f = psi(f);
783   //module syzf = psi(syzf);
784   ideal id = fetch(R,id);
785   ideal f = fetch(R,f);
786   module syzf = fetch(R,syzf);
787   ideal pf,Lin,Quad,Q;
788   matrix T,A;
789   list L1;
790
791//---------- computation of Hom(J,J) as affine ring ---------------------------
792// determine kernel of: R[T1,...,Tq] -> J:J >-> R[1/p]=R[t]/(t*p-1),
793// Ti -> fi/p -> t*fi (p=f1=f[1]), to get ring structure. This is of course
794// the same as the kernel of R[T1,...,Tq] -> pJ:J >-> R, Ti -> fi.
795// It is a fact, that the kernel is generated by the linear and the quadratic
796// relations
797// f=p,rf, rf=reduce(f,p), generates pJ:J mod(p),
798// i.e. p*Hom(J,J)/p*R as R-module
799
800   pf = f[1]*f;
801   T = matrix(ideal(T(1..q)),1,q);
802   Lin = ideal(T*syzf);
803   if(y>=1)
804   {
805      "// the ring structure of Hom(J,J) as R-algebra";
806      "//   the linear relations:";
807      Lin;
808   }
809
810   poly ff;
811   for (ii=2; ii<=q; ii++ )
812   {
813      for ( jj=2; jj<=ii; jj++ )
814      {
815         ff = NF(f[ii]*f[jj],std(0));       //this makes lift much faster
816         A = lift(pf,ff);                   //ff lin. comb. of elts of pf mod I
817         Quad = Quad, ideal(T(jj)*T(ii) - T*A);  //quadratic relations
818      }
819   }
820
821   if(y>=1)
822   {
823      "//   the quadratic relations";
824      Quad;
825      pause();
826      newline;
827   }
828   Q = Lin,Quad;
829   Q = subst(Q,T(1),1);
830   //Q = mstd(Q)[2];            //### sehr aufwendig, daher weggelassen (GMG)
831   //### ev das neue interred
832   //mstd dient nur zum verkleinern, die SB-Eigenschaft geht spaeter verloren
833   //da in neuen Ring abgebildet und mit id vereinigt
834
835//---------- reduce number of variables by substitution, if possible ----------
836   if (homo==1)
837   {
838      ring newRing = char(R),(X(1..nvars(R)),T(2..q)),(a(rw),dp);
839   }
840   else
841   {
842      ring newRing = char(R),(X(1..nvars(R)),T(2..q)),dp;
843   }
844
845   ideal endid  = imap(newR,id),imap(newR,Q);
846   //hier wird Q weiterverwendet, die SB-Eigenschaft wird nicht verwendet.
847   endid = simplify(endid,2);
848   ideal endphi = ideal(X(1..nvars(R)));
849
850
851  if(noRed == 0)
852  {
853    L = substpart(endid,endphi,homo,rw);
854    def lastRing=L[1];
855    setring lastRing;
856    //return(lastRing);
857  }
858  else
859  {
860    list RL = ringlist(newRing);
861    def lastRing = ring(RL);
862    setring lastRing;
863    ideal endid = fetch(newRing, endid);
864    ideal endphi = fetch(newRing, endphi);
865    export(endid);
866    export(endphi);
867    //def lastRing = newRing;
868    //setring R;
869    //return(newR);
870  }
871
872
873//   L = substpart(endid,endphi,homo,rw);
874
875//   def lastRing=L[1];
876//   setring lastRing;
877
878   attrib(endid,"onlySingularAtZero",0);
879   map sigma=R,endphi;
880   ideal an=sigma(ann);
881   export(an);  //noetig?
882   //ideal te=an,endid;
883   //if(isIso && (size(reduce(te,std(maxideal(1))))==0))   //#### ok???
884   // {
885   //    attrib(endid,"onlySingularAtZero",oSAZ);
886   // }
887   //kill te;
888   attrib(endid,"isCohenMacaulay",isCo);                //#### ok???
889   attrib(endid,"isPrim",isPr);
890   attrib(endid,"isIsolatedSingularity",isIso);
891   attrib(endid,"isRegInCodim2",isRe);
892   attrib(endid,"isEquidimensional",isEq);
893   attrib(endid,"isHypersurface",0);
894   attrib(endid,"isCompleteIntersection",0);
895   attrib(endid,"isRadical",0);
896   if(y>=1)
897   {
898      "// the new ring after reduction of the number of variables";
899      lastRing;
900      "//   the new ideal";
901      endid;  "";
902      "// the old ring";
903      P;
904      "//   the old ideal";
905      setring P;
906      id;
907      "   ";
908      setring lastRing;
909      "//   the map to the new ring";
910      endphi;
911      "   ";
912      pause();
913      "";
914   }
915   L = lastRing;
916   L = insert(L,0,1);
917   L[3] = delt;
918   return(L);
919}
920example
921{"EXAMPLE:";  echo = 2;
922  ring r   = 0,(x,y),wp(2,3);
923  ideal id = y^2-x^3;
924  ideal J  = x,y;
925  poly p   = x;
926  list Li  = std(id),id,J,p;
927  list L   = HomJJ(Li);
928  def end = L[1];    // defines ring L[1], containing ideals endid, endphi
929  setring end;       // makes end the basering
930  end;
931  endid;             // end/endid is isomorphic to End(r/id) as ring
932  map psi = r,endphi;// defines the canonical map r/id -> End(r/id)
933  psi;
934  L[3];              // contribution to delta
935}
936
937
938///////////////////////////////////////////////////////////////////////////////
939//compute intersection multiplicities as needed for delta(I) in
940//normalizationPrimes and normalP:
941
942proc iMult (list prim)
943"USAGE:   iMult(L);  L a list of ideals
944RETURN:  int, the intersection multiplicity of the ideals of L;
945         if iMult(L) is infinite, -1 is returned.
946THEORY:  If r=size(L)=2 then iMult(L) = vdim(std(L[1]+L[2])) and in general
947         iMult(L) = sum{ iMult(L[j],Lj) | j=1..r-1 } with Lj the intersection
948         of L[j+1],...,L[r]. If I is the intersection of all ideals in L then
949         we have delta(I) = delta(L[1])+...+delta(L[r]) + iMult(L) where
950         delta(I) = vdim (normalisation(R/I)/(R/I)), R the basering.
951EXAMPLE: example iMult; shows an example
952"
953{    int i,mul,mu;
954     int sp = size(prim);
955     int y = printlevel-voice+2;
956     if ( sp > 1 )
957     {
958        ideal I(sp-1) = prim[sp];
959        mu = vdim(std(I(sp-1)+prim[sp-1]));
960        mul = mu;
961        if ( y>=1 )
962        {
963          "// intersection multiplicity of component",sp,"with",sp-1,":"; mu;
964        }
965        if ( mu >= 0 )
966        {
967           for (i=sp-2; i>=1 ; i--)
968           {
969              ideal I(i) = intersect(I(i+1),prim[i+1]);
970              mu = vdim(std(I(i)+prim[i]));
971              if ( mu < 0 )
972              {
973                break;
974              }
975              mul = mul + mu;
976              if ( y>=1 )
977              {
978                "// intersection multiplicity of components",sp,"...",i+1,"with",i; mu;
979              }
980           }
981        }
982     }
983     return(mul);
984}
985example
986{ "EXAMPLE:"; echo = 2;
987   ring s  = 23,(x,y),dp;
988   list L = (x-y),(x3+y2);
989   iMult(L);
990   L = (x-y),(x3+y2),(x3-y4);
991   iMult(L);
992}
993///////////////////////////////////////////////////////////////////////////////
994//check if I has a singularity only at zero, as needed in normalizationPrimes
995
996proc locAtZero (ideal I)
997"USAGE:   locAtZero(I);  I = ideal
998RETURN:  int, 1 if I has only one point which is located at zero, 0 otherwise
999ASSUME:  I is given as a standard bases in the basering
1000NOTE:    only useful in affine rings, in local rings vdim does the check
1001EXAMPLE: example locAtZero; shows an example
1002"
1003{
1004   int ii,jj, caz;                   //caz: conzentrated at zero
1005   int dbp = printlevel-voice+2;
1006   int nva = nvars(basering);
1007   int vdi = vdim(I);
1008   if ( vdi < 0 )
1009   {
1010      if (dbp >=1)
1011      { "// non-isolated singularitiy";""; }
1012      return(caz);
1013   }
1014
1015   //Now the ideal is 0-dim
1016   //First an easy test
1017   //If I is homogenous and not constant it is concentrated at 0
1018   if( homog(I)==1 && size(jet(I,0))==0)
1019   {
1020      caz=1;
1021      if (dbp >=1)
1022      { "// isolated singularity and homogeneous";""; }
1023      return(caz);
1024   }
1025
1026   //Now the general case with I 0-dim. Choose an appropriate power pot,
1027   //and check each variable x whether x^pot is in I.
1028   int mi1 = mindeg1(lead(I));
1029   int pot = vdi;
1030   if ( (mi1+(mi1==1))^2 < vdi )
1031   {
1032      pot = (mi1+(mi1==1))^2;      //### alternativ: pot = vdi lassen
1033   }
1034
1035   while ( 1 )
1036   {
1037      caz = 1;
1038      for ( ii=1; ii<= nva; ii++ )
1039      {
1040        if ( NF(var(ii)^pot,I) != 0 )
1041        {
1042           caz = 0; break;
1043        }
1044      }
1045      if ( caz == 1 || pot >= vdi )
1046      {
1047        if (dbp >=1)
1048        {
1049          "// mindeg, exponent, vdim used in 'locAtZero':", mi1,pot,vdi; "";
1050        }
1051        return(caz);
1052      }
1053      else
1054      {
1055        if ( pot^2 < vdi )
1056        { pot = pot^2; }
1057        else
1058        { pot = vdi; }
1059      }
1060   }
1061}
1062example
1063{ "EXAMPLE:"; echo = 2;
1064   ring r = 0,(x,y,z),dp;
1065   poly f = z5+y4+x3+xyz;
1066   ideal i = jacob(f),f;
1067   i=std(i);
1068   locAtZero(i);
1069   i= std(i*ideal(x-1,y,z));
1070   locAtZero(i);
1071}
1072
1073///////////////////////////////////////////////////////////////////////////////
1074
1075//The next procedure normalizationPrimes computes the normalization of an
1076//irreducible or an equidimensional ideal i.
1077//- If i is irreducuble, then the returned list, say nor, has size 2
1078//with nor[1] the normalization ring and nor[2] the delta invariant.
1079//- If i is equidimensional, than the "splitting tools" can create a
1080//decomposition of i and nor can have more than 1 ring.
1081
1082static proc normalizationPrimes(ideal i,ideal ihp,int delt,intvec delti,list #)
1083"USAGE:   normalizationPrimes(i,ihp,delt[,si]);  i = equidimensional ideal,
1084         ihp = map (partial normalization), delt = partial delta-invariant,
1085         si = ideal s.t. V(si) contains singular locus (optional)
1086RETURN:   a list of rings, say nor, and an integer, the delta-invariant
1087          at the end of the list.
1088          each ring nor[j], j = 1..size(nor)-1, contains two ideals
1089          with given names norid and normap such that
1090           - the direct sum of the rings nor[j]/norid is
1091             the normalization of basering/i;
1092           - normap gives the normalization map from basering/id
1093             to nor[j]/norid (for each j)
1094          nor[size(nor)] = dim_K(normalisation(P/i) / (P/i)) is the
1095          delta-invariant, where P is the basering.
1096EXAMPLE: example normalizationPrimes; shows an example
1097"
1098{
1099   //Note: this procedure calls itself as long as the test for
1100   //normality, i.e if R==Hom(J,J), is negative.
1101
1102   int printlev = printlevel;   //store printlevel in order to reset it later
1103   int y = printlevel-voice+2;  // y=printlevel (default: y=0)
1104   if(y>=1)
1105   {
1106     "";
1107     "// START a normalization loop with the ideal";
1108     i;  "";
1109     "// in the ring:";
1110     basering;  "";
1111     pause();
1112     "";
1113   }
1114
1115   def BAS=basering;
1116   list result,keepresult1,keepresult2,JM,gnirlist;
1117   ideal J,SB,MB;
1118   int depth,lauf,prdim,osaz;
1119   int ti=timer;
1120
1121   gnirlist = ringlist(BAS);
1122
1123//----------- the trivial case of a zero ideal as input, RETURN ------------
1124   if(size(i)==0)
1125   {
1126      if(y>=1)
1127      {
1128          "// the ideal was the zero-ideal";
1129      }
1130     // execute("ring newR7="+charstr(basering)+",("+varstr(basering)+"),("
1131     //                 +ordstr(basering)+");");
1132         def newR7 = ring(gnirlist);
1133         setring newR7;
1134         ideal norid=ideal(0);
1135         ideal normap=fetch(BAS,ihp);
1136         export norid;
1137         export normap;
1138         result=newR7;
1139         result[size(result)+1]=list(delt,delti);
1140         setring BAS;
1141         return(result);
1142   }
1143
1144//--------------- General NOTATION, compute SB of input -----------------
1145// SM is a list, the result of mstd(i)
1146// SM[1] = SB of input ideal i,
1147// SM[2] = (minimal) generators for i.
1148// We work with SM and will copy the attributes from i to SM[2]
1149// JM will be a list, either JM[1]=maxideal(1),JM[2]=maxideal(1)
1150// in case i has onlySingularAtZero, or JM = mstd(si) where si = #[1],
1151// or JM = mstd(J) where J is the ideal of the singular locus
1152// JM[2] must be (made) radical
1153
1154   if(y>=1)
1155   {
1156     "// SB-computation of the ideal";
1157   }
1158
1159   list SM = mstd(i);              //Now the work starts
1160   int dimSM =  dim(SM[1]);        //dimension of variety to normalize
1161   if(y>=1)
1162   {
1163      "// the dimension is:";  dimSM;
1164   }
1165//----------------- the general case, set attributes ----------------
1166   //Note: onlySingularAtZero is NOT preserved under the ring extension
1167   //basering --> Hom(J,J) (in contrast to isIsolatedSingularity),
1168   //therefore we reset it:
1169
1170   attrib(i,"onlySingularAtZero",0);
1171
1172   if(attrib(i,"isPrim")==1)
1173   {
1174      attrib(SM[2],"isPrim",1);
1175   }
1176   else
1177   {
1178      attrib(SM[2],"isPrim",0);
1179   }
1180   if(attrib(i,"isIsolatedSingularity")==1)
1181   {
1182      attrib(SM[2],"isIsolatedSingularity",1);
1183   }
1184   else
1185   {
1186      attrib(SM[2],"isIsolatedSingularity",0);
1187   }
1188   if(attrib(i,"isCohenMacaulay")==1)
1189   {
1190      attrib(SM[2],"isCohenMacaulay",1);
1191   }
1192   else
1193   {
1194      attrib(SM[2],"isCohenMacaulay",0);
1195   }
1196   if(attrib(i,"isRegInCodim2")==1)
1197   {
1198      attrib(SM[2],"isRegInCodim2",1);
1199   }
1200   else
1201   {
1202      attrib(SM[2],"isRegInCodim2",0);
1203   }
1204   if(attrib(i,"isEquidimensional")==1)
1205   {
1206      attrib(SM[2],"isEquidimensional",1);
1207   }
1208   else
1209   {
1210      attrib(SM[2],"isEquidimensional",0);
1211   }
1212   if(attrib(i,"isCompleteIntersection")==1)
1213   {
1214     attrib(SM[2],"isCompleteIntersection",1);
1215   }
1216   else
1217   {
1218      attrib(SM[2],"isCompleteIntersection",0);
1219   }
1220   if(attrib(i,"isHypersurface")==1)
1221   {
1222     attrib(SM[2],"isHypersurface",1);
1223   }
1224   else
1225   {
1226      attrib(SM[2],"isHypersurface",0);
1227   }
1228
1229   if(attrib(i,"onlySingularAtZero")==1)
1230   {
1231      attrib(SM[2],"onlySingularAtZero",1);
1232   }
1233   else
1234   {
1235      attrib(SM[2],"onlySingularAtZero",0);
1236   }
1237
1238   //------- an easy and cheap test for onlySingularAtZero ---------
1239   if( (attrib(SM[2],"isIsolatedSingularity")==1) && (homog(SM[2])==1) )
1240   {
1241      attrib(SM[2],"onlySingularAtZero",1);
1242   }
1243
1244//-------------------- Trivial cases, in each case RETURN ------------------
1245// input ideal is the ideal of a partial normalization
1246
1247   // ------------ Trivial case: input ideal contains a unit ---------------
1248   if( dimSM == -1)
1249   {  "";
1250      "      // A unit ideal was found.";
1251      "      // Stop with partial result computed so far";"";
1252
1253         MB=SM[2];
1254         intvec rw;
1255         list LL=substpart(MB,ihp,0,rw);
1256         def newR6=LL[1];
1257         setring newR6;
1258         ideal norid=endid;
1259         ideal normap=endphi;
1260         kill endid,endphi;
1261         export norid;
1262         export normap;
1263         result=newR6;
1264         result[size(result)+1]=list(delt,delti);
1265         setring BAS;
1266         return(result);
1267   }
1268
1269   // --- Trivial case: input ideal is zero-dimensional and homog ---
1270   if( (dim(SM[1])==0) && (homog(SM[2])==1) )
1271   {
1272      if(y>=1)
1273      {
1274         "// the ideal was zero-dimensional and homogeneous";
1275      }
1276      MB=maxideal(1);
1277      intvec rw;
1278      list LL=substpart(MB,ihp,0,rw);
1279      def newR5=LL[1];
1280      setring newR5;
1281      ideal norid=endid;
1282      ideal normap=endphi;
1283      kill endid,endphi;
1284      export norid;
1285      export normap;
1286      result=newR5;
1287      result[size(result)+1]=list(delt,delti);
1288      setring BAS;
1289      return(result);
1290   }
1291
1292   // --- Trivial case: input ideal defines a line ---
1293   //the one-dimensional, homogeneous case and degree 1 case
1294   if( (dim(SM[1])==1) && (maxdeg1(SM[2])==1) && (homog(SM[2])==1) )
1295   {
1296      if(y>=1)
1297      {
1298         "// the ideal defines a line";
1299      }
1300      MB=SM[2];
1301      intvec rw;
1302      list LL=substpart(MB,ihp,0,rw);
1303      def newR4=LL[1];
1304      setring newR4;
1305      ideal norid=endid;
1306      ideal normap=endphi;
1307      kill endid,endphi;
1308      export norid;
1309      export normap;
1310      result=newR4;
1311      result[size(result)+1]=list(delt,delti);
1312      setring BAS;
1313      return(result);
1314   }
1315
1316//---------------------- The non-trivial cases start -------------------
1317   //the higher dimensional case
1318   //we test first hypersurface, CohenMacaulay and complete intersection
1319
1320   if( ((size(SM[2])+dim(SM[1])) == nvars(basering)) )
1321   {
1322      //the test for complete intersection
1323      attrib(SM[2],"isCohenMacaulay",1);
1324      attrib(SM[2],"isCompleteIntersection",1);
1325      attrib(SM[2],"isEquidimensional",1);
1326      if(y>=1)
1327      {
1328         "// the ideal is a complete intersection";
1329      }
1330   }
1331   if( size(SM[2]) == 1 )
1332   {
1333      attrib(SM[2],"isHypersurface",1);
1334      if(y>=1)
1335      {
1336         "// the ideal is a hypersurface";
1337      }
1338   }
1339
1340   //------------------- compute the singular locus -------------------
1341   // Computation if singular locus is critical
1342   // Notation: J ideal of singular locus or (if given) containing it
1343   // JM = mstd(J) or maxideal(1),maxideal(1)
1344   // JM[1] SB of singular locus, JM[2] minbasis, dimJ = dim(JM[1])
1345   // SM[1] SB of the input ideal i, SM[2] minbasis
1346   // Computation if singular locus is critical, because it determines the
1347   // size of the ring Hom_R(J,J). We only need a test ideal contained in J.
1348
1349   //----------------------- onlySingularAtZero -------------------------
1350   if( attrib(SM[2],"onlySingularAtZero") )
1351   {
1352       JM = maxideal(1),maxideal(1);
1353       attrib(JM[1],"isSB",1);
1354       attrib(JM[2],"isRadical",1);
1355       if( dim(SM[1]) >=2 )
1356       {
1357         attrib(SM[2],"isRegInCodim2",1);
1358       }
1359   }
1360
1361   //-------------------- not onlySingularAtZero -------------------------
1362   if( attrib(SM[2],"onlySingularAtZero") == 0 )
1363   {
1364      //--- the case where an ideal #[1] is given:
1365      if( size(#)>0 )
1366      {
1367         J = #[1],SM[2];
1368         JM = mstd(J);
1369         if( typeof(attrib(#[1],"isRadical"))!="int" )
1370         {
1371            attrib(JM[2],"isRadical",0);
1372         }
1373      }
1374
1375      //--- the case where an ideal #[1] is not given:
1376      if( (size(#)==0) )
1377      {
1378         if(y >=1 )
1379         {
1380            "// singular locus will be computed";
1381         }
1382
1383         J = SM[1],minor(jacob(SM[2]),nvars(basering)-dim(SM[1]),SM[1]);
1384         if( y >=1 )
1385         {
1386            "// SB of singular locus will be computed";
1387         }
1388         JM = mstd(J);
1389      }
1390
1391      int dimJ = dim(JM[1]);
1392      attrib(JM[1],"isSB",1);
1393      if( y>=1 )
1394      {
1395         "// the dimension of the singular locus is";  dimJ ; "";
1396      }
1397
1398      if(dim(JM[1]) <= dim(SM[1])-2)
1399      {
1400         attrib(SM[2],"isRegInCodim2",1);
1401      }
1402
1403      //------------------ the smooth case, RETURN -------------------
1404      if( dimJ == -1 )
1405      {
1406         if(y>=1)
1407         {
1408            "// the ideal is smooth";
1409         }
1410         MB=SM[2];
1411         intvec rw;
1412         list LL=substpart(MB,ihp,0,rw);
1413         def newR3=LL[1];
1414         setring newR3;
1415         ideal norid=endid;
1416         ideal normap=endphi;
1417         kill endid,endphi;
1418         export norid;
1419         export normap;
1420         result=newR3;
1421         result[size(result)+1]=list(delt,delti);
1422         setring BAS;
1423         return(result);
1424      }
1425
1426      //------- extra check for onlySingularAtZero, relatively cheap ----------
1427      //it uses the procedure 'locAtZero' from for testing
1428      //if an ideal is concentrated at 0
1429       if(y>=1)
1430       {
1431         "// extra test for onlySingularAtZero:";
1432       }
1433       // Not so cheap... removed       
1434       //if ( locAtZero(JM[1]) )
1435       //{
1436       //    attrib(SM[2],"onlySingularAtZero",1);
1437       //    JM = maxideal(1),maxideal(1);
1438       //    attrib(JM[1],"isSB",1);
1439       //    attrib(JM[2],"isRadical",1);
1440       //}
1441       //else
1442       //{
1443              attrib(SM[2],"onlySingularAtZero",0);
1444       //}
1445   }
1446
1447  //displaying the attributes:
1448   if(y>=2)
1449   {
1450      "// the attributes of the ideal are:";
1451      "// isCohenMacaulay:", attrib(SM[2],"isCohenMacaulay");
1452      "// isCompleteIntersection:", attrib(SM[2],"isCompleteIntersection");
1453      "// isHypersurface:", attrib(SM[2],"isHypersurface");
1454      "// isEquidimensional:", attrib(SM[2],"isEquidimensional");
1455      "// isPrim:", attrib(SM[2],"isPrim");
1456      "// isRegInCodim2:", attrib(SM[2],"isRegInCodim2");
1457      "// isIsolatedSingularity:", attrib(SM[2],"isIsolatedSingularity");
1458      "// onlySingularAtZero:", attrib(SM[2],"onlySingularAtZero");
1459      "// isRad:", attrib(SM[2],"isRad");"";
1460   }
1461
1462   //------------- case: CohenMacaulay in codim 2, RETURN ---------------
1463   if( (attrib(SM[2],"isRegInCodim2")==1) &&
1464       (attrib(SM[2],"isCohenMacaulay")==1) )
1465   {
1466      if(y>=1)
1467      {
1468         "// the ideal was CohenMacaulay and regular in codim 2, hence normal";
1469      }
1470      MB=SM[2];
1471      intvec rw;
1472      list LL=substpart(MB,ihp,0,rw);
1473      def newR6=LL[1];
1474      setring newR6;
1475      ideal norid=endid;
1476      ideal normap=endphi;
1477      kill endid,endphi;
1478      export norid;
1479      export normap;
1480      result=newR6;
1481      result[size(result)+1]=list(delt,delti);
1482      setring BAS;
1483      return(result);
1484   }
1485
1486//---------- case: isolated singularity only at 0, RETURN ------------
1487   // In this case things are easier, we can use the maximal ideal as radical
1488   // of the singular locus;
1489   // JM mstd of ideal of singular locus, SM mstd of input ideal
1490
1491   if( attrib(SM[2],"onlySingularAtZero") )
1492   {
1493   //------ check variables for being a non zero-divizor ------
1494   // SL = ideal of vars not contained in ideal SM[1]:
1495
1496      attrib(SM[2],"isIsolatedSingularity",1);
1497      ideal SL = simplify(reduce(maxideal(1),SM[1]),2);
1498      ideal Ann = quotient(SM[2],SL[1]);
1499      ideal qAnn = simplify(reduce(Ann,SM[1]),2);
1500      //NOTE: qAnn=0 if and only if first var (=SL[1]) not in SM is a nzd of R/SM
1501
1502   //------------- We found a non-zerodivisor of R/SM -----------------------
1503   // here the enlarging of the ring via Hom_R(J,J) starts
1504
1505      if( size(qAnn)==0 )
1506      {
1507         if(y>=1)
1508         {
1509            "";
1510            "// the ideal rad(J):"; maxideal(1);
1511            "";
1512         }
1513
1514      // ------------- test for normality, compute Hom_R(J,J) -------------
1515      // Note:
1516      // HomJJ (ideal SBid, ideal id, ideal J, poly p) with
1517      //        SBid = SB of id, J = radical ideal of basering  P with:
1518      //        nonNormal(R) is in V(J), J contains the nonzero divisor p
1519      //        of R = P/id (J = test ideal)
1520      // returns a list l of three objects
1521      // l[1] : a polynomial ring, containing two ideals, 'endid' and 'endphi'
1522      //        s.t. l[1]/endid = Hom_R(J,J) and endphi= map R -> Hom_R(J,J)
1523      // l[2] : an integer which is 1 if phi is an isomorphism, 0 if not
1524      // l[3] : an integer, = dim_K(Hom_R(J,J)/R) if finite, -1 otherwise
1525
1526         list RR;
1527         RR = SM[1],SM[2],maxideal(1),SL[1];
1528         RR = HomJJ(RR,y);
1529         // --------------------- non-normal case ------------------
1530         //RR[2]==0 means that the test for normality is negative
1531         if( RR[2]==0 )
1532         {
1533            def newR=RR[1];
1534            setring newR;
1535            map psi=BAS,endphi;
1536            list JM = psi(JM); //###
1537            ideal J = JM[2];
1538            if ( delt>=0 && RR[3]>=0 )
1539            {
1540               delt = delt+RR[3];
1541            }
1542            else
1543            { delt = -1; }
1544            delti[size(delti)]=delt;
1545
1546            // ---------- recursive call of normalizationPrimes -----------
1547        //normalizationPrimes(ideal i,ideal ihp,int delt,intvec delti,list #)
1548        //ihp = (partial) normalisation map from basering
1549        //#[1] ideal s.t. V(#[1]) contains singular locus of i (test ideal)
1550
1551            if ( y>=1 )
1552            {
1553            "// case: onlySingularAtZero, non-zerodivisor found";
1554            "// contribution of delta in ringextension R -> Hom_R(J,J):"; delt;
1555            }
1556
1557            //intvec atr=getAttrib(endid);
1558            //"//### case: isolated singularity only at 0, recursive";
1559            //"size endid:", size(endid), size(string(endid));
1560            //"interred:";
1561            //endid = interred(endid);
1562            //endid = setAttrib(endid,atr);
1563            //"size endid:", size(endid), size(string(endid));
1564
1565           printlevel=printlevel+1;
1566           list tluser =
1567                normalizationPrimes(endid,psi(ihp),delt,delti);
1568           //list tluser =
1569           //     normalizationPrimes(endid,psi(ihp),delt,delti,J);
1570           //#### ??? improvement: give also the old ideal of sing locus???
1571
1572           printlevel = printlev;             //reset printlevel
1573           setring BAS;
1574           return(tluser);
1575         }
1576
1577         // ------------------ the normal case, RETURN -----------------
1578         // Now RR[2] must be 1, hence the test for normality was positive
1579         MB=SM[2];
1580         //execute("ring newR7="+charstr(basering)+",("+varstr(basering)+"),("
1581         //             +ordstr(basering)+");");
1582         def newR7 = ring(gnirlist);
1583         setring newR7;
1584         ideal norid=fetch(BAS,MB);
1585         ideal normap=fetch(BAS,ihp);
1586         if ( delt>=0 && RR[3]>=0 )
1587         {
1588               delt = delt+RR[3];
1589         }
1590         else
1591         { delt = -1; }
1592         delti[size(delti)]=delt;
1593
1594         intvec atr = getAttrib(norid);
1595
1596         //"//### case: isolated singularity only at 0, final";
1597         //"size norid:", size(norid), size(string(norid));
1598         //"interred:";
1599         //norid = interred(norid);
1600         //norid = setAttrib(norid,atr);
1601         //"size norid:", size(norid), size(string(norid));
1602
1603         export norid;
1604         export normap;
1605         result=newR7;
1606         result[size(result)+1]=list(delt,delti);
1607         setring BAS;
1608         return(result);
1609      }
1610
1611   //------ zerodivisor of R/SM was found, gives a splitting ------------
1612   //Now the case where qAnn!=0, i.e. SL[1] is a zero divisor of R/SM
1613   //and we have found a splitting: id and id1
1614   //id = Ann defines components of R/SM in the complement of V(SL[1])
1615   //id1 defines components of R/SM in the complement of V(id)
1616
1617      else
1618       {
1619          ideal id = Ann;
1620          attrib(id,"isCohenMacaulay",0);
1621          attrib(id,"isPrim",0);
1622          attrib(id,"isIsolatedSingularity",1);
1623          attrib(id,"isRegInCodim2",0);
1624          attrib(id,"isHypersurface",0);
1625          attrib(id,"isCompleteIntersection",0);
1626          attrib(id,"isEquidimensional",0);
1627          attrib(id,"onlySingularAtZero",1);
1628
1629          ideal id1 = quotient(SM[2],Ann);
1630          attrib(id1,"isCohenMacaulay",0);
1631          attrib(id1,"isPrim",0);
1632          attrib(id1,"isIsolatedSingularity",1);
1633          attrib(id1,"isRegInCodim2",0);
1634          attrib(id1,"isHypersurface",0);
1635          attrib(id1,"isCompleteIntersection",0);
1636          attrib(id1,"isEquidimensional",0);
1637          attrib(id1,"onlySingularAtZero",1);
1638
1639          // ---------- recursive call of normalizationPrimes -----------
1640          if ( y>=1 )
1641          {
1642            "// case: onlySingularAtZero, zerodivisor found, splitting:";
1643            "// total delta before splitting:", delt;
1644            "// splitting in two components:";
1645          }
1646
1647          printlevel = printlevel+1;  //to see comments in normalizationPrimes
1648          keepresult1 = normalizationPrimes(id,ihp,0,0);   //1st split factor
1649          keepresult2 = normalizationPrimes(id1,ihp,0,0);  //2nd split factor
1650          printlevel = printlev;                           //reset printlevel
1651
1652          int delt1 = keepresult1[size(keepresult1)][1];
1653          int delt2 = keepresult2[size(keepresult2)][1];
1654          intvec delti1 = keepresult1[size(keepresult1)][2];
1655          intvec delti2 = keepresult2[size(keepresult2)][2];
1656
1657          if( delt>=0 && delt1>=0 && delt2>=0 )
1658          {  ideal idid1=id,id1;
1659             int mul = vdim(std(idid1));
1660             if ( mul>=0 )
1661             {
1662               delt = delt+mul+delt1+delt2;
1663             }
1664             else
1665             {
1666               delt = -1;
1667             }
1668          }
1669         if ( y>=1 )
1670         {
1671           "// delta of first component:", delt1;
1672           "// delta of second componenet:", delt2;
1673           "// intersection multiplicity of both components:", mul;
1674           "// total delta after splitting:", delt;
1675         }
1676
1677          else
1678          {
1679            delt = -1;
1680          }
1681          for(lauf=1;lauf<=size(keepresult2)-1;lauf++)
1682          {
1683             keepresult1=insert(keepresult1,keepresult2[lauf]);
1684          }
1685          keepresult1[size(keepresult1)]=list(delt,delti);
1686
1687          return(keepresult1);
1688       }
1689   }
1690   // Case "onlySingularAtZero" has finished and returned result
1691
1692//-------------- General case, not onlySingularAtZero, RETURN ---------------
1693   //test for non-normality, i.e. if Hom(I,I)<>R
1694   //we can use Hom(I,I) to continue
1695
1696   //------ check variables for being a non zero-divizor ------
1697   // SL = ideal of vars not contained in ideal SM[1]:
1698
1699   ideal SL = simplify(reduce(JM[2],SM[1]),2);
1700   ideal Ann = quotient(SM[2],SL[1]);
1701   ideal qAnn = simplify(reduce(Ann,SM[1]),2);
1702   //NOTE: qAnn=0 <==> first var (=SL[1]) not contained in SM is a nzd of R/SM
1703
1704   //------------- We found a non-zerodivisor of R/SM -----------------------
1705   //SM = mstd of ideal of variety, JM = mstd of ideal of singular locus
1706
1707   if( size(qAnn)==0 )
1708   {
1709      list RR;
1710      list RS;
1711      // ----------------- Computation of the radical -----------------
1712      if(y>=1)
1713      {
1714         "// radical computation of singular locus";
1715      }
1716      J = radical(JM[2]);   //the radical of singular locus
1717      JM = mstd(J);
1718
1719      if(y>=1)
1720      {
1721        "// radical is equal to:";"";  JM[2];
1722        "";
1723      }
1724      // ------------ choose non-zerodivisor of smaller degree ----------
1725      //### evtl. fuer SL[1] anderen Nichtnullteiler aus J waehlen ?
1726      if( deg(SL[1]) > deg(J[1]) )
1727      {
1728         Ann=quotient(SM[2],J[1]);
1729         qAnn=simplify(reduce(Ann,SM[1]),2);
1730         if(size(qAnn)==0)
1731         {
1732           SL[1]=J[1];
1733         }
1734      }
1735
1736      // --------------- computation of Hom(rad(J),rad(J)) --------------
1737      RR=SM[1],SM[2],JM[2],SL[1];
1738
1739     if(y>=1)
1740     {
1741        "// compute Hom(rad(J),rad(J))";
1742     }
1743
1744     RS=HomJJ(RR,y);               //most important subprocedure
1745
1746     // ------------------ the normal case, RETURN -----------------
1747     // RS[2]==1 means that the test for normality was positive
1748     if(RS[2]==1)
1749     {
1750         def lastR=RS[1];
1751         setring lastR;
1752         map psi1=BAS,endphi;
1753         ideal norid=endid;
1754         ideal normap=psi1(ihp);
1755         kill endid,endphi;
1756
1757        intvec atr=getAttrib(norid);
1758
1759        //"//### general case: not isolated singularity only at 0, final";
1760        //"size norid:", size(norid), size(string(norid));
1761        //"interred:";
1762        //norid = interred(norid);
1763        //norid = setAttrib(norid,atr);
1764        //"size norid:", size(norid), size(string(norid));
1765
1766         export norid;
1767         export normap;
1768         result=lastR;
1769         if ( y>=1 )
1770         {
1771            "// case: not onlySingularAtZero, last ring Hom_R(J,J) computed";
1772            "// delta before last ring:", delt;
1773         }
1774
1775         if ( delt>=0 && RS[3]>=0 )
1776         {
1777            delt = delt+RS[3];
1778         }
1779         else
1780         { delt = -1; }
1781
1782        // delti = delti,delt;
1783         delti[size(delti)]=delt;
1784
1785         if ( y>=1 )
1786         {
1787           "// delta of last ring:", delt;
1788         }
1789
1790         result[size(result)+1]=list(delt,delti);
1791         setring BAS;
1792         return(result);
1793     }
1794
1795    // ----- the non-normal case, recursive call of normalizationPrimes -------
1796    // RS=HomJJ(RR,y) was computed above, RS[1] contains endid and endphi
1797    // RS[1] = new ring Hom_R(J,J), RS[2]= 0 or 1, RS[2]=contribution to delta
1798    // now RS[2]must be 0, i.e. the test for normality was negative
1799
1800      int n = nvars(basering);
1801      ideal MJ = JM[2];
1802
1803      def newR=RS[1];
1804      setring newR;
1805      map psi=BAS,endphi;
1806      if ( y>=1 )
1807      {
1808        "// case: not onlySingularAtZero, compute new ring = Hom_R(J,J)";
1809        "// delta of old ring:", delt;
1810      }
1811      if ( delt>=0 && RS[3]>=0 )
1812      {
1813         delt = delt+RS[3];
1814      }
1815      else
1816      { delt = -1; }
1817      if ( y>=1 )
1818      {
1819        "// delta of new ring:", delt;
1820      }
1821
1822      delti[size(delti)]=delt;
1823      intvec atr=getAttrib(endid);
1824
1825      //"//### general case: not isolated singularity only at 0, recursive";
1826      //"size endid:", size(endid), size(string(endid));
1827      //"interred:";
1828      //endid = interred(endid);
1829      //endid = setAttrib(endid,atr);
1830      //"size endid:", size(endid), size(string(endid));
1831
1832      printlevel = printlevel+1;
1833      list tluser=
1834          normalizationPrimes(endid,psi(ihp),delt,delti,psi(MJ));
1835      printlevel = printlev;                //reset printlevel
1836      setring BAS;
1837      return(tluser);
1838   }
1839
1840   //---- A whole singular component was found, RETURN -----
1841   if( Ann == 1)
1842   {
1843      "// Input appeared not to be a radical ideal!";
1844      "// A (everywhere singular) component with ideal";
1845      "// equal to its Jacobian ideal was found";
1846      "// Procedure will stop with partial result computed so far";"";
1847
1848         MB=SM[2];
1849         intvec rw;
1850         list LL=substpart(MB,ihp,0,rw);
1851         def newR6=LL[1];
1852         setring newR6;
1853         ideal norid=endid;
1854         ideal normap=endphi;
1855         kill endid,endphi;
1856         export norid;
1857         export normap;
1858         result=newR6;
1859         result[size(result)+1]=lst(delt,delti);
1860         setring BAS;
1861         return(result);
1862   }
1863
1864   //------ zerodivisor of R/SM was found, gives a splitting ------------
1865   //Now the case where qAnn!=0, i.e. SL[1] is a zero divisor of R/SM
1866   //and we have found a splitting: new1 and new2
1867   //id = Ann defines components of R/SM in the complement of V(SL[1])
1868   //id1 defines components of R/SM in the complement of V(id)
1869
1870   else
1871   {
1872      if(y>=1)
1873      {
1874         "// zero-divisor found";
1875      }
1876      int equi = attrib(SM[2],"isEquidimensional");
1877      int oSAZ = attrib(SM[2],"onlySingularAtZero");
1878      int isIs = attrib(SM[2],"isIsolatedSingularity");
1879
1880      ideal new1 = Ann;
1881      ideal new2 = quotient(SM[2],Ann);
1882      //ideal new2=SL[1],SM[2];
1883
1884      //execute("ring newR1="+charstr(basering)+",("+varstr(basering)+"),("
1885      //                +ordstr(basering)+");");
1886      def newR1 = ring(gnirlist);
1887      setring newR1;
1888
1889      ideal vid = fetch(BAS,new1);
1890      ideal ihp = fetch(BAS,ihp);
1891      attrib(vid,"isCohenMacaulay",0);
1892      attrib(vid,"isPrim",0);
1893      attrib(vid,"isIsolatedSingularity",isIs);
1894      attrib(vid,"isRegInCodim2",0);
1895      attrib(vid,"onlySingularAtZero",oSAZ);
1896      attrib(vid,"isEquidimensional",equi);
1897      attrib(vid,"isHypersurface",0);
1898      attrib(vid,"isCompleteIntersection",0);
1899
1900      // ---------- recursive call of normalizationPrimes -----------
1901      if ( y>=1 )
1902      {
1903        "// total delta before splitting:", delt;
1904        "// splitting in two components:";
1905      }
1906      printlevel = printlevel+1;
1907      keepresult1 =
1908                  normalizationPrimes(vid,ihp,0,0);  //1st split factor
1909
1910      list delta1 = keepresult1[size(keepresult1)];
1911
1912      setring BAS;
1913      //execute("ring newR2="+charstr(basering)+",("+varstr(basering)+"),("
1914      //                +ordstr(basering)+");");
1915      def newR2 = ring(gnirlist);
1916      setring newR2;
1917
1918      ideal vid = fetch(BAS,new2);
1919      ideal ihp = fetch(BAS,ihp);
1920      attrib(vid,"isCohenMacaulay",0);
1921      attrib(vid,"isPrim",0);
1922      attrib(vid,"isIsolatedSingularity",isIs);
1923      attrib(vid,"isRegInCodim2",0);
1924      attrib(vid,"isEquidimensional",equi);
1925      attrib(vid,"isHypersurface",0);
1926      attrib(vid,"isCompleteIntersection",0);
1927      attrib(vid,"onlySingularAtZero",oSAZ);
1928
1929      keepresult2 =
1930                    normalizationPrimes(vid,ihp,0,0);
1931      list delta2 = keepresult2[size(keepresult2)];   //2nd split factor
1932      printlevel = printlev;                          //reset printlevel
1933
1934      setring BAS;
1935
1936      //compute intersection multiplicity of both components:
1937      new1 = new1,new2;
1938      int mul=vdim(std(new1));
1939
1940     // ----- normalizationPrimes finished, add up results, RETURN --------
1941      for(lauf=1;lauf<=size(keepresult2)-1;lauf++)
1942      {
1943         keepresult1 = insert(keepresult1,keepresult2[lauf]);
1944      }
1945      if ( delt >=0 && delta1[1] >=0 && delta2[1] >=0 && mul >=0 )
1946      {
1947         delt = delt+mul+delta1[1]+delta2[1];
1948      }
1949      else
1950      {  delt = -1; }
1951      delti = -2;
1952
1953      if ( y>=1 )
1954      {
1955        "// zero divisor produced a splitting into two components";
1956        "// delta of first component:", delta1;
1957        "// delta of second componenet:", delta2;
1958        "// intersection multiplicity of both components:", mul;
1959        "// total delta after splitting:", delt;
1960      }
1961      keepresult1[size(keepresult1)] = list(delt,delti);
1962      return(keepresult1);
1963   }
1964}
1965example
1966{ "EXAMPLE:";echo = 2;
1967   // Huneke
1968   ring qr=31991,(a,b,c,d,e),dp;
1969   ideal i=
1970   5abcde-a5-b5-c5-d5-e5,
1971   ab3c+bc3d+a3be+cd3e+ade3,
1972   a2bc2+b2cd2+a2d2e+ab2e2+c2de2,
1973   abc5-b4c2d-2a2b2cde+ac3d2e-a4de2+bcd2e3+abe5,
1974   ab2c4-b5cd-a2b3de+2abc2d2e+ad4e2-a2bce3-cde5,
1975   a3b2cd-bc2d4+ab2c3e-b5de-d6e+3abcd2e2-a2be4-de6,
1976   a4b2c-abc2d3-ab5e-b3c2de-ad5e+2a2bcde2+cd2e4,
1977   b6c+bc6+a2b4e-3ab2c2de+c4d2e-a3cde2-abd3e2+bce5;
1978
1979   list pr=normalizationPrimes(i);
1980   def r1 = pr[1];
1981   setring r1;
1982   norid;
1983   normap;
1984}
1985
1986///////////////////////////////////////////////////////////////////////////////
1987static proc substpart(ideal endid, ideal endphi, int homo, intvec rw)
1988
1989"//Repeated application of elimpart to endid, until no variables can be
1990//directy substituded. homo=1 if input is homogeneous, rw contains
1991//original weights, endphi (partial) normalization map";
1992
1993//NOTE concerning iteration of maps: Let phi: x->f(y,z), y->g(x,z) then
1994//phi: x+y+z->f(y,z)+g(x,z)+z, phi(phi):x+y+z->f(g(x,z),z)+g(f(y,z),z)+z
1995//and so on: none of the x or y will be eliminated
1996//Now subst: first x and then y: x+y+z->f(g(x,z),z)+g(x,z)+z eliminates y
1997//further subst replaces x by y, makes no sense (objects more compicated).
1998//Subst first y and then x eliminates x
1999//In our situation we have triangular form: x->f(y,z), y->g(z).
2000//phi: x+y+z->f(y,z)+g(z)+z, phi(phi):x+y+z->f(g(z),z)+g(z)+z eliminates x,y
2001//subst x,y: x+y+z->f(g(z),z)+g(z)+z, eliminates x,y
2002//subst y,x: x+y+z->f(y,z)+g(z)+z eliminates only x
2003//HENCE: substitute vars depending on most other vars first
2004//However, if the sytem xi-fi is reduced then xi does not appear in any of the
2005//fj and hence the order does'nt matter when substitutinp xi by fi
2006
2007{
2008   def newRing = basering;
2009   int ii,jj;
2010   map phi = newRing,maxideal(1);    //identity map
2011   list Le = elimpart(endid);
2012   //this proc and the next loop try to substitute as many variables as
2013   //possible indices of substituted variables
2014
2015   int q = size(Le[2]);    //q vars, stored in Le[2], have been substitutet
2016   intvec rw1 = 0;         //will become indices of substituted variables
2017   rw1[nvars(basering)] = 0;
2018   rw1 = rw1+1;            //rw1=1,..,1 (as many 1 as nvars(basering))
2019
2020   while( size(Le[2]) != 0 )
2021   {
2022      endid = Le[1];
2023      if ( defined(ps) )
2024      { kill ps; }
2025      map ps = newRing,Le[5];
2026      phi = ps(phi);
2027      for(ii=1;ii<=size(Le[2]);ii++)
2028      {
2029         phi=phi(phi);
2030      }
2031      //eingefuegt wegen x2-y2z2+z3
2032
2033      for( ii=1; ii<=size(rw1); ii++ )
2034      {
2035         if( Le[4][ii]==0 )        //ii = index of var which was substituted
2036         {
2037            rw1[ii]=0;             //substituted vars have entry 0 in rw1
2038         }
2039      }
2040      Le=elimpart(endid);          //repeated application of elimpart
2041      q = q + size(Le[2]);
2042   }
2043   endphi = phi(endphi);
2044//---------- return -----------------------------------------------------------
2045// first the trivial case, where all variable have been eliminated
2046   if( nvars(newRing) == q )
2047   {
2048     ring lastRing = char(basering),T(1),dp;
2049     ideal endid = T(1);
2050     ideal endphi = T(1);
2051     for(ii=2; ii<=q; ii++ )
2052     {
2053        endphi[ii] = 0;
2054     }
2055     export(endid,endphi);
2056     list L = lastRing;
2057     setring newRing;
2058     return(L);
2059   }
2060
2061// in the homogeneous case put weights for the remaining vars correctly, i.e.
2062// delete from rw those weights for which the corresponding entry of rw1 is 0
2063
2064   if (homo==1 && nvars(newRing)-q >1 && size(endid) >0 )
2065   {
2066      jj=1;
2067      for( ii=2; ii<size(rw1); ii++)
2068      {
2069         jj++;
2070         if( rw1[ii]==0 )
2071         {
2072            rw=rw[1..jj-1],rw[jj+1..size(rw)];
2073            jj=jj-1;
2074         }
2075      }
2076      if( rw1[1]==0 ) { rw=rw[2..size(rw)]; }
2077      if( rw1[size(rw1)]==0 ){ rw=rw[1..size(rw)-1]; }
2078
2079      ring lastRing = char(basering),(T(1..nvars(newRing)-q)),(a(rw),dp);
2080   }
2081   else
2082   {
2083      ring lastRing = char(basering),(T(1..nvars(newRing)-q)),dp;
2084   }
2085   ideal lastmap;
2086   jj = 1;
2087
2088   for(ii=1; ii<=size(rw1); ii++ )
2089   {
2090      if ( rw1[ii]==1 ) { lastmap[ii] = T(jj); jj=jj+1; }
2091      if ( rw1[ii]==0 ) { lastmap[ii] = 0; }
2092   }
2093   map phi1 = newRing,lastmap;
2094   ideal endid  = phi1(endid);      //### bottelneck
2095   ideal endphi = phi1(endphi);
2096
2097/*
2098Versuch: subst statt phi
2099   for(ii=1; ii<=size(rw1); ii++ )
2100   {
2101      if ( rw1[ii]==1 ) { endid = subst(endid,var(ii),T(jj)); }
2102      if ( rw1[ii]==0 ) { endid = subst(endid,var(ii),0); }
2103   }
2104*/
2105   export(endid);
2106   export(endphi);
2107   list L = lastRing;
2108   setring newRing;
2109   return(L);
2110}
2111///////////////////////////////////////////////////////////////////////////////
2112static proc deltaP(ideal I)
2113{
2114   def R=basering;
2115   int c,d,i;
2116   int n=nvars(R);
2117   list nor;
2118   if(size(I)>1){ERROR("no hypersurface");}
2119   ideal J=std(slocus(I));
2120   if(dim(J)<=0){return(0);}
2121   poly h;
2122   d=1;
2123   while((d)&&(i<n))
2124   {
2125      i++;
2126      h=var(i);
2127      d=dim(std(J+ideal(h)));
2128   }
2129   i=0;
2130   while(d)
2131   {
2132      i++;
2133      if(i>10){ERROR("delta not found, please inform the authors")};
2134      h=randomLast(100)[n];
2135      d=dim(std(J+ideal(h)));
2136   }
2137   I=I,h-1;
2138   if(char(R)<=19)
2139   {
2140      nor=normalP(I);
2141   }
2142   else
2143   {
2144      nor=normal(I);
2145   }
2146   return(nor[2][2]);
2147}
2148
2149proc genus(ideal I,list #)
2150"USAGE:   genus(i) or genus(i,1); I a 1-dimensional ideal
2151RETURN:  an integer, the geometric genus p_g = p_a - delta of the projective
2152         curve defined by i, where p_a is the arithmetic genus.
2153NOTE:    delta is the sum of all local delta-invariants of the singularities,
2154         i.e. dim(R'/R), R' the normalization of the local ring R of the
2155         singularity. @*
2156         genus(i,1) uses the normalization to compute delta. Usually genus(i,1)
2157         is slower than genus(i) but sometimes not.
2158EXAMPLE: example genus; shows an example
2159"
2160{
2161   int w = printlevel-voice+2;  // w=printlevel (default: w=0)
2162
2163   def R0=basering;
2164   if(char(basering)>0)
2165   {
2166     def R1=changeord("dp");
2167     setring R1;
2168     ideal I=imap(R0,I);
2169     I=radical(I);
2170     I=std(I);
2171     if(dim(I)!=1)
2172     {
2173       if(((homog(I))&&(dim(I)!=2))||(!homog(I)))
2174       {
2175         ERROR("This is not a curve");
2176       }
2177     }
2178     if(homog(I)&&(dim(I)==2))
2179     {
2180       def S=R0;
2181       setring S;
2182       ideal J=I;
2183     }
2184     else
2185     {
2186       def S=changevar(varstr(R0)+",@t");
2187       setring S;
2188       ideal J=imap(R1,I);
2189       J=homog(J,@t);
2190       J=std(J);
2191     }
2192     int pa=1-hilbPoly(J)[1];
2193     pa=pa-deltaP(J);
2194     setring R0;
2195     return(pa);
2196   }
2197   I=std(I);
2198   if(dim(I)!=1)
2199   {
2200      if(((homog(I))&&(dim(I)!=2))||(!homog(I)))
2201      {
2202        // ERROR("This is not a curve");
2203        if(w==1){"** WARNING: Input does not define a curve **"; "";}
2204      }
2205   }
2206   list L=elimpart(I);
2207   if(size(L[2])!=0)
2208   {
2209      map psi=R0,L[5];
2210      I=std(psi(I));
2211   }
2212   if(size(I)==0)
2213   {
2214      return(0);
2215   }
2216   list N=findvars(I,0);
2217   if(size(N[1])==1)
2218   {
2219
2220      poly p=I[1];
2221     // if(deg(squarefree(p))<deg(p)){ERROR("Curve is not reduced");}
2222      return(-deg(p)+1);
2223   }
2224   if(size(N[1]) < nvars(R0))
2225   {
2226      string newvar=string(N[1]);
2227      execute("ring R=("+charstr(R0)+"),("+newvar+"),dp;");
2228      ideal I =imap(R0,I);
2229      attrib(I,"isSB",1);
2230   }
2231   else
2232   {
2233      def R=basering;
2234   }
2235   if(dim(I)==2)
2236   {
2237      def newR=basering;
2238   }
2239   else
2240   {
2241      if(dim(I)==0)
2242      {
2243         execute("ring Rhelp=("+charstr(R0)+"),(@s,@t),dp;");
2244      }
2245      else
2246      {
2247         execute("ring Rhelp=("+charstr(R0)+"),(@s),dp;");
2248      }
2249      def newR=R+Rhelp;
2250      setring newR;
2251      ideal I=imap(R,I);
2252      I=homog(I,@s);
2253      attrib(I,"isSB",1);
2254   }
2255
2256   if((nvars(basering)<=3)&&(size(I)>1))
2257   {
2258       ERROR("This is not equidimensional");
2259   }
2260
2261   intvec hp=hilbPoly(I);
2262   int p_a=1-hp[1];
2263   int d=hp[2];
2264
2265   if(w>=1)
2266   {
2267      "";"The ideal of the projective curve:";"";I;"";
2268      "The coefficients of the Hilbert polynomial";hp;
2269      "arithmetic genus:";p_a;
2270      "degree:";d;"";
2271   }
2272
2273   intvec v = hilb(I,1);
2274   int i,o;
2275   if(nvars(basering)>3)
2276   {
2277      map phi=newR,maxideal(1);
2278      int de;
2279      ideal K,L1;
2280      matrix M;
2281      poly m=var(4);
2282      poly he;
2283      for(i=5;i<=nvars(basering);i++){m=m*var(i);}
2284      K=eliminate(I,m,v);
2285      if(size(K)==1){de=deg(K[1]);}
2286      m=var(1);
2287      for(i=2;i<=nvars(basering)-3;i++){m=m*var(i);}
2288      i=0;
2289      while(d!=de)
2290      {
2291         o=1;
2292         i++;
2293         K=phi(I);
2294         K=eliminate(K,m,v);
2295         if(size(K)==1){de=deg(K[1]);}
2296         if((i==5)&&(d!=de))
2297         {
2298            K=reduce(equidimMax(I),I);
2299            if(size(K)!=0){ERROR("This is not equidimensional");}
2300         }
2301         if(i==10)
2302         {
2303            J;K;
2304            ERROR("genus: did not find a good projection for to
2305                           the plain");
2306         }
2307         if(i<5)
2308         {
2309            M=sparsetriag(nvars(newR),nvars(newR),80-5*i,i);
2310         }
2311         else
2312         {
2313            if(i<8)
2314            {
2315               M=transpose(sparsetriag(nvars(newR),nvars(newR),80-5*i,i));
2316            }
2317            else
2318            {
2319               he=0;
2320               while(he==0)
2321               {
2322                  M=randommat(nvars(newR),nvars(newR),ideal(1),20);
2323                  he=det(M);
2324               }
2325            }
2326         }
2327         L1=M*transpose(maxideal(1));
2328         phi=newR,L1;
2329      }
2330      I=K;
2331   }
2332   poly p=I[1];
2333
2334   execute("ring S=("+charstr(R)+"),(x,y,t),dp;");
2335   ideal L=maxideal(1);
2336   execute("ring C=("+charstr(R)+"),(x,y),ds;");
2337   ideal I;
2338   execute("ring A=("+charstr(R)+"),(x,t),dp;");
2339   map phi=S,1,x,t;
2340   map psi=S,x,1,t;
2341   poly g,h;
2342   ideal I,I1;
2343   execute("ring B=("+charstr(R)+"),(x,t),ds;");
2344
2345   setring S;
2346   if(o)
2347   {
2348     for(i=1;i<=nvars(newR)-3;i++){L[i]=0;}
2349     L=L,maxideal(1);
2350   }
2351   map sigma=newR,L;
2352   poly F=sigma(p);
2353   if(w>=1){"the projected curve:";"";F;"";}
2354
2355   kill newR;
2356
2357   int genus=(d-1)*(d-2)/2;
2358   if(w>=1){"the arithmetic genus of the plane curve:";genus;pause();}
2359
2360   int delt,deltaloc,deltainf,tau,tauinf,cusps,iloc,iglob,l,nsing,
2361       tauloc,tausing,k,rat,nbranchinf,nbranch,nodes,cuspsinf,nodesinf;
2362   list inv;
2363
2364   if(w>=1)
2365     {"";"analyse the singularities at oo";"";"singular locus at (1,x,0):";"";}
2366   setring A;
2367   g=phi(F);
2368   h=psi(F);
2369   I=g,jacob(g),var(2);
2370   I=std(I);
2371   if(deg(I[1])>0)
2372   {
2373      list qr=minAssGTZ(I);
2374      if(w>=1){qr;"";}
2375
2376      for(k=1;k<=size(qr);k++)
2377      {
2378         if(w>=1){ nsing=nsing+vdim(std(qr[k]));}
2379         inv=deltaLoc(g,qr[k]);
2380         deltainf=deltainf+inv[1];
2381         tauinf=tauinf+inv[2];
2382         l=vdim(std(qr[k]));
2383         if(inv[2]==l){nodesinf=nodesinf+l;}
2384         if(inv[2]==2*l){cuspsinf=cuspsinf+l;}
2385         nbranchinf=nbranchinf+inv[3];
2386      }
2387   }
2388   else
2389   {
2390     if(w>=1){"            the curve is smooth at (1,x,0)";"";}
2391   }
2392   if(w>=1){"singular locus at (0,1,0):";"";}
2393   inv=deltaLoc(h,maxideal(1));
2394   if((w>=1)&&(inv[2]!=0)){ nsing++;}
2395   deltainf=deltainf+inv[1];
2396   tauinf=tauinf+inv[2];
2397   if(inv[2]==1){nodesinf++;}
2398   if(inv[2]==2){cuspsinf++;}
2399
2400   if((w>=1)&&(inv[2]==0)){"            the curve is smooth at (0,1,0)";"";}
2401   if(inv[2]>0){nbranchinf=nbranchinf+inv[3];}
2402
2403   if(w>=1)
2404   {
2405      if(tauinf==0)
2406      {
2407        "            the curve is smooth at oo";"";
2408      }
2409      else
2410      {
2411         "number of singularities at oo:";nsing;
2412         "nodes at oo:";nodesinf;
2413         "cusps at oo:";cuspsinf;
2414         "branches at oo:";nbranchinf;
2415         "Tjurina number at oo:";tauinf;
2416         "delta at oo:";deltainf;
2417         "Milnor number at oo:";2*deltainf-nbranchinf+nsing;
2418         pause();
2419      }
2420      "singularities at (x,y,1):";"";
2421   }
2422   execute("ring newR=("+charstr(R)+"),(x,y),dp;");
2423   //the singularities at the affine part
2424   map sigma=S,var(1),var(2),1;
2425   ideal I=sigma(F);
2426
2427   if(size(#)!=0)
2428   {                              //uses the normalization to compute delta
2429      list nor=normal(I);
2430      delt=nor[size(nor)][2];
2431      genus=genus-delt-deltainf;
2432      setring R0;
2433      return(genus);
2434   }
2435
2436   ideal I1=jacob(I);
2437   matrix Hess[2][2]=jacob(I1);
2438   ideal ID=I+I1+ideal(det(Hess));//singular locus of I+I1
2439
2440   ideal radID=std(radical(ID));//the non-nodal locus
2441   if(w>=1){"the non-nodal locus:";"";radID;pause();"";}
2442   if(deg(radID[1])==0)
2443   {
2444     ideal IDsing=1;
2445   }
2446   else
2447   {
2448     ideal IDsing=minor(jacob(ID),2)+radID;//singular locus of ID
2449   }
2450
2451   iglob=vdim(std(IDsing));
2452
2453   if(iglob!=0)//computation of the radical of IDsing
2454   {
2455      ideal radIDsing=reduce(IDsing,radID);
2456      if(size(radIDsing)==0)
2457      {
2458         radIDsing=radID;
2459         attrib(radIDsing,"isSB",1);
2460      }
2461      else
2462      {
2463         radIDsing=std(radical(IDsing));
2464      }
2465      iglob=vdim(radIDsing);
2466      if((w>=1)&&(iglob))
2467          {"the non-nodal-cuspidal locus:";radIDsing;pause();"";}
2468   }
2469   cusps=vdim(radID)-iglob;
2470   nsing=nsing+cusps;
2471
2472   if(iglob==0)
2473   {
2474      if(w>=1){"             there are only cusps and nodes";"";}
2475      tau=vdim(std(I+jacob(I)));
2476      tauinf=tauinf+tau;
2477      nodes=tau-2*cusps;
2478      delt=nodes+cusps;
2479      nbranch=2*tau-3*cusps;
2480      nsing=nsing+nodes;
2481   }
2482   else
2483   {
2484       if(w>=1){"the non-nodal-cuspidal singularities";"";}
2485       setring C;
2486       ideal I1=imap(newR,IDsing);
2487       iloc=vdim(std(I1));
2488       if(iglob==iloc)
2489       {
2490          if(w>=1){"only cusps and nodes outside (0,0,1)";}
2491          setring newR;
2492          tau=vdim(std(I+jacob(I)));
2493          tauinf=tauinf+tau;
2494          inv=deltaLoc(I[1],maxideal(1));
2495          delt=inv[1];
2496          tauloc=inv[2];
2497          nodes=tau-tauloc-2*cusps;
2498          nsing=nsing+nodes;
2499          nbranch=inv[3]+ 2*nodes+cusps;
2500          delt=delt+nodes+cusps;
2501          if((w>=1)&&(inv[2]==0)){"smooth at (0,0,1)";}
2502        }
2503        else
2504        {
2505           setring newR;
2506           list pr=minAssGTZ(IDsing);
2507           if(w>=1){pr;}
2508
2509           for(k=1;k<=size(pr);k++)
2510           {
2511              if(w>=1){nsing=nsing+vdim(std(pr[k]));}
2512              inv=deltaLoc(I[1],pr[k]);
2513              delt=delt+inv[1];
2514              tausing=tausing+inv[2];
2515              nbranch=nbranch+inv[3];
2516           }
2517           tau=vdim(std(I+jacob(I)));
2518           tauinf=tauinf+tau;
2519           nodes=tau-tausing-2*cusps;
2520           nsing=nsing+nodes;
2521           delt=delt+nodes+cusps;
2522           nbranch=nbranch+2*nodes+cusps;
2523        }
2524   }
2525   genus=genus-delt-deltainf;
2526   if(w>=1)
2527   {
2528      "The projected plane curve has locally:";"";
2529      "singularities:";nsing;
2530      "branches:";nbranch+nbranchinf;
2531      "nodes:"; nodes+nodesinf;
2532      "cusps:";cusps+cuspsinf;
2533      "Tjurina number:";tauinf;
2534      "Milnor number:";2*(delt+deltainf)-nbranch-nbranchinf+nsing;
2535      "delta of the projected curve:";delt+deltainf;
2536      "delta of the curve:";p_a-genus;
2537      "genus:";genus;
2538      "====================================================";
2539      "";
2540   }
2541   setring R0;
2542   return(genus);
2543}
2544example
2545{ "EXAMPLE:"; echo = 2;
2546   ring r=0,(x,y),dp;
2547   ideal i=y^9 - x^2*(x - 1)^9;
2548   genus(i);
2549   ring r7=7,(x,y),dp;
2550   ideal i=y^9 - x^2*(x - 1)^9;
2551   genus(i);
2552}
2553
2554///////////////////////////////////////////////////////////////////////////////
2555proc deltaLoc(poly f,ideal singL)
2556"USAGE:  deltaLoc(f,J);  f poly, J ideal
2557ASSUME: f is reduced bivariate polynomial; basering has exactly two variables;
2558        J is irreducible prime component of the singular locus of f (e.g., one
2559        entry of the output of @code{minAssGTZ(I);}, I = <f,jacob(f)>).
2560RETURN:  list L:
2561@texinfo
2562@table @asis
2563@item @code{L[1]}; int:
2564         the sum of (local) delta invariants of f at the (conjugated) singular
2565         points given by J.
2566@item @code{L[2]}; int:
2567         the sum of (local) Tjurina numbers of f at the (conjugated) singular
2568         points given by J.
2569@item @code{L[3]}; int:
2570         the sum of (local) number of branches of f at the (conjugated)
2571         singular points given by J.
2572@end table
2573@end texinfo
2574NOTE:    procedure makes use of @code{execute}; increasing printlevel displays
2575         more comments (default: printlevel=0).
2576SEE ALSO: delta, tjurina
2577KEYWORDS: delta invariant; Tjurina number
2578EXAMPLE: example deltaLoc;  shows an example
2579"
2580{
2581   option(redSB);
2582   def R=basering;
2583   execute("ring S=("+charstr(R)+"),(x,y),lp;");
2584   map phi=R,x,y;
2585   ideal singL=phi(singL);
2586   singL=simplify(std(singL),1);
2587   attrib(singL,"isSB",1);
2588   int d=vdim(singL);
2589   poly f=phi(f);
2590   int i;
2591   int w = printlevel-voice+2;  // w=printlevel (default: w=0)
2592   if(d==1)
2593   {
2594      map alpha=S,var(1)-singL[2][2],var(2)-singL[1][2];
2595      f=alpha(f);
2596      execute("ring C=("+charstr(S)+"),("+varstr(S)+"),ds;");
2597      poly f=imap(S,f);
2598      ideal singL=imap(S,singL);
2599      if((w>=1)&&(ord(f)>=2))
2600      {
2601        "local analysis of the singularities";"";
2602        basering;
2603        singL;
2604        f;
2605        pause();
2606      }
2607   }
2608   else
2609   {
2610      poly p;
2611      poly c;
2612      map psi;
2613      number co;
2614
2615      while((deg(lead(singL[1]))>1)&&(deg(lead(singL[2]))>1))
2616      {
2617         psi=S,x,y+random(-100,100)*x;
2618         singL=psi(singL);
2619         singL=std(singL);
2620          f=psi(f);
2621      }
2622
2623      if(deg(lead(singL[2]))==1)
2624      {
2625         p=singL[1];
2626         c=singL[2]-lead(singL[2]);
2627         co=leadcoef(singL[2]);
2628      }
2629      if(deg(lead(singL[1]))==1)
2630      {
2631         psi=S,y,x;
2632         f=psi(f);
2633         singL=psi(singL);
2634         p=singL[2];
2635         c=singL[1]-lead(singL[1]);
2636         co=leadcoef(singL[1]);
2637      }
2638
2639      execute("ring B=("+charstr(S)+"),a,dp;");
2640      map beta=S,a,a;
2641      poly p=beta(p);
2642
2643      execute("ring C=("+charstr(S)+",a),("+varstr(S)+"),ds;");
2644      number p=number(imap(B,p));
2645
2646      minpoly=p;
2647      map iota=S,a,a;
2648      number c=number(iota(c));
2649      number co=iota(co);
2650
2651      map alpha=S,x-c/co,y+a;
2652      poly f=alpha(f);
2653      f=cleardenom(f);
2654      if((w>=1)&&(ord(f)>=2))
2655      {
2656        "local analysis of the singularities";"";
2657        basering;
2658        alpha;
2659        f;
2660        pause();
2661        "";
2662      }
2663   }
2664   option(noredSB);
2665   ideal fstd=std(ideal(f)+jacob(f));
2666   poly hc=highcorner(fstd);
2667   int tau=vdim(fstd);
2668   int o=ord(f);
2669   int delt,nb;
2670
2671   if(tau==0)                 //smooth case
2672   {
2673      setring R;
2674      return(list(0,0,1));
2675   }
2676   if((char(basering)>=181)||(char(basering)==0))
2677   {
2678      if(o==2)                //A_k-singularity
2679      {
2680        if(w>=1){"A_k-singularity";"";}
2681         setring R;
2682         delt=(tau+1)/2;
2683         return(list(d*delt,d*tau,d*(2*delt-tau+1)));
2684      }
2685      if((lead(f)==var(1)*var(2)^2)||(lead(f)==var(1)^2*var(2)))
2686      {
2687        if(w>=1){"D_k- singularity";"";}
2688
2689         setring R;
2690         delt=(tau+2)/2;
2691         return(list(d*delt,d*tau,d*(2*delt-tau+1)));
2692      }
2693
2694      int mu=vdim(std(jacob(f)));
2695      poly g=f+var(1)^mu+var(2)^mu;  //to obtain a convenient Newton-polygon
2696
2697      list NP=newtonpoly(g);
2698      if(w>=1){"Newton-Polygon:";NP;"";}
2699      int s=size(NP);
2700
2701      if(is_NND(f,mu,NP))
2702      { // the Newton-polygon is non-degenerate
2703        // compute nb, the number of branches
2704        for(i=1;i<=s-1;i++)
2705        {
2706          nb=nb+gcd(NP[i][2]-NP[i+1][2],NP[i][1]-NP[i+1][1]);
2707        }
2708        if(w>=1){"Newton-Polygon is non-degenerated";"";}
2709        return(list(d*(mu+nb-1)/2,d*tau,d*nb));
2710      }
2711
2712      if(w>=1){"Newton-Polygon is degenerated";"";}
2713
2714      // the following can certainly be made more efficient when replacing
2715      // 'hnexpansion' (used only for computing number of branches) by
2716      // successive blowing-up + test if Newton polygon degenerate:
2717      if(s>2)    //  splitting of f
2718      {
2719         if(w>=1){"Newton polygon can be used for splitting";"";}
2720         intvec v=NP[1][2]-NP[2][2],NP[2][1];
2721         int de=w_deg(g,v);
2722         int st=w_deg(hc,v)+v[1]+v[2];
2723         poly f1=var(2)^NP[2][2];
2724         poly f2=jet(g,de,v)/var(2)^NP[2][2];
2725         poly h=g-f1*f2;
2726         de=w_deg(h,v);
2727         poly k;
2728         ideal wi=var(2)^NP[2][2],f2;
2729         matrix li;
2730         while(de<st)
2731         {
2732           k=jet(h,de,v);
2733           li=lift(wi,k);
2734           f1=f1+li[2,1];
2735           f2=f2+li[1,1];
2736           h=g-f1*f2;
2737           de=w_deg(h,v);
2738         }
2739         nb=deltaLoc(f1,maxideal(1))[3]+deltaLoc(f2,maxideal(1))[3];
2740         setring R;
2741         return(list(d*(mu+nb-1)/2,d*tau,d*nb));
2742      }
2743
2744      f=jet(f,deg(hc)+2);
2745      if(w>=1){"now we have to use Hamburger-Noether (Puiseux) expansion";}
2746      ideal fac=factorize(f,1);
2747      if(size(fac)>1)
2748      {
2749         nb=0;
2750         for(i=1;i<=size(fac);i++)
2751         {
2752            nb=nb+deltaLoc(fac[i],maxideal(1))[3];
2753         }
2754         setring R;
2755         return(list(d*(mu+nb-1)/2,d*tau,d*nb));
2756      }
2757      list HNEXP=hnexpansion(f);
2758      if (typeof(HNEXP[1])=="ring") {
2759        def altring = basering;
2760        def HNEring = HNEXP[1]; setring HNEring;
2761        nb=size(hne);
2762        setring R;
2763        kill HNEring;
2764      }
2765      else
2766      {
2767        nb=size(HNEXP);
2768      }
2769      return(list(d*(mu+nb-1)/2,d*tau,d*nb));
2770   }
2771   else             //the case of small characteristic
2772   {
2773      f=jet(f,deg(hc)+2);
2774      if(w>=1){"now we have to use Hamburger-Noether (Puiseux) expansion";}
2775      delt=delta(f);
2776      return(list(d*delt,d*tau,d));
2777   }
2778}
2779example
2780{ "EXAMPLE:"; echo = 2;
2781  ring r=0,(x,y),dp;
2782  poly f=(x2+y^2-1)^3 +27x2y2;
2783  ideal I=f,jacob(f);
2784  I=std(I);
2785  list qr=minAssGTZ(I);
2786  size(qr);
2787  // each component of the singular locus either describes a cusp or a pair
2788  // of conjugated nodes:
2789  deltaLoc(f,qr[1]);
2790  deltaLoc(f,qr[2]);
2791  deltaLoc(f,qr[3]);
2792  deltaLoc(f,qr[4]);
2793  deltaLoc(f,qr[5]);
2794  deltaLoc(f,qr[6]);
2795}
2796///////////////////////////////////////////////////////////////////////////////
2797// compute the weighted degree of p
2798static proc w_deg(poly p, intvec v)
2799{
2800   if(p==0){return(-1);}
2801   int d=0;
2802   while(jet(p,d,v)==0){d++;}
2803   d=(transpose(leadexp(jet(p,d,v)))*v)[1];
2804   return(d);
2805}
2806
2807//proc hilbPoly(ideal J)
2808//{
2809//   poly hp;
2810//   int i;
2811//   if(!attrib(J,"isSB")){J=std(J);}
2812//   intvec v = hilb(J,2);
2813//   for(i=1; i<=size(v); i++){ hp=hp+v[i]*(var(1)-i+2);}
2814//   return(hp);
2815//}
2816
2817
2818//////////////////////////////////////////////////////////////////////////////
2819
2820proc primeClosure (list L, list #)
2821"USAGE:    primeClosure(L [,c]); L a list of a ring containing a prime ideal
2822          ker, c an optional integer
2823RETURN:   a list L (of size n+1) consisting of rings L[1],...,L[n] such that
2824          - L[1] is a copy of (not a reference to!) the input ring L[1]
2825          - all rings L[i] contain ideals ker, L[2],...,L[n] contain ideals phi
2826            such that
2827                    L[1]/ker --> ... --> L[n]/ker
2828            are injections given by the corresponding ideals phi, and L[n]/ker
2829            is the integral closure of L[1]/ker in its quotient field.
2830          - all rings L[i] contain a polynomial nzd such that elements of
2831            L[i]/ker are quotients of elements of L[i-1]/ker with denominator
2832            nzd via the injection phi.
2833            L[n+1] is the delta invariant
2834NOTE:     - L is constructed by recursive calls of primeClosure itself.
2835          - c determines the choice of nzd:
2836               - c not given or equal to 0: first generator of the ideal SL,
2837                 the singular locus of Spec(L[i]/ker)
2838               - c<>0: the generator of SL with least number of monomials.
2839EXAMPLE:  example primeClosure; shows an example
2840"
2841{
2842  //---- Start with a consistency check:
2843
2844  if (!(typeof(L[1])=="ring"))
2845  {
2846      "// Parameter must be a ring or a list containing a ring!";
2847      return(-1);
2848  }
2849
2850  int dblvl = printlevel-voice+2;
2851  list gnirlist = ringlist(basering);
2852
2853  //---- Some auxiliary variables:
2854  int delt;                      //finally the delta invariant
2855  if ( size(L) == 1 )
2856  {
2857      L[2] = delt;              //set delta to 0
2858  }
2859  int n = size(L)-1;            //L without delta invariant
2860
2861  //---- How to choose the non-zerodivisor later on?
2862
2863  int nzdoption=0;
2864  if (size(#)>0)
2865  {
2866      nzdoption=#[1];
2867  }
2868
2869// R0 below is the ring to work with, if we are in step one, make a copy of the
2870// input ring, so that all objects are created in the copy, not in the original
2871// ring (therefore a copy, not a reference is defined).
2872
2873  if (n==1)
2874  {
2875      def R = L[1];
2876      list Rlist = ringlist(R);
2877      def BAS = basering;
2878      setring R;
2879      if (!(typeof(ker)=="ideal"))
2880      {
2881          "// No ideal ker in the input ring!";
2882          return (-1);
2883      }
2884      ker=simplify(interred(ker),15);
2885      //execute ("ring R0="+charstr(R)+",("+varstr(R)+"),("+ordstr(R)+");");
2886      // Rlist may be not defined in this new ring, so we define it again.
2887      list Rlist2 = ringlist(R);
2888      def R0 = ring(Rlist2);
2889      setring R0;
2890      ideal ker=fetch(R,ker);
2891      // check whether we compute the normalization of the blow up of
2892      // an isolated singularity at the origin (checked in normalI)
2893
2894      if (typeof(attrib(L[1],"iso_sing_Rees"))=="int")
2895      {
2896        attrib(R0,"iso_sing_Rees",attrib(L[1],"iso_sing_Rees"));
2897      }
2898      L[1]=R0;
2899  }
2900  else
2901  {
2902      def R0 = L[n];
2903      setring R0;
2904  }
2905
2906// In order to apply HomJJ from normal.lib, we need the radical of the singular
2907// locus of ker, J:=rad(ker):
2908
2909   list SM=mstd(ker);
2910
2911// In the first iteration, we have to compute the singular locus "from
2912// scratch".
2913// In further iterations, we can fetch it from the previous one but
2914// have to compute its radical
2915// the next rings R1 contain already the (fetched) ideal
2916
2917  if (n==1)                              //we are in R0=L[1]
2918  {
2919      if (typeof(attrib(R0,"iso_sing_Rees"))=="int")
2920      {
2921        ideal J;
2922        for (int s=1;s<=attrib(R0,"iso_sing_Rees");s++)
2923        {
2924          J=J,var(s);
2925        }
2926        J = J,SM[2];
2927        list JM = mstd(J);
2928      }
2929      else
2930      {
2931        if ( dblvl >= 1 )
2932        {"";
2933           "// compute the singular locus";
2934        }
2935        //### Berechnung des singulaeren Orts geaendert (ist so schneller)
2936        ideal J = minor(jacob(SM[2]),nvars(basering)-dim(SM[1]),SM[1]);
2937        J = J,SM[2];
2938        list JM = mstd(J);
2939      }
2940
2941      if ( dblvl >= 1 )
2942      {"";
2943         "// dimension of singular locus is", dim(JM[1]);
2944         if (  dblvl >= 2 )
2945         {"";
2946            "// the singular locus is:"; JM[2];
2947         }
2948      }
2949
2950      if ( dblvl >= 1 )
2951      {"";
2952         "// compute radical of singular locus";
2953      }
2954
2955      J = simplify(radical(JM[2]),2);
2956      if ( dblvl >= 1 )
2957      {"";
2958         "// radical of singular locus is:"; J;
2959         pause();
2960      }
2961  }
2962  else
2963  {
2964      if ( dblvl >= 1 )
2965      {"";
2966         "// compute radical of test ideal in ideal of singular locus";
2967      }
2968      J = simplify(radical(J),2);
2969      if ( dblvl >= 1 )
2970      {"";
2971         "// radical of test ideal is:"; J;
2972         pause();
2973      }
2974  }
2975
2976  // having computed the radical J of/in the ideal of the singular locus,
2977  // we now need to pick an element nzd of J;
2978  // NOTE: nzd must be a non-zero divisor mod ker, i.e. not contained in ker
2979
2980  poly nzd = J[1];
2981  poly nzd1 = NF(nzd,SM[1]);
2982  if (nzd1 != 0)
2983  {
2984     if ( deg(nzd)>=deg(nzd1) && size(nzd)>size(nzd1) )
2985     {
2986        nzd = nzd1;
2987     }
2988  }
2989
2990  if (nzdoption || nzd1==0)
2991  {
2992    for (int ii=2;ii<=ncols(J);ii++)
2993    {
2994      nzd1 = NF(J[ii],SM[1]);
2995      if ( nzd1 != 0 )
2996      {
2997        if ( (deg(nzd)>=deg(J[ii])) && (size(nzd)>size(J[ii])) )
2998        {
2999          nzd=J[ii];
3000        }
3001        if ( deg(nzd)>=deg(nzd1) && size(nzd)>size(nzd1) )
3002        {
3003          nzd = nzd1;
3004        }
3005      }
3006    }
3007  }
3008
3009  export nzd;
3010  // In this case we do not eliminate variables, so that the maps
3011  // are well defined.
3012  list RR = SM[1],SM[2],J,nzd,1;
3013
3014  if ( dblvl >= 1 )
3015  {"";
3016     "// compute the first ring extension:";
3017     "RR: ";
3018     RR;
3019  }
3020
3021  list RS = HomJJ(RR);
3022  //NOTE: HomJJ creates new ring with variables X(i) and T(j)
3023//-------------------------------------------------------------------------
3024// If we've reached the integral closure (as determined by the result of
3025// HomJJ), then we are done, otherwise we have to prepare the next iteration.
3026
3027  if (RS[2]==1)     // we've reached the integral closure, we are still in R0
3028    {
3029      kill J;
3030      if ( n== 1)
3031      {
3032        def R1 = RS[1];
3033        setring R1;
3034        ideal norid, normap = endid, endphi;
3035        kill endid,  endphi;
3036
3037        //"//### case: primeClosure, final";
3038        //"size norid:", size(norid), size(string(norid));
3039        //"interred:";
3040        //norid = interred(norid);
3041        //"size norid:", size(norid), size(string(norid));
3042
3043        export (norid, normap);
3044        L[1] = R1;
3045      }
3046      return(L);
3047    }
3048  else                        // prepare the next iteration
3049    {
3050      if (n==1)               // In the first iteration: keep only the data
3051      {                       // needed later on.
3052         kill RR,SM;
3053         export(ker);
3054      }
3055      if ( dblvl >= 1 )
3056      {"";
3057         "// computing the next ring extension, we are in loop"; n+1;
3058      }
3059
3060      def R1 = RS[1];         // The data of the next ring R1:
3061      delt = RS[3];           // the delta invariant of the ring extension
3062      setring R1;             // keep only what is necessary and kill
3063      ideal ker=endid;        // everything else.
3064      export(ker);
3065      ideal norid=endid;
3066
3067      //"//### case: primeClosure, loop", n+1;
3068      //"size norid:", size(norid), size(string(norid));
3069      //"interred:";
3070      //norid = interred(norid);        //????
3071      //"size norid:", size(norid), size(string(norid));
3072
3073      export(norid);
3074      kill endid;
3075
3076      map phi = R0,endphi;                        // fetch the singular locus
3077      ideal J = mstd(simplify(phi(J)+ker,4))[2];  // ideal J in R1
3078      export(J);
3079      if(n>1)
3080      {
3081         ideal normap=phi(normap);
3082      }
3083      else
3084      {
3085         ideal normap=endphi;
3086      }
3087      export(normap);
3088      kill phi;              // we save phi as ideal, not as map, so that
3089      ideal phi=endphi;      // we have more flexibility in the ring names
3090      kill endphi;           // later on.
3091      export(phi);
3092      L=insert(L,R1,n);       // Add the new ring R1 and go on with the
3093                              // next iteration
3094      if ( L[size(L)] >= 0 && delt >= 0 )
3095      {
3096         delt = L[size(L)] + delt;
3097      }
3098      else
3099      {
3100         delt = -1;
3101      }
3102      L[size(L)] = delt;
3103
3104      if (size(#)>0)
3105      {
3106          return (primeClosure(L,#));
3107      }
3108      else
3109      {
3110          return(primeClosure(L));         // next iteration.
3111      }
3112    }
3113}
3114example
3115{
3116  "EXAMPLE:"; echo=2;
3117  ring R=0,(x,y),dp;
3118  ideal I=x4,y4;
3119  def K=ReesAlgebra(I)[1];        // K contains ker such that K/ker=R[It]
3120  list L=primeClosure(K);
3121  def R(1)=L[1];                  // L[4] contains ker, L[4]/ker is the
3122  def R(4)=L[4];                  // integral closure of L[1]/ker
3123  setring R(1);
3124  R(1);
3125  ker;
3126  setring R(4);
3127  R(4);
3128  ker;
3129}
3130
3131///////////////////////////////////////////////////////////////////////////////
3132
3133proc closureFrac(list L)
3134"USAGE:    closureFrac (L); L a list of size n+1 as in the result of
3135          primeClosure, L[n] contains an additional polynomial f
3136CREATE:   a list fraction of two elements of L[1], such that
3137          f=fraction[1]/fraction[2] via the injections phi L[i]-->L[i+1].
3138EXAMPLE:  example closureFrac; shows an example
3139"
3140{
3141// Define some auxiliary variables:
3142
3143  int n=size(L)-1;
3144  int i,j,k,l,n2,n3;
3145  intvec V;
3146  string mapstr;
3147  for (i=1; i<=n; i++) { def R(i) = L[i]; }
3148
3149// The quotient representing f is computed as in 'closureGenerators' with
3150// the differences that
3151//   - the loop is done twice: for the numerator and for the denominator;
3152//   - the result is stored in the list fraction and
3153//   - we have to make sure that no more objects of the rings R(i) survive.
3154
3155  for (j=1; j<=2; j++)
3156    {
3157      setring R(n);
3158      if (j==1)
3159      {
3160         poly p=f;
3161      }
3162      else
3163      {
3164         p=1;
3165      }
3166
3167      for (k=n; k>1; k--)
3168      {
3169          if (j==1)
3170          {
3171             map phimap=R(k-1),phi;
3172          }
3173
3174          p=p*phimap(nzd);
3175
3176          if (j==2)
3177          {
3178            kill phimap;
3179          }
3180
3181          if (j==1)
3182          {
3183             //### noch abfragen ob Z(i) definiert ist
3184             list gnirlist = ringlist(R(k));
3185             n2 = size(gnirlist[2]);
3186             n3 = size(gnirlist[3]);
3187             for( i=1; i<=ncols(phi); i++)
3188             {
3189               gnirlist[2][n2+i] = "Z("+string(i)+")";
3190             }
3191             V=0;
3192             V[ncols(phi)]=0; V=V+1;
3193             gnirlist[3] = insert(gnirlist[3],list("dp",V),n3-1);
3194             def S(k) = ring(gnirlist);
3195             setring S(k);
3196
3197             //execute ("ring S(k) = "+charstr(R(k))+",("+varstr(R(k))+",
3198             //          Z(1.."+string(ncols(phi))+")),(dp("+string(nvars(R(k)))
3199             //          +"),dp("+string(ncols(phi))+"));");
3200
3201              ideal phi = imap(R(k),phi);
3202              ideal J = imap (R(k),ker);
3203              for (l=1;l<=ncols(phi);l++)
3204              {
3205                  J=J+(Z(l)-phi[l]);
3206              }
3207              J=groebner(J);
3208              poly h=NF(imap(R(k),p),J);
3209          }
3210          else
3211          {
3212              setring S(k);
3213              h=NF(imap(R(k),p),J);
3214              setring R(k);
3215              kill p;
3216          }
3217
3218          setring R(k-1);
3219
3220          if (j==1)
3221          {
3222              ideal maxi;
3223              maxi[nvars(R(k))] = 0;
3224              maxi = maxi,maxideal(1);
3225              map backmap = S(k),maxi;
3226
3227              //mapstr=" map backmap = S(k),";
3228              //for (l=1;l<=nvars(R(k));l++)
3229              //{
3230              //  mapstr=mapstr+"0,";
3231              //}
3232              //execute (mapstr+"maxideal(1);");
3233              poly p;
3234          }
3235          p=NF(backmap(h),std(ker));
3236          if (j==2)
3237          {
3238            kill backmap;
3239          }
3240        }
3241
3242      if (j==1)
3243        {
3244          if (defined(fraction))
3245            {
3246              kill fraction;
3247              list fraction=p;
3248            }
3249          else
3250            {
3251              list fraction=p;
3252            }
3253        }
3254      else
3255        {
3256          fraction=insert(fraction,p,1);
3257        }
3258    }
3259  export(fraction);
3260  return ();
3261}
3262example
3263{
3264  "EXAMPLE:"; echo=2;
3265  ring R=0,(x,y),dp;
3266  ideal ker=x2+y2;
3267  export ker;
3268  list L=primeClosure(R);          // We normalize R/ker
3269  for (int i=1;i<=size(L);i++) { def R(i)=L[i]; }
3270  setring R(2);
3271  kill R;
3272  phi;                             // The map R(1)-->R(2)
3273  poly f=T(2);                     // We will get a representation of f
3274  export f;
3275  L[2]=R(2);
3276  closureFrac(L);
3277  setring R(1);
3278  kill R(2);
3279  fraction;                        // f=fraction[1]/fraction[2] via phi
3280  kill R(1);
3281}
3282
3283///////////////////////////////////////////////////////////////////////////////
3284// closureGenerators is called inside proc normal (option "withGens" )
3285//
3286
3287// INPUT is the output of proc primeClosure (except for the last element, the
3288// delta invariant) : hence input is a list L consisting of rings
3289// L[1],...,L[n] (denoted R(1)...R(n) below) such that
3290// - L[1] is a copy of (not a reference to!) the input ring L[1]
3291// - all rings L[i] contain ideals ker, L[2],...,L[n] contain ideals phi
3292// such that
3293//                L[1]/ker --> ... --> L[n]/ker
3294// are injections given by the corresponding ideals phi, and L[n]/ker
3295// is the integral closure of L[1]/ker in its quotient field.
3296// - all rings L[i] contain a polynomial nzd such that elements of
3297// L[i]/ker are quotients of elements of L[i-1]/ker with denominator
3298// nzd via the injection phi.
3299
3300// COMPUTE: In the list L of rings R(1),...,R(n), compute representations of
3301// the ring variables of the last ring R(n) as fractions of elements of R(1):
3302// The proc returns an ideal preim s.t. preim[i]/preim[size(preim)] expresses
3303// the ith variable of R(n) as fraction of elements of the basering R(1)
3304// preim[size(preim)] is a non-zero divisor of basering/i.
3305
3306proc closureGenerators(list L);
3307{
3308  def Rees=basering;         // when called inside normalI (in reesclos.lib)
3309                             // the Rees Algebra is the current basering
3310
3311  // ------- First of all we need some variable declarations -----------
3312  int n = size(L);                // the number of rings R(1)-->...-->R(n)
3313  int length = nvars(L[n]);       // the number of variables of the last ring
3314  int j,k,l,n2,n3;
3315  intvec V;
3316  string mapstr;
3317  list preimages;
3318  //Note: the empty list belongs to no ring, hence preimages can be used
3319  //later in R(1)
3320  //this is not possible for ideals (belong always to some ring)
3321
3322  for (int i=1; i<=n; i++)
3323  {
3324     def R(i)=L[i];          //give the rings from L a name
3325  }
3326
3327  // For each variable (counter j) and for each intermediate ring (counter k):
3328  // Find a preimage of var_j*phi(nzd(k-1)) in R(k-1).
3329  // Finally, do the same for nzd.
3330
3331  for (j=1; j <= length+1; j++ )
3332  {
3333      setring R(n);
3334      if (j==1)
3335      {
3336        poly p;
3337      }
3338      if (j <= length )
3339      {
3340        p=var(j);
3341      }
3342      else
3343      {
3344        p=1;
3345      }
3346      //i.e. p=j-th var of R(n) for j<=length and p=1 for j=length+1
3347
3348      for (k=n; k>1; k--)
3349      {
3350
3351        if (j==1)
3352        {
3353          map phimap=R(k-1),phi;   //phimap:R(k-1)-->R(n), k=2..n, is the map
3354                                   //belonging to phi in R(n)
3355        }
3356
3357        p = p*phimap(nzd);
3358
3359          // Compute the preimage of [p mod ker(k)] under phi in R(k-1):
3360          // As p is an element of Image(phi), there is a polynomial h such
3361          // that h is mapped to [p mod ker(k)], and h can be computed as the
3362          // normal form of p w.r.t. a Groebner basis of
3363          // J(k) := <ker(k),Z(l)-phi(k)(l)> in R(k)[Z]=:S(k)
3364
3365        if (j==1)   // In the first iteration: Create S(k), fetch phi and
3366                    // ker(k) and construct the ideal J(k).
3367        {
3368         //### noch abfragen ob Z(i) definiert ist
3369         list gnirlist = ringlist(R(k));
3370         n2 = size(gnirlist[2]);
3371         n3 = size(gnirlist[3]);
3372         for( i=1; i<=ncols(phi); i++)
3373         {
3374            gnirlist[2][n2+i] = "Z("+string(i)+")";
3375         }
3376         V=0;
3377         V[ncols(phi)]=0;
3378         V=V+1;
3379         gnirlist[3] = insert(gnirlist[3],list("dp",V),n3-1);
3380         def S(k) = ring(gnirlist);
3381         setring S(k);
3382
3383        // execute ("ring S(k) = "+charstr(R(k))+",("+varstr(R(k))+",
3384        //           Z(1.."+string(ncols(phi))+")),(dp("+string(nvars(R(k)))
3385        //           +"),dp("+string(ncols(phi))+"));");
3386
3387          ideal phi = imap(R(k),phi);
3388          ideal J = imap (R(k),ker);
3389          for ( l=1; l<=ncols(phi); l++ )
3390          {
3391             J=J+(Z(l)-phi[l]);
3392          }
3393          J = groebner(J);
3394          poly h = NF(imap(R(k),p),J);
3395        }
3396        else
3397        {
3398           setring S(k);
3399           h = NF(imap(R(k),p),J);
3400        }
3401
3402        setring R(k-1);
3403
3404        if (j==1)  // In the first iteration: Compute backmap:S(k)-->R(k-1)
3405        {
3406           ideal maxi;
3407           maxi[nvars(R(k))] = 0;
3408           maxi = maxi,maxideal(1);
3409           map backmap = S(k),maxi;
3410
3411           //mapstr=" map backmap = S(k),";
3412           //for (l=1;l<=nvars(R(k));l++)
3413           //{
3414           //  mapstr=mapstr+"0,";
3415           //}
3416           //execute (mapstr+"maxideal(1);");
3417
3418           poly p;
3419        }
3420        p = NF(backmap(h),std(ker));
3421     }
3422     // Whe are down to R(1), store here the result in the list preimages
3423     preimages = insert(preimages,p,j-1);
3424  }
3425  ideal preim;                  //make the list preimages to an ideal preim
3426  for ( i=1; i<=size(preimages); i++ )
3427  {
3428     preim[i] = preimages[i];
3429  }
3430  // R(1) was a copy of Rees, so we have to get back to the basering Rees from
3431  // the beginning and fetch the result (the ideal preim) to this ring.
3432  setring Rees;
3433  return (fetch(R(1),preim));
3434}
3435
3436///////////////////////////////////////////////////////////////////////////////
3437//                From here: procedures for char p with Frobenius
3438///////////////////////////////////////////////////////////////////////////////
3439
3440proc normalP(ideal id,list #)
3441"USAGE:  normalP(id [,choose]); id = radical ideal, choose = optional list of
3442         strings.
3443         Optional parameters in list choose (can be entered in any order):@*
3444         \"withRing\", \"isPrim\", \"noFac\", \"noRed\", where@*
3445         - \"noFac\" -> factorization is avoided during the computation
3446         of the minimal associated primes.@*
3447         - \"isPrim\" -> assumes that the ideal is prime. If the assumption
3448         does not hold, output might be wrong.@*
3449         - \"withRing\" -> the ring structure of the normalization is
3450         computed. The number of variables in the new ring is reduced as much
3451         as possible.@*
3452         - \"noRed\" -> when computing the ring structure, no reduction on the
3453         number of variables is done, it creates one new variable for every
3454         new module generator of the integral closure in the quotient field.@*
3455ASSUME:  The characteristic of the ground field must be positive. If the
3456         option \"isPrim\" is not set, the minimal associated primes of id
3457         are computed first and hence normalP computes the normalization of
3458         the radical of id. If option \"isPrim\" is set, the ideal must be
3459         a prime ideal otherwise the result may be wrong.
3460RETURN:  a list, say 'nor' of size 2 (resp. 3 if \"withRing\" is set).@*
3461         ** If option \"withRing\" is not set: @*
3462         Only the module structure is computed: @*
3463         * nor[1] is a list of ideals Ii, i=1..r, in the basering R where r
3464         is the number of minimal associated prime ideals P_i of the input
3465         ideal id, describing the module structure:@*
3466         If Ii is given by polynomials g_1,...,g_k in R, then c:=g_k is
3467         non-zero in the ring R/P_i and g_1/c,...,g_k/c generate the integral
3468         closure of R/P_i as R-module in the quotient field of R/P_i.@*
3469         * nor[2] shows the delta invariants: it is a list of an intvec
3470         of size r, the delta invariants of the r components, and an integer,
3471         the total delta invariant of R/id
3472         (-1 means infinite, and 0 that R/P_i resp. R/id is normal). @*
3473         ** If option \"withRing\" is set: @*
3474         The ring structure is also computed, and in this case:@*
3475         * nor[1] is a list of r rings.@*
3476         Each ring Ri = nor[1][i], i=1..r, contains two ideals with given
3477         names @code{norid} and @code{normap} such that @*
3478         - Ri/norid is the normalization of R/P_i, i.e. isomorphic as
3479           K-algebra (K the ground field) to the integral closure of R/P_i in
3480           the field of fractions of R/P_i; @*
3481         - the direct sum of the rings Ri/norid is the normalization
3482           of R/id; @*
3483         - @code{normap} gives the normalization map from R to Ri/norid.@*
3484         * nor[2] gives the module generators of the normalization of R/P_i,
3485         it is the same as nor[1] if \"withRing\" is not set.@*
3486         * nor[3] shows the delta invariants, it is the same as nor[2] if
3487         \"withRing\" is not set.
3488THEORY:  normalP uses the Leonard-Pellikaan-Singh-Swanson algorithm (using the
3489         Frobenius) cf. [A. K. Singh, I. Swanson: An algorithm for computing
3490         the integral closure, arXiv:0901.0871].
3491         The delta invariant of a reduced ring A is dim_K(normalization(A)/A).
3492         For A=K[x1,...,xn]/id we call this number also the delta invariant of
3493         id. The procedure returns the delta invariants of the components P_i
3494         and of id.
3495NOTE:    To use the i-th ring type: @code{def R=nor[1][i]; setring R;}.
3496@*       Increasing/decreasing printlevel displays more/less comments
3497         (default: printlevel = 0).
3498@*       Not implemented for local or mixed orderings or quotient rings.
3499         For local or mixed orderings use proc 'normal'.
3500@*       If the input ideal id is weighted homogeneous a weighted ordering may
3501         be used (qhweight(id); computes weights).
3502@*       Works only in characteristic p > 0; use proc normal in char 0.
3503KEYWORDS: normalization; integral closure; delta invariant.
3504SEE ALSO: normal, normalC
3505EXAMPLE: example normalP; shows an example
3506"
3507{
3508   int i,j,y, sr, del, co;
3509   intvec deli;
3510   list resu, Resu, prim, Gens, mstdid;
3511   ideal gens;
3512
3513   // Default options
3514   int wring = 0;           // The ring structure is not computed.
3515   int noRed = 0;           // No reduction is done in the ring structure
3516   int isPrim = 0;          // Ideal is not assumed to be prime
3517   int noFac = 0;           // Use facstd when computing the decomposition
3518
3519
3520   y = printlevel-voice+2;
3521
3522   if ( ord_test(basering) != 1)
3523   {
3524     "";
3525     "// Not implemented for this ordering,";
3526     "// please change to global ordering!";
3527     return(resu);
3528   }
3529   if ( char(basering) <= 0)
3530   {
3531     "";
3532     "// Algorithm works only in positive characteristic,";
3533     "// use procedure 'normal' if the characteristic is 0";
3534     return(resu);
3535   }
3536
3537//--------------------------- define the method ---------------------------
3538   string method;                //make all options one string in order to use
3539                                 //all combinations of options simultaneously
3540   for ( i=1; i<= size(#); i++ )
3541   {
3542     if ( typeof(#[i]) == "string" )
3543     {
3544       method = method + #[i];
3545     }
3546   }
3547
3548   if ( find(method,"withring") or find(method,"withRing") )
3549   {
3550     wring=1;
3551   }
3552   if ( find(method,"noRed") or find(method,"nored") )
3553   {
3554     noRed=1;
3555   }
3556   if ( find(method,"isPrim") or find(method,"isprim") )
3557   {
3558     isPrim=1;
3559   }
3560   if ( find(method,"noFac") or find(method,"nofac"))
3561   {
3562     noFac=1;
3563   }
3564
3565   kill #;
3566   list #;
3567//--------------------------- start computation ---------------------------
3568   ideal II,K1,K2;
3569
3570   //----------- check first (or ignore) if input id is prime -------------
3571
3572   if ( isPrim )
3573   {
3574      prim[1] = id;
3575      if( y >= 0 )
3576      { "";
3577    "// ** WARNING: result is correct if ideal is prime (not checked) **";
3578    "// disable option \"isPrim\" to decompose ideal into prime components";"";
3579      }
3580   }
3581   else
3582   {
3583      if(y>=1)
3584      {  "// compute minimal associated primes"; }
3585
3586      if( noFac )
3587      { prim = minAssGTZ(id,1); }
3588      else
3589      { prim = minAssGTZ(id); }
3590
3591      if(y>=1)
3592      {
3593         prim;"";
3594         "// number of irreducible components is", size(prim);
3595      }
3596   }
3597
3598   //----------- compute integral closure for every component -------------
3599
3600      for(i=1; i<=size(prim); i++)
3601      {
3602         if(y>=1)
3603         {
3604            ""; pause(); "";
3605            "// start computation of component",i;
3606            "   --------------------------------";
3607         }
3608         if(y>=1)
3609         {  "// compute SB of ideal";
3610         }
3611         mstdid = mstd(prim[i]);
3612         if(y>=1)
3613         {  "// dimension of component is", dim(mstdid[1]);"";}
3614
3615      //------- 1-st main subprocedure: compute module generators ----------
3616         printlevel = printlevel+1;
3617         II = normalityTest(mstdid);
3618
3619      //------ compute also the ringstructure if "withRing" is given -------
3620         if ( wring )
3621         {
3622         //------ 2-nd main subprocedure: compute ring structure -----------
3623           if(noRed == 0){
3624             resu = list(computeRing(II,prim[i])) + resu;
3625           }
3626           else
3627           {
3628             resu = list(computeRing(II,prim[i], "noRed")) + resu;
3629           }
3630         }
3631         printlevel = printlevel-1;
3632
3633      //----- rearrange module generators s.t. denominator comes last ------
3634         gens=0;
3635         for( j=2; j<=size(II); j++ )
3636         {
3637            gens[j-1]=II[j];
3638         }
3639         gens[size(gens)+1]=II[1];
3640         Gens = list(gens) + Gens;
3641      //------------------------------ compute delta -----------------------
3642         K1 = mstdid[1]+II;
3643         K1 = std(K1);
3644         K2 = mstdid[1]+II[1];
3645         K2 = std(K2);
3646         // K1 = std(mstdid[1],II);      //### besser
3647         // K2 = std(mstdid[1],II[1]);   //### besser: Hannes, fixen!
3648         co = codim(K1,K2);
3649         deli = co,deli;
3650         if ( co >= 0 && del >= 0 )
3651         {
3652            del = del + co;
3653         }
3654         else
3655         { del = -1; }
3656      }
3657
3658      if ( del >= 0 )
3659      {
3660         int mul = iMult(prim);
3661         del = del + mul;
3662      }
3663      else
3664      { del = -1; }
3665
3666      deli = deli[1..size(deli)-1];
3667      if ( wring )
3668      { Resu = resu,Gens,list(deli,del); }
3669      else
3670      { Resu = Gens,list(deli,del); }
3671
3672   sr = size(prim);
3673
3674//-------------------- Finally print comments and return --------------------
3675   if(y >= 0)
3676   {"";
3677     if ( wring )
3678     {
3679"// 'normalP' created a list, say nor, of three lists:
3680// To see the result, type
3681     nor;
3682
3683// * nor[1] is a list of",sr,"ring(s):
3684// To access the i-th ring nor[1][i] give it a name, say Ri, and type e.g.
3685     def R1 = nor[1][1]; setring R1;  norid; normap;
3686// for the other rings type first setring R; (if R is the name of your
3687// original basering) and then continue as for R1;
3688// Ri/norid is the affine algebra of the normalization of the i-th
3689// component R/P_i (where P_i is a min. associated prime of the input ideal)
3690// and normap the normalization map from R to Ri/norid;
3691
3692// * nor[2] is a list of",sr,"ideal(s), each ideal nor[2][i] consists of
3693// elements g1..gk of r such that the gj/gk generate the integral
3694// closure of R/P_i as R-module in the quotient field of R/P_i.
3695
3696// * nor[3] shows the delta-invariant of each component and of the input
3697// ideal (-1 means infinite, and 0 that r/P_i is normal).";
3698     }
3699     else
3700     {
3701"// 'normalP' computed a list, say nor, of two lists:
3702// To see the result, type
3703     nor;
3704
3705// * nor[1] is a list of",sr,"ideal(s), where each ideal nor[1][i] consists
3706// of elements g1..gk of the basering R such that gj/gk generate the integral
3707// closure of R/P_i (where P_i is a min. associated prime of the input ideal)
3708// as R-module in the quotient field of R/P_i;
3709
3710// * nor[2] shows the delta-invariant of each component and of the input ideal
3711// (-1 means infinite, and 0 that R/P_i is normal).";
3712     }
3713   }
3714
3715   return(Resu);
3716}
3717example
3718{ "EXAMPLE:"; echo = 2;
3719   ring r  = 11,(x,y,z),wp(2,1,2);
3720   ideal i = x*(z3 - xy4 + x2);
3721   list nor= normalP(i); nor;
3722   //the result says that both components of i are normal, but i itself
3723   //has infinite delta
3724   pause("hit return to continue");
3725
3726   ring s = 2,(x,y),dp;
3727   ideal i = y*((x-y^2)^2 - x^3);
3728   list nor = normalP(i,"withRing"); nor;
3729
3730   def R2  = nor[1][2]; setring R2;
3731   norid; normap;
3732}
3733
3734///////////////////////////////////////////////////////////////////////////////
3735// Assume: mstdid is the result of mstd(prim[i]), prim[i] a prime component of
3736// the input ideal id of normalP.
3737// Output is an ideal U s.t. U[i]/U[1] are module generators.
3738
3739static proc normalityTest(list mstdid)
3740{
3741   int y = printlevel-voice+2;
3742   intvec op = option(get);
3743   option(redSB);
3744   def R = basering;
3745   int n, p = nvars(R), char(R);
3746   int ii;
3747
3748   ideal J = mstdid[1];         //J is the SB of I
3749   ideal I = mstdid[2];
3750   int h = n-dim(J);            //codimension of V(I), I is a prime ideal
3751
3752   //-------------------------- compute singular locus ----------------------
3753   qring Q = J;                 //pass to quotient ring
3754   ideal I = imap(R,I);
3755   ideal J = imap(R,J);
3756   attrib(J,"isSB",1);
3757   if ( y >= 1)
3758   { "start normality test";  "compute singular locus";}
3759
3760   ideal M = minor(jacob(I),h,J); //use the command minor modulo J (hence J=0)
3761   M = std(M);                    //this makes M much smaller
3762   //keep only minors which are not 0 mod I (!) this is important since we
3763   //need a nzd mod I
3764
3765   //---------------- choose nzd from ideal of singular locus --------------
3766   ideal D = M[1];
3767   for( ii=2; ii<=size(M); ii++ )            //look for the shortest one
3768   {
3769      if( size(M[ii]) < size(D[1]) )
3770      {
3771          D = M[ii];
3772      }
3773   }
3774
3775   //--------------- start p-th power algorithm and return ----------------
3776   ideal F = var(1)^p;
3777   for(ii=2; ii<=n; ii++)
3778   {
3779      F=F,var(ii)^p;
3780   }
3781
3782   ideal Dp=D^(p-1);
3783   ideal U=1;
3784   ideal K,L;
3785   map phi=Q,F;
3786   if ( y >= 1)
3787   {  "compute module generators of integral closure";
3788      "denominator D is:";  D;
3789      pause();
3790   }
3791
3792   ii=0;
3793   list LK;
3794   while(1)
3795   {
3796      ii=ii+1;
3797      if ( y >= 1)
3798      { "iteration", ii; }
3799      L = U*Dp + I;
3800      //### L=interred(L) oder mstd(L)[2]?
3801      //Wird dadurch kleiner aber string(L) wird groesser
3802      K = preimage(Q,phi,L);    //### Improvement by block ordering?
3803      option(returnSB);
3804      K = intersect(U,K);          //K is the new U, it is a SB
3805      LK = mstd(K);
3806      K = LK[2];
3807
3808   //---------------------------- simplify output --------------------------
3809      if(size(reduce(U,LK[1]))==0)  //previous U coincides with new U
3810      {                             //i.e. we reached the integral closure
3811         U=simplify(reduce(U,groebner(D)),2);
3812         U = D,U;
3813         poly gg = gcd(U[1],U[size(U)]);
3814         for(ii=2; ii<=size(U)-1 ;ii++)
3815         {
3816            gg = gcd(gg,U[ii]);
3817         }
3818         for(ii=1; ii<=size(U); ii++)
3819         {
3820            U[ii]=U[ii]/gg;
3821         }
3822         U = simplify(U,6);
3823         //if ( y >= 1)
3824         //{ "module generators are U[i]/U[1], with U:"; U;
3825         //  ""; pause(); }
3826         option(set,op);
3827         setring R;
3828         ideal U = imap(Q,U);
3829         return(U);
3830      }
3831      U=K;
3832   }
3833}
3834
3835///////////////////////////////////////////////////////////////////////////////
3836
3837static proc substpartSpecial(ideal endid, ideal endphi)
3838{
3839   //Note: newRing is of the form (R the original basering):
3840   //char(R),(T(1..N),X(1..nvars(R))),(dp(N),...);
3841
3842   int ii,jj,kk;
3843   def BAS = basering;
3844   int n = nvars(basering);
3845
3846   list Le = elimpart(endid);
3847   int q = size(Le[2]);                   //q variables have been substituted
3848//Le;"";
3849   if ( q == 0 )
3850   {
3851      ideal normap = endphi;
3852      ideal norid = endid;
3853      export(norid);
3854      export(normap);
3855      list L = BAS;
3856      return(L);
3857   }
3858
3859      list gnirlist = ringlist(basering);
3860      endid = Le[1];
3861//endphi;"";
3862      for( ii=1; ii<=n; ii++)
3863      {
3864         if( Le[4][ii] == 0 )            //ii=index of substituted var
3865         {
3866            endphi = subst(endphi,var(ii),Le[5][ii]);
3867         }
3868      }
3869//endphi;"";
3870      list g2 = gnirlist[2];             //the varlist
3871      list g3 = gnirlist[3];             //contains blocks of orderings
3872      int n3 = size(g3);
3873
3874   //----------------- first identify module ordering ------------------
3875      if ( g3[n3][1]== "c" or g3[n3][1] == "C" )
3876      {
3877         list gm = g3[n3];              //last blockis module ordering
3878         g3 = delete(g3,n3);
3879         int m = 0;
3880      }
3881      else
3882      {
3883         list gm = g3[1];              //first block is module ordering
3884         g3 = delete(g3,1);
3885         int m = 1;
3886      }
3887   //---- delete variables which were substituted and weights  --------
3888      intvec V;
3889      int n(0);
3890      list newg2;
3891      list newg3;
3892      for ( ii=1; ii<=n3-1; ii++ )
3893      {
3894        // If order is a matrix ordering, it is replaced by dp ordering.
3895        // TODO: replace it only when some of the original
3896        //       variables are eliminated.
3897        if(g3[ii][1] == "M"){
3898          g3[ii][1] = "dp";
3899          g3[ii][2] = (1..sqroot(size(g3[ii][2])))*0+1;
3900        }
3901        V = V,g3[ii][2];           //copy weights for ordering in each block
3902        if ( ii==1 )               //into one intvector
3903        {
3904           V = V[2..size(V)];
3905        }
3906        // int n(ii) = size(g3[ii][2]);
3907        int n(ii) = size(V);
3908        intvec V(ii);
3909
3910        for ( jj = n(ii-1)+1; jj<=n(ii); jj++)
3911        {
3912          if( Le[4][jj] !=0 )     //jj=index of var which was not substituted
3913          {
3914            kk=kk+1;
3915            newg2[kk] = g2[jj];   //not substituted var from varlist
3916            V(ii)=V(ii),V[jj];    //weight of not substituted variable
3917          }
3918        }
3919        if ( size(V(ii)) >= 2 )
3920        {
3921           V(ii) = V(ii)[2..size(V(ii))];
3922           list g3(ii)=g3[ii][1],V(ii);
3923           newg3 = insert(newg3,g3(ii),size(newg3));
3924//"newg3"; newg3;
3925        }
3926      }
3927//"newg3"; newg3;
3928      //newg3 = delete(newg3,1);    //delete empty list
3929
3930/*
3931//### neue Ordnung, 1 Block fuer alle vars, aber Gewichte erhalten;
3932//vorerst nicht realisiert, da bei leonhard1 alte Version (neue Variable T(i)
3933//ein neuer Block) ein kuerzeres Ergebnis liefert
3934      kill g3;
3935      list g3;
3936      V=0;
3937      for ( ii= 1; ii<=n3-1; ii++ )
3938      {
3939        V=V,V(ii);
3940      }
3941      V = V[2..size(V)];
3942
3943      if ( V==1 )
3944      {
3945         g3[1] = list("dp",V);
3946      }
3947      else
3948      {
3949         g3[1] = lis("wp",V);
3950      }
3951      newg3 = g3;
3952
3953//"newg3";newg3;"";
3954//### Ende neue Ordnung
3955*/
3956
3957      if ( m == 0 )
3958      {
3959         newg3 = insert(newg3,gm,size(newg3));
3960      }
3961      else
3962      {
3963         newg3 = insert(newg3,gm);
3964      }
3965      gnirlist[2] = newg2;
3966      gnirlist[3] = newg3;
3967
3968//gnirlist;
3969      def newBAS = ring(gnirlist);            //change of ring to less vars
3970      setring newBAS;
3971      ideal normap = imap(BAS,endphi);
3972      //normap = simplify(normap,2);
3973      ideal norid =  imap(BAS,endid);
3974      export(norid);
3975      export(normap);
3976      list L = newBAS;
3977      return(L);
3978
3979   //Hier scheint interred gut zu sein, da es Ergebnis relativ schnell
3980   //verkleinert. Hier wird z.B. bei leonard1 size(norid) verkleinert aber
3981   //size(string(norid)) stark vergroessert, aber es hat keine Auswirkungen
3982   //da keine map mehr folgt.
3983   //### Bei Leonard2 haengt interred (BUG)
3984   //mstd[2] verkleinert norid nocheinmal um die Haelfte, dauert aber 3.71 sec
3985   //### Ev. Hinweis auf mstd in der Hilfe?
3986
3987}
3988
3989///////////////////////////////////////////////////////////////////////////////
3990// Computes the ring structure of a ring given by module generators.
3991// Assume: J[i]/J[1] are the module generators in the quotient field
3992// with J[1] as universal denominator.
3993// If option "noRed" is not given, a reduction in the number of variables is
3994// attempted.
3995static proc computeRing(ideal J, ideal I, list #)
3996{
3997  int i, ii,jj;
3998  intvec V;                          // to be used for variable weights
3999  int y = printlevel-voice+2;
4000  def R = basering;
4001  poly c = J[1];                     // the denominator
4002  list gnirlist = ringlist(basering);
4003  string svars = varstr(basering);
4004  int nva = nvars(basering);
4005  string svar;
4006  ideal maxid = maxideal(1);
4007
4008  int noRed = 0;     // By default, we try to reduce the number of generators.
4009  if(size(#) > 0){
4010    if ( typeof(#[1]) == "string" )
4011    {
4012      if (#[1] == "noRed"){noRed = 1;}
4013    }
4014  }
4015
4016  if ( y >= 1){"// computing the ring structure...";}
4017
4018  if(c==1)
4019  {
4020/*    if( defined(norid) )  { kill norid; }
4021      if( defined(normap) ) { kill normap; }
4022      ideal norid = I;
4023      ideal normap =  maxid;  */
4024
4025    list gnirlist = ringlist(R);
4026    def R1 = ring(gnirlist);
4027    setring R1;
4028    ideal norid = imap(R, I);
4029    ideal normap = imap(R, maxid);
4030    export norid;
4031    export normap;
4032
4033    if(noRed == 1){
4034      setring R;
4035      return(R1);
4036    }
4037    else
4038    {
4039      list L = substpartSpecial(norid,normap);
4040      def lastRing = L[1];
4041      setring R;
4042      return(lastRing);
4043    }
4044  }
4045
4046
4047  //-------------- Enlarge ring by creating new variables ------------------
4048  //check first whether variables T(i) and then whether Z(i),...,A(i) exist
4049  //old variable names are not touched
4050
4051  if ( find(svars,"T(") == 0 )
4052  {
4053    svar = "T";
4054  }
4055  else
4056  {
4057    for (ii=90; ii>=65; ii--)
4058    {
4059      if ( find(svars,ASCII(ii)+"(") == 0 )
4060      {
4061        svar = ASCII(ii);  break;
4062      }
4063    }
4064  }
4065
4066  int q = size(J)-1;
4067  if ( size(svar) != 0 )
4068  {
4069    for ( ii=q; ii>=1; ii-- )
4070    {
4071      gnirlist[2] = insert(gnirlist[2],svar+"("+string(ii)+")");
4072    }
4073  }
4074  else
4075  {
4076    for ( ii=q; ii>=1; ii-- )
4077    {
4078      gnirlist[2] = insert(gnirlist[2],"T("+string(100*nva+ii)+")");
4079    }
4080  }
4081
4082  V[q]=0;                        //create intvec of variable weights
4083  V=V+1;
4084  gnirlist[3] = insert(gnirlist[3],list("dp",V));
4085
4086  //this is a block ordering with one dp-block (1st block) for new vars
4087  //the remaining weights and blocks for old vars are kept
4088  //### perhaps better to make only one block, keeping weights ?
4089  //this might effect syz below
4090  //alt: ring newR = char(R),(X(1..nvars(R)),T(1..q)),dp;
4091  //Reihenfolge geaendert:neue Variablen kommen zuerst, Namen ev. nicht T(i)
4092
4093  def newR = ring(gnirlist);
4094  setring newR;                //new extended ring
4095  ideal I = imap(R,I);
4096
4097  //------------- Compute linear and quadratic relations ---------------
4098  if(y>=1)
4099  {
4100     "// compute linear relations:";
4101  }
4102  qring newQ = std(I);
4103
4104  ideal f = imap(R,J);
4105  module syzf = syz(f);
4106  ideal pf = f[1]*f;
4107  //f[1] is the denominator D from normalityTest, a non zero divisor of R/I
4108
4109  ideal newT = maxideal(1);
4110  newT = 1,newT[1..q];
4111  //matrix T = matrix(ideal(1,T(1..q)),1,q+1);   //alt
4112  matrix T = matrix(newT,1,q+1);
4113  ideal Lin = ideal(T*syzf);
4114  //Lin=interred(Lin);
4115  //### interred reduziert ev size aber size(string(LIN)) wird groesser
4116
4117  if(y>=1)
4118  {
4119    if(y>=3)
4120    {
4121      "//   the linear relations:";  Lin; pause();"";
4122    }
4123      "// the ring structure of the normalization as affine algebra";
4124      "//   number of linear relations:", size(Lin);
4125  }
4126
4127  if(y>=1)
4128  {
4129    "// compute quadratic relations:";
4130  }
4131  matrix A;
4132  ideal Quad;
4133  poly ff;
4134  newT = newT[2..size(newT)];
4135  matrix u;  // The units for non-global orderings.
4136
4137  // Quadratic relations
4138  for (ii=2; ii<=q+1; ii++ )
4139  {
4140    for ( jj=2; jj<=ii; jj++ )
4141    {
4142      ff = NF(f[ii]*f[jj],std(0));     // this makes lift much faster
4143      // For non-global orderings, we have to take care of the units.
4144      if(ord_test(basering) != 1){
4145        A = lift(pf, ff, u);
4146        Quad = Quad,ideal(newT[jj-1]*newT[ii-1] * u[1, 1]- T*A);
4147      }
4148      else
4149      {
4150        A = lift(pf,ff);              // ff lin. comb. of elts of pf mod I
4151        Quad = Quad,ideal(newT[jj-1]*newT[ii-1] - T*A);
4152      }
4153      //A = lift(pf, f[ii]*f[jj]);
4154      //Quad = Quad, ideal(T(jj-1)*T(ii-1) - T*A);
4155    }
4156  }
4157  Quad = Quad[2..ncols(Quad)];
4158
4159  if(y>=1)
4160  {
4161    if(y>=3)
4162    {
4163      "//   the quadratic relations"; Quad; pause();"";
4164    }
4165      "//   number of quadratic relations:", size(Quad);
4166  }
4167  ideal Q1 = Lin,Quad;     //elements of Q1 are in NF w.r.t. I
4168
4169  //Q1 = mstd(Q1)[2];
4170  //### weglassen, ist sehr zeitaufwendig.
4171  //Ebenso interred, z.B. bei Leonard1 (1. Komponente von Leonard):
4172  //"size Q1:", size(Q1), size(string(Q1));   //75 60083
4173  //Q1 = interred(Q1);
4174  //"size Q1:", size(Q1), size(string(Q1));   //73 231956 (!)
4175  //### Speicherueberlauf bei substpartSpecial bei 'ideal norid  = phi1(endid)'
4176  //Beispiel fuer Hans um map zu testen!
4177
4178  setring newR;
4179  ideal endid  = imap(newQ,Q1),I;
4180  ideal endphi = imap(R,maxid);
4181
4182  if(noRed == 0){
4183    list L=substpartSpecial(endid,endphi);
4184    def lastRing=L[1];
4185    if(y>=1)
4186    {
4187      "//   number of substituted variables:", nvars(newR)-nvars(lastRing);
4188      pause();"";
4189    }
4190    return(lastRing);
4191  }
4192  else
4193  {
4194    ideal norid = endid;
4195    ideal normap = endphi;
4196    export(norid);
4197    export(normap);
4198    setring R;
4199    return(newR);
4200  }
4201}
4202
4203//                Up to here: procedures for char p with Frobenius
4204///////////////////////////////////////////////////////////////////////////////
4205
4206///////////////////////////////////////////////////////////////////////////////
4207//                From here: subprocedures for normal
4208
4209// inputJ is used in parametrization of rational curves algorithms, to specify
4210// a different test ideal.
4211
4212static proc normalM(ideal I, int decomp, int withDelta, int denomOption, ideal inputJ, ideal inputC){
4213// Computes the normalization of a ring R / I using the module structure as far
4214// as possible.
4215// The ring R is the basering.
4216// Input: ideal I
4217// Output: a list of 3 elements (resp 4 if withDelta = 1), say nor.
4218// - nor[1] = U, an ideal of R.
4219// - nor[2] = c, an element of R.
4220// U and c satisfy that 1/c * U is the normalization of R / I in the
4221// quotient field Q(R/I).
4222// - nor[3] = ring say T, containing two ideals norid and normap such that
4223// normap gives the normalization map from R / I to T / norid.
4224// - nor[4] = the delta invariant, if withDelta = 1.
4225
4226// Details:
4227// --------
4228// Computes the ideal of the minors in the first step and then reuses it in all
4229// steps.
4230// In step s, the denominator is D^s, where D is a nzd of the original quotient
4231// ring, contained in the radical of the singular locus.
4232// This denominator is used except when the degree of D^i is greater than the
4233// degree of a universal denominator.
4234// The nzd is taken as the smallest degree polynomial in the radical of the
4235// singular locus.
4236
4237// It assumes that the ideal I is equidimensional radical. This is not checked
4238// in the procedure!
4239// If decomp = 0 or decomp = 3 it assumes further that I is prime. Therefore
4240// any non-zero element in the jacobian ideal is assumed to be a
4241// non-zerodivisor.
4242
4243// It works over the given basering.
4244// If it has a non-global ordering, it changes it to dp global only for
4245// computing radical.
4246
4247// The delta invariant is only computed if withDelta = 1, and decomp = 0 or
4248// decomp = 3 (meaning that the ideal is prime).
4249
4250// denomOption = 0      -> Uses the smallest degree polynomial
4251// denomOption = i > 0  -> Uses a polynomial in the i-th variable
4252
4253  option("redSB");
4254  option("returnSB");
4255  int step = 0;                       // Number of steps. (for debugging)
4256  int dbg = printlevel - voice + 2;   // dbg = printlevel (default: dbg = 0)
4257  int i;                              // counter
4258  int isGlobal = ord_test(basering);
4259
4260  poly c;                     // The common denominator.
4261
4262  def R = basering;
4263
4264//------------------------ Groebner bases and dimension of I-----------------
4265  if(isGlobal == 1){
4266    list IM = mstd(I);
4267    I = IM[1];
4268    ideal IMin = IM[2];   // A minimal set of generators in the groebner basis.
4269  }
4270  else
4271  {
4272    // The minimal set of generators is not computed by mstd for
4273    // non-global orderings.
4274    I = groebner(I);
4275    ideal IMin = I;
4276  }
4277  int d = dim(I);
4278
4279  // ---------------- computation of the singular locus ---------------------
4280  // We compute the radical of the ideal of minors modulo the original ideal.
4281  // This is done only in the first step.
4282  qring Q = I;   // We work in the quotient by the groebner base of the ideal I
4283  option("redSB");
4284  option("returnSB");
4285
4286  // If a conductor ideal was given as input, we use it instead of the
4287  // singular locus. If a test ideal was given as input, we do not compute the
4288  // singular locus.
4289  ideal inputC = fetch(R, inputC);
4290  ideal inputJ = fetch(R, inputJ);
4291  if((inputC == 0) && (inputJ == 0)){
4292    // We compute the radical of the ideal of minors modulo the original ideal.
4293    // This is done only in the first step.
4294    ideal I = fetch(R, I);
4295    attrib(I, "isSB", 1);
4296    ideal IMin = fetch(R, IMin);
4297
4298    dbprint(dbg, "Computing the jacobian ideal...");
4299
4300    // If a given conductor ideal is given, we use it.
4301    // If a given test ideal is given, we don't need to compute the jacobian
4302    ideal J = minor(jacob(IMin), nvars(basering) - d, I);
4303    J = groebner(J);
4304  } else {
4305    ideal J = fetch(R, inputC);
4306    J = groebner(J);
4307  }
4308
4309  //------------------ We check if the singular locus is empty -------------
4310  if(J[1] == 1){
4311    // The original ring R/I was normal. Nothing to do.
4312    // We define anyway a new ring, equal to R, to be able to return it.
4313    setring R;
4314    list lR = ringlist(R);
4315    def ROut = ring(lR);
4316    setring ROut;
4317    ideal norid = fetch(R, I);
4318    ideal normap = maxideal(1);
4319    export norid;
4320    export normap;
4321    setring R;
4322    if(withDelta){
4323      list output = ideal(1), poly(1), ROut, 0;
4324    }
4325    else
4326    {
4327      list output = ideal(1), poly(1), ROut;
4328    }
4329    return(list(output));
4330  }
4331
4332
4333  // -------------------- election of the universal denominator----------------
4334  // We first check if a conductor ideal was computed. If not, we don't
4335  // compute a universal denominator.
4336  ideal Id1;
4337  if(J != 0){
4338    if(denomOption == 0){
4339      poly condu = getSmallest(J);   // Choses the polynomial of smallest degree
4340                                     // of J as universal denominator.
4341    } else {
4342      poly condu = getOneVar(J, denomOption);
4343    }
4344    if(dbg >= 1){
4345      "";
4346      "The universal denominator is ", condu;
4347    }
4348
4349    // ----- splitting the ideal by the universal denominator (if possible) -----
4350    // If the ideal is equidimensional, but not necessarily prime, we check if
4351    // the universal denominator is a non-zerodivisor of R/I.
4352    // If not, we split I.
4353    if((decomp == 1) or (decomp == 2)){
4354      Id1 = quotient(0, condu);
4355      if(size(Id1) > 0){
4356        // We have to split.
4357        if(dbg >= 1){
4358          "A zerodivisor was found. We split the ideal. The zerodivisor is ", condu;
4359        }
4360        setring R;
4361        ideal Id1 = fetch(Q, Id1), I;
4362        Id1 = groebner(Id1);
4363        ideal Id2 = quotient(I, Id1);
4364        // I = I1 \cap I2
4365        printlevel = printlevel + 1;
4366        ideal JDefault = 0;             // Now it uses the default J;
4367        list nor1 = normalM(Id1, decomp, withDelta, denomOption, JDefault, JDefault)[1];
4368        list nor2 = normalM(Id2, decomp, withDelta, denomOption, JDefault, JDefault)[1];
4369        printlevel = printlevel - 1;
4370        return(list(nor1, nor2));
4371      }
4372    }
4373  } else {
4374    poly condu = 0;
4375  }
4376
4377  // --------------- computation of the first test ideal ---------------------
4378  // To compute the radical we go back to the original ring.
4379  // If we are using a non-global ordering, we must change to the global
4380  // ordering.
4381  setring R;
4382  // If a test ideal is given at the input, we use it.
4383  if(inputJ == 0){
4384    if(isGlobal == 1){
4385      ideal J = fetch(Q, J);
4386      J = J, I;
4387      if(dbg >= 1){
4388        "The original singular locus is";
4389        groebner(J);
4390        if(dbg >= 2){pause();}
4391        "";
4392      }
4393      // We check if the only singular point is the origin.
4394      // If so, the radical is the maximal ideal at the origin.
4395      J = groebner(J);
4396      if(locAtZero(J)){
4397        J = maxideal(1);
4398      } else {
4399        J = radical(J);
4400      }
4401    } else {
4402      // We change to global dp ordering.
4403      list rl = ringlist(R);
4404      list origOrd = rl[3];
4405      list newOrd = list("dp", intvec(1:nvars(R))), list("C", 0);
4406      rl[3] = newOrd;
4407      def globR = ring(rl);
4408      setring globR;
4409      ideal J = fetch(Q, J);
4410      ideal I = fetch(R, I);
4411      J = J, I;
4412      if(dbg >= 1){
4413        "The original singular locus is";
4414        groebner(J);
4415        if(dbg>=2){pause();}
4416        "";
4417      }
4418      J = radical(J);
4419      setring R;
4420      ideal J = fetch(globR, J);
4421    }
4422  } else {
4423    ideal J = inputJ;
4424  }
4425
4426  if(dbg >= 1){
4427    "The radical of the original singular locus is";
4428    J;
4429    if(dbg>=2){pause();}
4430  }
4431
4432  // ---------------- election of the non zero divisor ---------------------
4433  setring Q;
4434  J = fetch(R, J);
4435  J = interred(J);
4436  if(denomOption == 0){
4437    poly D = getSmallest(J);    // Chooses the polynomial of smallest degree as
4438                                // non-zerodivisor.
4439  } else {
4440    poly D = getOneVar(J, denomOption);
4441  }
4442  if(dbg >= 1){
4443    "The non zero divisor is ", D;
4444    "";
4445  }
4446
4447  // ------- splitting the ideal by the non-zerodivisor (if possible) --------
4448  // If the ideal is equidimensional, but not necessarily prime, we check if D
4449  // is actually a non-zerodivisor of R/I.
4450  // If not, we split I.
4451  if((decomp == 1) or (decomp == 2)){
4452    // We check if D is actually a non-zerodivisor of R/I.
4453    // If not, we split I.
4454    Id1 = quotient(0, D);
4455    if(size(Id1) > 0){
4456      // We have to split.
4457      if(dbg >= 1){
4458        "A zerodivisor was found. We split the ideal. The zerodivisor is ", D;
4459      }
4460      setring R;
4461      ideal Id1 = fetch(Q, Id1), I;
4462      Id1 = groebner(Id1);
4463      ideal Id2 = quotient(I, Id1);
4464      // I = Id1 \cap Id2
4465      printlevel = printlevel + 1;
4466
4467      ideal JDefault = 0;  // Now it uses the default J;
4468      list nor1 = normalM(Id1, decomp, withDelta, denomOption, JDefault, JDefault)[1];
4469      list nor2 = normalM(Id2, decomp, withDelta, denomOption, JDefault, JDefault)[1];
4470      printlevel = printlevel - 1;
4471      return(list(nor1, nor2));
4472    }
4473  }
4474
4475  // --------------------- normalization ------------------------------------
4476  // We call normalMEqui to compute the normalization.
4477  setring R;
4478  poly D = fetch(Q, D);
4479  poly condu = fetch(Q, condu);
4480  J = fetch(Q, J);
4481  printlevel = printlevel + 1;
4482  list result = normalMEqui(I, J, condu, D, withDelta, denomOption);
4483  printlevel = printlevel - 1;
4484  return(list(result));
4485}
4486
4487///////////////////////////////////////////////////////////////////////////////
4488
4489static proc normalMEqui(ideal I, ideal origJ, poly condu, poly D, int withDelta)
4490// Here is where the normalization is actually computed.
4491
4492// Computes the normalization of R/I. (basering is R)
4493// I is assumed to be radical and equidimensional.
4494// origJ is the first test ideal.
4495// D is a non-zerodivisor of R/I.
4496// condu is a non-zerodivisor in the conductor or 0 if it was not computed.
4497// If withDelta = 1, computes the delta invariant.
4498{
4499  int step = 0;                       // Number of steps. (for debugging)
4500  int dbg = printlevel - voice + 2;   // dbg = printlevel (default: dbg = 0)
4501  int i;                              // counter
4502  int isNormal = 0;                   // check for exiting the loop
4503  int isGlobal = ord_test(basering);
4504  int delt;
4505
4506  def R = basering;
4507  poly c = D;
4508  ideal U;
4509  ideal cJ;
4510  list testOut;                 // Output of proc testIdeal
4511                                // (the test ideal and the ring structure)
4512
4513  qring Q = groebner(I);
4514  option("redSB");
4515  option("returnSB");
4516  ideal J = imap(R, origJ);
4517  poly c = imap(R, c);
4518  poly D = imap(R, D);
4519  poly condu = imap(R, condu);
4520  ideal cJ;
4521  ideal cJMod;
4522
4523  dbprint(dbg, "Preliminar step begins.");
4524
4525  // --------------------- computation of A1 -------------------------------
4526  dbprint(dbg, "Computing the quotient (DJ : J)...");
4527  ideal U = groebner(quotient(D*J, J));
4528  ideal oldU = 1;
4529
4530  if(dbg >= 2) { "The quotient is"; U; }
4531
4532  // ----------------- Grauer-Remmert criterion check -----------------------
4533  // We check if the equality in Grauert - Remmert criterion is satisfied.
4534  isNormal = checkInclusions(D*oldU, U);
4535  if(isNormal == 0)
4536  {
4537    if(dbg >= 1)
4538    {
4539      "In this step, we have the ring 1/c * U, with c =", c;
4540      "and U = "; U;
4541    }
4542  }
4543  else
4544  {
4545    // The original ring R/I was normal. Nothing to do.
4546    // We define anyway a new ring, equal to R, to be able to return it.
4547    setring R;
4548    list lR = ringlist(R);
4549    def ROut = ring(lR);
4550    setring ROut;
4551    ideal norid = fetch(R, I);
4552    ideal normap = maxideal(1);
4553    export norid;
4554    export normap;
4555    setring R;
4556    if(withDelta)
4557    {
4558      list output = ideal(1), poly(1), ROut, 0;
4559    }
4560    else
4561    {
4562      list output = ideal(1), poly(1), ROut;
4563    }
4564    return(output);
4565  }
4566
4567  // ----- computation of the chain of ideals A1 c A2 c ... c An ------------
4568  while(isNormal == 0)
4569  {
4570    step++;
4571    if(dbg >= 1) { ""; "Step ", step, " begins."; }
4572    dbprint(dbg, "Computing the test ideal...");
4573
4574    // --------------- computation of the test ideal ------------------------
4575    // Computes a test ideal for the new ring.
4576    // The test ideal will be the radical in the new ring of the original
4577    // test ideal.
4578    setring R;
4579    U = imap(Q, U);
4580    c = imap(Q, c);
4581    testOut = testIdeal(I, U, origJ, c, D);
4582    cJ = testOut[1];
4583
4584    setring Q;
4585    cJ = imap(R, cJ);
4586    cJ = groebner(cJ);
4587
4588    // cJ / c is now the ideal mapped back.
4589    // We have the generators as an ideal in the new ring,
4590    // but we want the generators as an ideal in the original ring.
4591    cJMod = getGenerators(cJ, U, c);
4592
4593    if(dbg >= 2) { "The test ideal in this step is "; cJMod; }
4594
4595    cJ = cJMod;
4596
4597    // ------------- computation of the quotient (DJ : J)--------------------
4598    oldU = U;
4599    dbprint(dbg, "Computing the quotient (c*D*cJ : cJ)...");
4600    U = quotient(c*D*cJ, cJ);
4601    if(dbg >= 2){"The quotient is "; U;}
4602
4603    // ------------- Grauert - Remmert criterion check ----------------------
4604    // We check if the equality in Grauert - Remmert criterion is satisfied.
4605    isNormal = checkInclusions(D*oldU, U);
4606
4607    if(isNormal == 1)
4608    {
4609      // We go one step back. In the last step we didnt get antyhing new,
4610      // we just verified that the ring was already normal.
4611      dbprint(dbg, "The ring in the previous step was already normal.");
4612      dbprint(dbg, "");
4613      U = oldU;
4614    }
4615    else
4616    {
4617      // ------------- preparation for next iteration ----------------------
4618      // We have to go on.
4619      // The new denominator is chosen.
4620      c = D * c;
4621     
4622      // If we have a universal denominator of smaller degree than c,
4623      // we replace c by it.
4624      if(condu != 0){
4625        if(deg(c) > deg(condu))
4626        {
4627          U = changeDenominatorQ(U, c, condu);
4628          c = condu;
4629        }
4630      }
4631      if(dbg >= 1)
4632      {
4633        "In this step, we have the ring 1/c * U, with c =", c;
4634        "and U = ";
4635        U;
4636        if(dbg>=2){pause();}
4637      }
4638    }
4639  }
4640
4641  // ------------------------- delta computation ----------------------------
4642  if(withDelta)
4643  {
4644    ideal UD = groebner(U);
4645    delt = vdim(std(modulo(UD, c)));
4646  }
4647
4648  // -------------------------- prepare output -----------------------------
4649  setring R;
4650  U = fetch(Q, U);
4651  c = fetch(Q, c);
4652
4653  // Ring structure of the new ring
4654  def ere = testOut[2];
4655  if(withDelta)
4656  {
4657    list output = U, c, ere, delt;
4658  }
4659  else
4660  {
4661    list output = U, c, ere;
4662  }
4663  return(output);
4664}
4665
4666///////////////////////////////////////////////////////////////////////////////
4667
4668static proc lineUpLast(ideal U, poly c)
4669// Sets c as the last generator of U.
4670{
4671  int i;
4672  ideal newU;
4673  for (i = 1; i <= ncols(U); i++)
4674  {
4675    if(U[i] != c)
4676    {
4677      if(size(newU) == 0)
4678      { newU = U[i]; }
4679      else
4680      { newU = newU, U[i]; }
4681    }
4682  }
4683  if(size(newU) == 0)
4684  { newU = c; }
4685  else
4686  { newU = newU, c; }
4687  return(newU);
4688}
4689
4690///////////////////////////////////////////////////////////////////////////////
4691
4692static proc lineUp(ideal U, poly c)
4693// Sets c as the first generator of U.
4694{
4695  int i;
4696  ideal newU = c;
4697  for (i = 1; i <= ncols(U); i++)
4698  {
4699    if(U[i] != c)
4700    {
4701      newU = newU, U[i];
4702    }
4703  }
4704  return(newU);
4705}
4706
4707///////////////////////////////////////////////////////////////////////////////
4708
4709//WARNING - elim is not working here!! Check!!
4710//It is now replaced by computing an eliminating groebner basis.
4711proc getOneVar(ideal J, int vari)
4712"USAGE:   getOneVar(J, vari); J is a 0-dimensional ideal, vari is an integer.
4713RETURN:  a polynomial of J in the variable indicated by vari of smallest
4714         degree.@*
4715NOTE:    Works only over rings of two variables.@*
4716         It is intended mainly as an auxiliary procedure for computing
4717         integral bases. @*
4718EXAMPLE: example getOneVar; shows an example
4719"
4720{
4721  def R = basering;
4722  ring RR = 0, (var(3-vari), var(vari)), lp;
4723  ideal J = imap(R, J);
4724  J = groebner(J);
4725  poly g = J[1];
4726  setring R;
4727  poly g = imap(RR, g);
4728  return(g);
4729}
4730example
4731{ "EXAMPLE:";
4732  printlevel = printlevel+1;
4733  echo = 2;
4734  ring s = 0,(x,y),dp;
4735  ideal J = x3-y, y3;
4736  getOneVar(J, 1);
4737
4738  echo = 0;
4739  printlevel = printlevel-1;
4740}
4741///////////////////////////////////////////////////////////////////////////////
4742
4743proc getSmallest(ideal J)
4744"USAGE:   getSmallest(J); J is an ideal.
4745RETURN:  the generator of J of smallest degree. If there are more than one, it
4746         chooses the one with smallest number of monomials.@*
4747NOTE:    It looks only at the generator of J, not at all the polynomials in
4748         the ideal.@*
4749         It is intended maninly to compute a good universal denominator in the
4750         normalization algorithms.@*
4751EXAMPLE: example getSmallest; shows an example
4752"
4753{
4754// Computes the polynomial of smallest degree of J.
4755//
4756  int i;
4757  poly p = J[1];
4758  int d = deg(p);
4759  int di;
4760  for(i = 2; i <= ncols(J); i++)
4761  {
4762    if(J[i] != 0)
4763    {
4764      di = deg(J[i]);
4765      if(di < d)
4766      {
4767        p = J[i];
4768        d = di;
4769      }
4770      else
4771      {
4772        if(di == d)
4773        {
4774          if(size(J[i]) < size(p))
4775          {
4776            p = J[i];
4777          }
4778        }
4779      }
4780    }
4781  }
4782  return(p);
4783}
4784example
4785{ "EXAMPLE:";
4786  printlevel = printlevel+1;
4787  echo = 2;
4788  ring s = 0,(x,y),dp;
4789  ideal J = x3-y, y5, x2-y2+1;
4790  getSmallest(J);
4791
4792  echo = 0;
4793  printlevel = printlevel-1;
4794}
4795
4796///////////////////////////////////////////////////////////////////////////////
4797
4798static proc getGenerators(ideal J, ideal U, poly c)
4799{
4800// Computes the generators of J as an ideal in the original ring,
4801// where J is given by generators in the new ring.
4802
4803// The new ring is given by 1/c * U in the total ring of fractions.
4804
4805  int i, j;                             // counters;
4806  int dbg = printlevel - voice + 2;     // dbg = printlevel (default: dbg = 0)
4807  poly p;                               // The lifted polynomial
4808  ideal JGr = groebner(J);              // Groebner base of J
4809
4810  if(dbg>1){"Checking for new generators...";}
4811  for(i = 1; i <= ncols(J); i++)
4812  {
4813    for(j = 1; j <= ncols(U); j++)
4814    {
4815      p = lift(c, J[i]*U[j])[1,1];
4816      p = reduce(p, JGr);
4817      if(p != 0)
4818      {
4819        if(dbg>1)
4820        {
4821          "New polynoial added:", p;
4822          if(dbg>4) {pause();}
4823        }
4824        JGr = JGr, p;
4825        JGr = groebner(JGr);
4826        J = J, p;
4827      }
4828    }
4829  }
4830  return(J);
4831}
4832
4833///////////////////////////////////////////////////////////////////////////////
4834
4835static proc testIdeal(ideal I, ideal U, ideal origJ, poly c, poly D)
4836{
4837// Internal procedure, used in normalM.
4838// Computes the test ideal in the new ring.
4839// It takes the original test ideal and computes the radical of it in the
4840// new ring.
4841
4842// The new ring is 1/c * U.
4843// The original test ideal is origJ.
4844// The original ring is R / I, where R is the basering.
4845  int i;                                // counter
4846  int dbg = printlevel - voice + 2;     // dbg = printlevel (default: dbg = 0)
4847  def R = basering;                      // We dont work in the quo
4848  ideal J = origJ;
4849
4850  // ---------- computation of the ring structure of 1/c * U ----------------
4851  U = lineUp(U, c);
4852
4853  if(dbg > 1){"Computing the new ring structure...";}
4854  list ele = computeRing(U, I, "noRed");
4855
4856  def origEre = ele[1];
4857  setring origEre;
4858  if(dbg > 1){"The relations are"; norid;}
4859
4860  // ---------------- setting the ring to work in  --------------------------
4861  int isGlobal = ord_test(origEre);      // Checks if the original ring has
4862                                         // global ordering.
4863  if(isGlobal != 1)
4864  {
4865    list rl = ringlist(origEre);
4866    list origOrd = rl[3];
4867    list newOrd = list("dp", intvec(1:nvars(origEre))), list("C", 0);
4868    rl[3] = newOrd;
4869    def ere = ring(rl);     // globR is the original ring but
4870                            // with a global ordering.
4871    setring ere;
4872    ideal norid = imap(origEre, norid);
4873  }
4874  else
4875  {
4876    def ere = origEre;
4877  }
4878
4879  ideal I = imap(R, I);
4880  ideal J = imap(R, J);
4881  J = J, norid, I;
4882
4883
4884  // ----- computation of the test ideal using the ring structure of Ai -----
4885  option("redSB");
4886  option("returnSB");
4887
4888  if(dbg > 1){"Computing the radical of J...";}
4889  J = radical(J);
4890  if(dbg > 1){"Computing the interreduction of the radical...";}
4891  J = groebner(J);
4892  //J = interred(J);
4893  if(dbg > 1)
4894  {
4895    "The radical in the generated ring is";
4896    J;
4897    if(dbg>4){pause();}
4898  }
4899
4900  setring ere;
4901
4902  // -------------- map from Ai to the total ring of fractions ---------------
4903  // Now we must map back this ideal J to U_i / c in the total ring of
4904  // fractions.
4905  // The map sends T_j -> u_j / c.
4906  // The map is built by the following steps:
4907  // 1) We compute the degree of the generators of J with respect to the
4908  //    new variables T_j.
4909  // 2) For each generator, we multiply each term by a power of c, as if
4910  //    taking c^n as a common denominator (considering the new variables as
4911  //    a polynomial in the old variables divided by c).
4912  // 3) We replace the new variables T_j by the corresponding numerator u_j.
4913  // 4) We lift the resulting polynomial to change the denominator
4914  //    from c^n to c.
4915  int nNewVars = nvars(ere) - nvars(R);      // Number of new variables
4916  poly c = imap(R, c);
4917  intvec @v = 1..nNewVars;    // Vector of the new variables.
4918                              // They must be the first ones.
4919  if(dbg > 1){"The indices of the new variables are", @v;}
4920
4921  // ---------------------- step 1 of the mapping ---------------------------
4922  intvec degs;
4923  for(i = 1; i<=ncols(J); i++)
4924  {
4925    degs[i] = degSubring(J[i], @v);
4926  }
4927  if(dbg > 1)
4928  {
4929    "The degrees with respect to the new variables are";
4930    degs;
4931  }
4932
4933  // ---------------------- step 2 of the mapping ---------------------------
4934  ideal mapJ = mapBackIdeal(J, c, @v);
4935
4936  setring R;
4937
4938  // ---------------------- step 3 of the mapping ---------------------------
4939  ideal z;                    // The variables of the original ring in order.
4940  for(i = 1; i<=nvars(R); i++)
4941  {
4942    z[i] = var(i);
4943  }
4944
4945  map f = ere, U[2..ncols(U)], z[1..ncols(z)]; // The map to the original ring.
4946  if(dbg > 1)
4947  {
4948    "The map is ";
4949    f;
4950    if(dbg>4){pause();}
4951  }
4952
4953  if(dbg > 1){ "Computing the map..."; }
4954
4955  J = f(mapJ);
4956  if(dbg > 1)
4957  {
4958    "The ideal J mapped back (before lifting) is";
4959    J;
4960    if(dbg>4){pause();}
4961  }
4962
4963  // ---------------------- step 4 of the mapping ---------------------------
4964  qring Q = groebner(I);
4965  ideal J = imap(R, J);
4966  poly c = imap(R, c);
4967  for(i = 1; i<=ncols(J); i++)
4968  {
4969    if(degs[i]>1)
4970    {
4971      J[i] = lift(c^(degs[i]-1), J[i])[1,1];
4972    }
4973    else
4974    {
4975      if(degs[i]==0) { J[i] = c*J[i]; }
4976    }
4977  }
4978
4979  if(dbg > 1)
4980  {
4981    "The ideal J lifted is";
4982    J;
4983    if(dbg>4){pause();}
4984  }
4985
4986  // --------------------------- prepare output ----------------------------
4987  J = groebner(J);
4988
4989  setring R;
4990  J = imap(Q, J);
4991
4992  return(list(J, ele[1]));
4993}
4994
4995///////////////////////////////////////////////////////////////////////////////
4996
4997proc changeDenominator(ideal U1, poly c1, poly c2, ideal I)
4998"USAGE:   changeDenominator(U1, c1, c2, I); U1 and I ideals, c1 and c2
4999         polynomials.@*
5000RETURN:  an ideal U2 such that the A-modules 1/c1 * U1 and 1/c2 * U2 are equal,
5001         where A = R/I and R is the basering.@*
5002NOTE:    It assumes that such U2 exists. It is intended maninly as an auxiliary
5003         procedure in the normalization algorithms.@*
5004EXAMPLE: example changeDenominator; shows an example
5005"
5006{
5007// Let A = R / I. Given an A-module in the form 1/c1 * U1 (U1 ideal of A), it
5008// computes a new ideal U2 such that the the A-module is 1/c2 * U2.
5009// The base ring is R, but the computations are to be done in R / I.
5010  int a;      // counter
5011  def R = basering;
5012  qring Q = I;
5013  ideal U1 = fetch(R, U1);
5014  poly c1 = fetch(R, c1);
5015  poly c2 = fetch(R, c2);
5016  ideal U2 = changeDenominatorQ(U1, c1, c2);
5017  setring R;
5018  ideal U2 = fetch(Q, U2);
5019  return(U2);
5020}
5021example
5022{
5023  "EXAMPLE:";
5024  echo = 2;
5025  ring s = 0,(x,y),dp;
5026  ideal I = y5-y4x+4y2x2-x4;
5027  ideal U1 = normal(I)[2][1];
5028  poly c1 = U1[4];
5029  U1;c1;
5030  // 1/c1 * U1 is the normalization of I.
5031  ideal U2 = changeDenominator(U1, c1, x3, I);
5032  U2;
5033  // 1/x3 * U2 is also the normalization of I, but with a different denominator.
5034  echo = 0;
5035}
5036
5037///////////////////////////////////////////////////////////////////////////////
5038
5039static proc changeDenominatorQ(ideal U1, poly c1, poly c2)
5040{
5041// Given a ring in the form 1/c1 * U, it computes a new U2 st the ring
5042// is 1/c2 * U2.
5043// The base ring is already a quotient ring R / I.
5044  int a;      // counter
5045  ideal U2;
5046  poly p;
5047  for(a = 1; a <= ncols(U1); a++)
5048  {
5049    p = lift(c1, c2*U1[a])[1,1];
5050    U2[a] = p;
5051  }
5052  return(U2);
5053}
5054
5055///////////////////////////////////////////////////////////////////////////////
5056
5057static proc checkInclusions(ideal U1, ideal U2)
5058{
5059// Checks if the identity A = Hom(J, J) of Grauert-Remmert criterion is
5060// satisfied.
5061  int dbg = printlevel - voice + 2;     // dbg = printlevel (default: dbg = 0)
5062  list reduction1;
5063  list reduction2;
5064
5065  // ---------------------- inclusion Hom(J, J) c A -------------------------
5066  if(dbg > 1){"Checking the inclusion Hom(J, J) c A:";}
5067  // This interred is used only because a bug in groebner!
5068  U1 = groebner(U1);
5069  reduction1 = reduce(U2, U1);
5070  if(dbg > 1){reduction1[1];}
5071
5072  // ---------------------- inclusion A c Hom(J, J) -------------------------
5073  // The following check should always be satisfied.
5074  // This is only used for debugging.
5075  if(dbg > 1)
5076  {
5077    "and the inclusion A c Hom(J, J): (this should always be satisfied)";
5078    // This interred is used only because a bug in groebner!
5079    U2 = groebner(U2);
5080    reduction2 = reduce(U1, groebner(U2));
5081    reduction2[1];
5082    if(size(reduction2[1]) > 0)
5083    {
5084      "Something went wrong... (this inclusion should always be satisfied)";
5085      ~;
5086    }
5087    else
5088    {
5089      if(dbg>4){pause();}
5090    }
5091  }
5092
5093  if(size(reduction1[1]) == 0)
5094  {
5095    // We are done! The ring computed in the last step was normal.
5096    return(1);
5097  }
5098  else
5099  {
5100    return(0);
5101  }
5102}
5103
5104///////////////////////////////////////////////////////////////////////////////
5105
5106static proc degSubring(poly p, intvec @v)
5107{
5108// Computes the degree of a polynomial taking only some variables as variables
5109// and the others as parameters.
5110
5111// The degree is taken w.r.t. the variables indicated in v.
5112  int i;      // Counter
5113  int d = 0;  // The degree
5114  int e;      // Degree (auxiliar variable)
5115  for(i = 1; i <= size(p); i++)
5116  {
5117    e = sum(leadexp(p[i]), @v);
5118    if(e > d){d = e;}
5119  }
5120  return(d);
5121}
5122
5123///////////////////////////////////////////////////////////////////////////////
5124
5125static proc mapBackIdeal(ideal I, poly c, intvec @v)
5126{
5127// Modifies all polynomials in I so that a map x(i) -> y(i)/c can be
5128// carried out.
5129
5130// v indicates wicih variables x(i) of the ring will be mapped to y(i)/c.
5131
5132  int i;  // counter
5133  for(i = 1; i <= ncols(I); i++)
5134  {
5135    I[i] = mapBackPoly(I[i], c, @v);
5136  }
5137  return(I);
5138}
5139
5140///////////////////////////////////////////////////////////////////////////////
5141
5142static proc mapBackPoly(poly p, poly c, intvec @v)
5143{
5144// Multiplies each monomial of p by a power of c so that a map x(i) -> y(i)/c
5145// can be carried out.
5146
5147// v indicates wicih variables x(i) of the ring will be mapped to y(i)/c.
5148  int i;  // counter
5149  int e;  // exponent
5150  int d = degSubring(p, @v);
5151  poly g = 0;
5152  int size_p=size(p);
5153  for(i = 1; i <= size_p; i++)
5154  {
5155    e = sum(leadexp(p[i]), @v);
5156    g = g + p[i] * c^(d-e);
5157  }
5158  return(g);
5159}
5160
5161//                    End procedures for normal
5162///////////////////////////////////////////////////////////////////////////////
5163
5164
5165///////////////////////////////////////////////////////////////////////////////
5166//                  Begin procedures for normalC
5167
5168// We first define resp. copy some attributes to be used in proc normal and
5169// static proc normalizationPrimes, and ..., to speed up computation in
5170// special cases
5171//NOTE:  We use the following attributes:
5172// 1     attrib(id,"isCohenMacaulay");         //--- Cohen Macaulay
5173// 2     attrib(id,"isCompleteIntersection");  //--- complete intersection
5174// 3     attrib(id,"isHypersurface");          //--- hypersurface
5175// 4     attrib(id,"isEquidimensional");       //--- equidimensional ideal
5176// 5     attrib(id,"isPrim");                  //--- prime ideal
5177// 6     attrib(id,"isRegInCodim2");           //--- regular in codimension 2
5178// 7     attrib(id,"isIsolatedSingularity");   //--- isolated singularities
5179// 8     attrib(id,"onlySingularAtZero");      //--- only singular at 0
5180// 9     attrib(id,"isRadical");               //--- radical ideal
5181//Recall: (attrib(id,"xy"),1) sets attrib xy to TRUE and
5182//        (attrib(id,"xy"),0) to FALSE
5183
5184static proc getAttrib (ideal id)
5185"USAGE:   getAttrib(id);  id=ideal
5186COMPUTE: check attributes for id. If the attributes above are defined,
5187         take its value, otherwise define it and set it to 0
5188RETURN:  intvec of size 9, with entries 0 or 1,  values of attributes defined
5189         above (in this order)
5190EXAMPLE: no example
5191"
5192{
5193  int isCoM,isCoI,isHy,isEq,isPr,isReg,isIso,oSAZ,isRad;
5194
5195  if( typeof(attrib(id,"isCohenMacaulay"))=="int" )
5196  {
5197    if( attrib(id,"isCohenMacaulay")==1 )
5198    { isCoM=1; isEq=1; }
5199  }
5200
5201  if( typeof(attrib(id,"isCompleteIntersection"))=="int" )
5202  {
5203    if(attrib(id,"isCompleteIntersection")==1)
5204    { isCoI=1; isCoM=1; isEq=1; }
5205  }
5206
5207  if( typeof(attrib(id,"isHypersurface"))=="int" )
5208  {
5209    if(attrib(id,"isHypersurface")==1)
5210    { isHy=1; isCoI=1; isCoM=1; isEq=1; }
5211  }
5212
5213  if( typeof(attrib(id,"isEquidimensional"))=="int" )
5214  {
5215    if(attrib(id,"isEquidimensional")==1)
5216    { isEq=1; }
5217  }
5218
5219  if( typeof(attrib(id,"isPrim"))=="int" )
5220  {
5221    if(attrib(id,"isPrim")==1)
5222    { isPr=1; }
5223  }
5224
5225  if( typeof(attrib(id,"isRegInCodim2"))=="int" )
5226  {
5227    if(attrib(id,"isRegInCodim2")==1)
5228    { isReg=1; }
5229  }
5230
5231  if( typeof(attrib(id,"isIsolatedSingularity"))=="int" )
5232  {
5233    if(attrib(id,"isIsolatedSingularity")==1)
5234    { isIso=1; }
5235  }
5236
5237  if( typeof(attrib(id,"onlySingularAtZero"))=="int" )
5238  {
5239    if(attrib(id,"onlySingularAtZero")==1)
5240    { oSAZ=1; }
5241  }
5242
5243  if( typeof(attrib(id,"isRad"))=="int" )
5244  {
5245    if(attrib(id,"isRad")==1)
5246    { isRad=1; }
5247  }
5248
5249  intvec atr = isCoM,isCoI,isHy,isEq,isPr,isReg,isIso,oSAZ,isRad;
5250  return(atr);
5251}
5252
5253///////////////////////////////////////////////////////////////////////////////
5254
5255static proc setAttrib (ideal id, intvec atr)
5256"USAGE:   setAttrib(id,atr);  id ideal, atr intvec
5257COMPUTE: set attributes to id specified by atr
5258RETURN:  id, with assigned attributes from atr
5259EXAMPLE: no example
5260"
5261{
5262  attrib(id,"isCohenMacaulay",atr[1]);         //--- Cohen Macaulay
5263  attrib(id,"isCompleteIntersection",atr[2]);  //--- complete intersection
5264  attrib(id,"isHypersurface",atr[3]);          //--- hypersurface
5265  attrib(id,"isEquidimensional",atr[4]);       //--- equidimensional ideal
5266  attrib(id,"isPrim",atr[5]);                  //--- prime ideal
5267  attrib(id,"isRegInCodim2",atr[6]);           //--- regular in codimension 2
5268  attrib(id,"isIsolatedSingularity",atr[7]);   //--- isolated singularities
5269  attrib(id,"onlySingularAtZero",atr[8]);      //--- only singular at 0
5270  attrib(id,"isRadical",atr[9]);               //--- radical ideal
5271
5272  return(id);
5273}
5274
5275///////////////////////////////////////////////////////////////////////////////
5276// copyAttribs is not used anywhere so far
5277
5278static proc copyAttribs (ideal id1, ideal id)
5279"USAGE:   copyAttribs(id1,id);  id1, id ideals
5280COMPUTE: copy attributes from id1 to id
5281RETURN:  id, with assigned attributes from id1
5282EXAMPLE: no example
5283"
5284{
5285  if( typeof(attrib(id1,"isCohenMacaulay"))=="int" )
5286  {
5287    if( attrib(id1,"isCohenMacaulay")==1 )
5288    {
5289      attrib(id,"isEquidimensional",1);
5290    }
5291  }
5292  else
5293  {
5294    attrib(id,"isCohenMacaulay",0);
5295  }
5296
5297  if( typeof(attrib(id1,"isCompleteIntersection"))=="int" )
5298  {
5299    if(attrib(id1,"isCompleteIntersection")==1)
5300    {
5301      attrib(id,"isCohenMacaulay",1);
5302      attrib(id,"isEquidimensional",1);
5303    }
5304  }
5305  else
5306  {
5307    attrib(id,"isCompleteIntersection",0);
5308  }
5309
5310  if( typeof(attrib(id1,"isHypersurface"))=="int" )
5311  {
5312    if(attrib(id1,"isHypersurface")==1)
5313    {
5314      attrib(id,"isCompleteIntersection",1);
5315      attrib(id,"isCohenMacaulay",1);
5316      attrib(id,"isEquidimensional",1);
5317    }
5318  }
5319  else
5320  {
5321    attrib(id,"isHypersurface",0);
5322  }
5323
5324  if( (typeof(attrib(id1,"isEquidimensional"))=="int") )
5325  {
5326    if(attrib(id1,"isEquidimensional")==1)
5327    {
5328      attrib(id,"isEquidimensional",1);
5329    }
5330  }
5331  else
5332  {
5333    attrib(id,"isEquidimensional",0);
5334  }
5335
5336  if( typeof(attrib(id1,"isPrim"))=="int" )
5337  {
5338    if(attrib(id1,"isPrim")==1)
5339    {
5340      attrib(id,"isEquidimensional",1);
5341    }
5342  }
5343  else
5344  {
5345    attrib(id,"isPrim",0);
5346  }
5347
5348  if( (typeof(attrib(id1,"isRegInCodim2"))=="int") )
5349  {
5350    if(attrib(id1,"isRegInCodim2")==1)
5351    {
5352      attrib(id,"isRegInCodim2",1);
5353    }
5354  }
5355  else
5356  {
5357    attrib(id,"isRegInCodim2",0);
5358  }
5359
5360  if( (typeof(attrib(id1,"isIsolatedSingularity"))=="int") )
5361  {
5362    if(attrib(id1,"isIsolatedSingularity")==1)
5363    {
5364      attrib(id,"isIsolatedSingularity",1);
5365    }
5366  }
5367  else
5368  {
5369    attrib(id,"isIsolatedSingularity",0);
5370  }
5371
5372  if( typeof(attrib(id1,"onlySingularAtZero"))=="int" )
5373  {
5374    if(attrib(id1,"onlySingularAtZero")==1)
5375    {
5376      attrib(id,"isIsolatedSingularity",1);
5377    }
5378  }
5379  else
5380  {
5381    attrib(id,"onlySingularAtZero",0);
5382  }
5383
5384  if( typeof(attrib(id1,"isRad"))=="int" )
5385  {
5386    if(attrib(id1,"isRad")==1)
5387    {
5388      attrib(id,"isRad",1);
5389    }
5390  }
5391  else
5392  {
5393    attrib(id,"isRad",0);
5394  }
5395  return(id);
5396}
5397///////////////////////////////////////////////////////////////////////////////
5398
5399proc normalC(ideal id, list #)
5400"USAGE:  normalC(id [,choose]);  id = radical ideal, choose = optional list
5401         of string.
5402         Optional parameters in list choose (can be entered in any order):@*
5403         Decomposition:@*
5404         - \"equidim\" -> computes first an equidimensional decomposition,
5405         and then the normalization of each component (default).@*
5406         - \"prim\" -> computes first the minimal associated primes, and then
5407         the normalization of each prime. @*
5408         - \"noDeco\" -> no preliminary decomposition is done. If the ideal is
5409         not equidimensional radical, output might be wrong.@*
5410         - \"isPrim\" -> assumes that the ideal is prime. If the assumption does
5411         not hold, output might be wrong.@*
5412         - \"noFac\" -> factorization is avoided in the computation of the
5413         minimal associated primes;
5414         Other:@*
5415         - \"withGens\" -> the minimal associated primes P_i of id are
5416         computed and for each P_i, algebra generators of the integral closure
5417         of basering/P_i are computed as elements of its quotient field;@*
5418         If choose is not given or empty, the default options are used.@*
5419ASSUME:  The ideal must be radical, for non-radical ideals the output may
5420         be wrong (id=radical(id); makes id radical). However, if option
5421         \"prim\" is set the minimal associated primes are computed first
5422         and hence normalC computes the normalization of the radical of id.
5423         \"isPrim\" should only be used if id is known to be irreducible.
5424RETURN:  a list, say nor, of size 2 (resp. 3 if option \"withGens\" is set).@*
5425         * nor[1] is always a of r rings, where r is the number of associated
5426         primes with option \"prim\" (resp. >= no of equidimenensional
5427         components with option  \"equidim\").@*
5428         Each ring Ri=nor[1][i], i=1..r, contains two ideals with given
5429         names @code{norid} and @code{normap} such that @*
5430         - Ri/norid is the normalization of the i-th component, i.e. the
5431          integral closure in its field of fractions as affine ring, i.e. Ri is
5432          given in the form K[X(1..p),T(1..q)], where K is the ground field;
5433         - normap gives the normalization map from basering/id to
5434           Ri/norid for each i (the j-th element of normap is mapped to the
5435           j-th variable of R).@*
5436         - the direct sum of the rings Ri/norid is the normalization
5437           of basering/id; @*
5438         ** If option \"withGens\" is not set: @*
5439         * nor[2] shows the delta invariants: nor[2] is a list of an intvec of
5440         size r, the delta invariants of the r components, and an integer, the
5441         delta invariant of basering/id. (-1 means infinite, 0 that basering/P_i
5442         resp. basering/input is normal, -2 means that delta resp. delta of one
5443         of the components is not computed (which may happen if \"equidim\" is
5444         given). @*
5445         ** If option \"withGens\" is set:
5446         * nor[2] is a list of ideals Ii=nor[2][i], i=1..r, in the basering,
5447         generating the integral closure of basering/P_i in its quotient field
5448         as K-algebra (K the ground field):@*
5449         If Ii is given by polynomials g_1,...,g_k, then c:=g_k is a non-zero
5450         divisor and the j-th variables of the ring Ri satisfies var(j)=g_j/c,
5451         j=1..k-1, as element in the quotient field of basering/P_i. The
5452         g_j/g_k+1 are K-algebra generators  of the integral closure of
5453         basering/P_i.@*
5454         * nor[3] shows the delta invariant as above.
5455THEORY:  We use the Grauert-Remmert-de Jong algorithm [c.f. G.-M. Greuel,
5456         G. Pfister: A SINGULAR Introduction to Commutative Algebra, 2nd Edition.
5457         Springer Verlag (2007)].
5458         The procedure computes the algebra structure and the delta invariant of
5459         the normalization of R/id:@*
5460         The normalization is an affine algebra over the ground field K
5461         and nor[1] presents it as such: Ri = K[X(1..p),T(1..q)] and Ri/norid
5462         is the integral closure of R/P_i; if option \"withGens\" is set the
5463         X(j) and T(j) are expressed as quotients in the total ring of
5464         fractions. Note that the X(j) and T(j) generate the integral closure
5465         as K-algebra, but not necessarily as R-module (since relations of the
5466         form X(1)=T(1)*T(2) may have been eliminated). Geometrically the
5467         algebra structure is relevant since the variety of the ideal norid in
5468         Ri is the normalization of the variety of the ideal P_i in R.@*
5469         The delta invariant of a reduced ring A is dim_K(normalization(A)/A).
5470         For A=K[x1,...,xn]/id we call this number also the delta invariant of
5471         id. nor[3] returns the delta invariants of the components P_i and of
5472         id.
5473NOTE:    To use the i-th ring type: @code{def R=nor[1][i]; setring R;}.
5474@*       Increasing/decreasing printlevel displays more/less comments
5475         (default: printlevel=0).
5476@*       Not implemented for local or mixed orderings or quotient rings.
5477         For local or mixed orderings use proc 'normal'.
5478@*       If the input ideal id is weighted homogeneous a weighted ordering may
5479         be used (qhweight(id); computes weights).
5480KEYWORDS: normalization; integral closure; delta invariant.
5481SEE ALSO: normal, normalP.
5482EXAMPLE: example normalC; shows an example
5483"
5484{
5485   int i,j;
5486   int withGens, withEqui, withPrim, isPrim, noFac;
5487   int dbg = printlevel-voice+2;
5488   int nvar = nvars(basering);
5489   int chara  = char(basering);
5490   list result, prim, keepresult;
5491
5492  int decomp;   // Preliminar decomposition:
5493                // 0 -> no decomposition (id is assumed to be prime)
5494                // 1 -> no decomposition
5495                //      (id is assumed to be equidimensional radical)
5496                // 2 -> equidimensional decomposition
5497                // 3 -> minimal associated primes
5498
5499   // Default methods:
5500   noFac = 0;         // Use facstd when computing minimal associated primes
5501   decomp = 2;        // Equidimensional decomposition for nvar > 2
5502   if (nvar <= 2)
5503   { decomp = 3; }    // Compute minimal associated primes if nvar <= 2
5504
5505   if ( ord_test(basering) != 1 )
5506   {
5507     "";
5508     "// Not implemented for this ordering,";
5509     "// please change to global ordering or use proc normal";
5510     return(result);
5511   }
5512
5513//--------------------------- define the method ---------------------------
5514   string method;                //make all options one string in order to use
5515                                 //all combinations of options simultaneously
5516   for ( i=1; i <= size(#); i++ )
5517   {
5518     if ( typeof(#[i]) == "string" )
5519     {
5520       method = method + #[i];
5521     }
5522   }
5523
5524   //--------------------------- choosen methods -----------------------
5525   // "withGens": computes algebra generators for each irreducible component
5526   // ### the extra code for withGens should be incorporated in the general case
5527
5528   if ( find(method,"withgens") or find(method,"withGens"))
5529   {
5530     withGens = 1;
5531   }
5532
5533   // the general case: either equidim or minAssGTZ or no decomposition
5534
5535   if ( find(method,"isprim") or find(method,"isPrim") )
5536   {decomp = 0; isPrim=1;}
5537
5538   if ( find(method,"nodeco") or find(method,"noDeco") )
5539   {decomp = 1;}
5540
5541   if ( find(method,"equidim") )
5542   { decomp = 2; }
5543
5544   if ( find(method,"prim") )
5545   { decomp = 3; }
5546
5547   if ( find(method,"nofac") or find(method,"noFac") )
5548   { noFac = 1; }
5549
5550   kill #;
5551   list #;
5552
5553//------- Special algorithm with computation of the generators, RETURN -------
5554   //--------------------- method "withGens" ----------------------------------
5555   //the integral closure is computed in proc primeClosure. In the general case
5556   //it is computed in normalizationPrimes. The main difference is that in
5557   //primeClosure the singular locus is only computed in the first iteration,
5558   //that no attributes are used, and that the generators are computed.
5559   //In primeClosure the (algebra) generators for each irreducible component
5560   //are computed in the static proc closureGenerators
5561
5562   if( withGens )
5563   {
5564      if( dbg >= 1 )
5565      {  "";
5566         "// We use method 'withGens'";
5567      }
5568      if ( decomp == 0 or decomp == 1 )
5569      {
5570         prim[1] = id;
5571         if( dbg >= 0 )
5572         {
5573           "";
5574           "// ** WARNING: result is correct if ideal is prime (not checked) **";
5575           "// if procedure is called with string \"prim\", primality is checked";
5576         }
5577      }
5578      else
5579      {
5580         if(dbg >= 1)
5581         {  "// Computing minimal associated primes..."; }
5582
5583         if( noFac )
5584         { prim = minAssGTZ(id,1); }
5585         else
5586         { prim = minAssGTZ(id); }
5587
5588         if(dbg >= 2)
5589         {  prim;""; }
5590         if(dbg >= 1)
5591         {
5592            "// number of irreducible components is", size(prim);
5593         }
5594      }
5595   //----------- compute integral closure for every component -------------
5596      int del;
5597      intvec deli;
5598      list Gens,l,resu,Resu;
5599      ideal gens;
5600      def R = basering;
5601      poly gg;
5602
5603      for(i=1; i<=size(prim); i++)
5604      {
5605         if(dbg>=1)
5606         {
5607            ""; pause(); "";
5608            "// Computing normalization of component",i;
5609            "   ---------------------------------------";
5610         }
5611
5612         if( defined(ker) ) { kill ker; }
5613         ideal ker = prim[i];
5614         export(ker);
5615         l = R;
5616         l = primeClosure(l,1);              //here the work is done
5617         // primeClosure is called with list l consisting of the basering
5618         //### ausprobieren ob primeClosure(l,1) schneller als primeClosure(l)
5619         // 1 bedeutet: kuerzester nzd
5620         // l[size(l)] is the delta invariant
5621
5622         if ( l[size(l)] >= 0 && del >= 0 )
5623         {
5624            del = del + l[size(l)];
5625         }
5626         else
5627         { del = -1; }
5628         deli = l[size(l)],deli;
5629
5630         l = l[1..size(l)-1];
5631         resu = list(l[size(l)]) + resu;
5632         gens = closureGenerators(l);         //computes algebra(!) generators
5633
5634         //NOTE: gens[i]/gens[size(gens)] expresses the ith variable of resu[1]
5635         //(the normalization) as fraction of elements of the basering;
5636         //the variables of resu[1] are algebra generators.
5637         //gens[size(gens)] is a non-zero divisor of basering/i
5638
5639         //divide by the greatest common divisor:
5640         gg = gcd( gens[1],gens[size(gens)] );
5641         for(j=2; j<=size(gens)-1; j++)
5642         {
5643            gg=gcd(gg,gens[j]);
5644         }
5645         for(j=1; j<=size(gens); j++)
5646         {
5647            gens[j]=gens[j]/gg;
5648         }
5649         Gens = list(gens) + Gens;
5650
5651/*       ### Da die gens Algebra-Erzeuger sind, ist reduce nach Bestimmung
5652         der Algebra-Variablen T(i) nicht zulaessig!
5653         for(i=1;i<=size(gens)-1;i++)
5654         {
5655            gens[i]= reduce(gens[i],std(gens[size(gens)]));
5656         }
5657         for(i=size(gens)-1; i>=1; i--)
5658         {
5659            if(gens[i]==0)
5660            { gens = delete(gens,i); }
5661         }
5662*/
5663         if( defined(ker) ) { kill ker; }
5664      }
5665
5666      if ( del >= 0 )
5667      {
5668         int mul = iMult(prim);
5669         del = del + mul;
5670      }
5671      else
5672      { del = -1; }
5673      deli = deli[1..size(deli)-1];
5674      Resu = resu,Gens,list(deli,del);
5675      int sr = size(resu);
5676
5677      if ( dbg >= 0 )
5678      {"";
5679"// 'normalC' created a list, say nor, of three lists:
5680// To see the list type
5681      nor;
5682
5683// * nor[1] is a list of",sr,"ring(s)
5684// To access the i-th ring nor[1][i] give it a name, say Ri, and type e.g.
5685     def R1 = nor[1][1]; setring R1;  norid; normap;
5686// For the other rings type first (if R is the name of your original basering)
5687     setring R;
5688// and then continue as for R1.
5689// Ri/norid is the affine algebra of the normalization of the i-th
5690// component R/P_i (where P_i is an associated prime of the input ideal id)
5691// and normap the normalization map from R to Ri/norid.
5692
5693// * nor[2] is a list of",sr,"ideal(s), each ideal nor[2][i] consists of
5694// elements g1..gk of R such that the gj/gk generate the integral
5695// closure of R/P_i as sub-algebra in the quotient field of R/P_i, with
5696// gj/gk being mapped by normap to the j-th variable of Ri;
5697
5698// * nor[3] shows the delta-invariant of each component and of id
5699// (-1 means infinite, and 0 that R/P_i resp. R/id is normal).";
5700      }
5701      return(Resu);
5702   }
5703   //----------------- end method "withGens" --------------------------------
5704
5705//-------- The general case without computation of the generators -----------
5706// (attrib(id,"xy"),1) sets attrib xy to TRUE and (attrib(id,"xy"),0) to FALSE
5707// We use the following attributes:
5708//   attrib(id,"isCohenMacaulay");         //--- Cohen Macaulay
5709//   attrib(id,"isCompleteIntersection");  //--- complete intersection
5710//   attrib(id,"isHypersurface");          //--- hypersurface
5711//   attrib(id,"isEquidimensional",-1);    //--- equidimensional ideal
5712//   attrib(id,"isPrim");                  //--- prime ideal
5713//   attrib(id,"isRegInCodim2");           //--- regular in codimension 2
5714//   attrib(id,"isIsolatedSingularity";    //--- isolated singularities
5715//   attrib(id,"onlySingularAtZero");      //--- only singular at 0
5716
5717 //------------------- first set the attributes ----------------------
5718   if( typeof(attrib(id,"isCohenMacaulay"))=="int" )
5719   {
5720      if( attrib(id,"isCohenMacaulay")==1 )
5721      {
5722         attrib(id,"isEquidimensional",1);
5723      }
5724   }
5725   else
5726   {
5727      attrib(id,"isCohenMacaulay",0);
5728   }
5729
5730   if( typeof(attrib(id,"isCompleteIntersection"))=="int" )
5731   {
5732      if(attrib(id,"isCompleteIntersection")==1)
5733      {
5734         attrib(id,"isCohenMacaulay",1);
5735         attrib(id,"isEquidimensional",1);
5736      }
5737   }
5738   else
5739   {
5740      attrib(id,"isCompleteIntersection",0);
5741   }
5742
5743   if( typeof(attrib(id,"isHypersurface"))=="int" )
5744   {
5745      if(attrib(id,"isHypersurface")==1)
5746      {
5747         attrib(id,"isCompleteIntersection",1);
5748         attrib(id,"isCohenMacaulay",1);
5749         attrib(id,"isEquidimensional",1);
5750      }
5751   }
5752   else
5753   {
5754      attrib(id,"isHypersurface",0);
5755   }
5756
5757   if( ! (typeof(attrib(id,"isEquidimensional"))=="int") )
5758   {
5759         attrib(id,"isEquidimensional",0);
5760   }
5761
5762   if( typeof(attrib(id,"isPrim"))=="int" )
5763   {
5764      if(attrib(id,"isPrim")==1)
5765      {
5766         attrib(id,"isEquidimensional",1);
5767      }
5768   }
5769   else
5770   {
5771      attrib(id,"isPrim",0);
5772   }
5773
5774   if( ! (typeof(attrib(id,"isRegInCodim2"))=="int") )
5775   {
5776         attrib(id,"isRegInCodim2",0);
5777   }
5778
5779   if( ! (typeof(attrib(id,"isIsolatedSingularity"))=="int") )
5780   {
5781         attrib(id,"isIsolatedSingularity",0);
5782   }
5783
5784   if( typeof(attrib(id,"onlySingularAtZero"))=="int" )
5785   {
5786      if(attrib(id,"onlySingularAtZero")==1)
5787      {
5788         attrib(id,"isIsolatedSingularity",1);
5789      }
5790   }
5791   else
5792   {
5793      attrib(id,"onlySingularAtZero",0);
5794   }
5795
5796   //-------------- compute equidimensional decomposition --------------------
5797   //If the method "equidim" is given, compute the equidim decomposition
5798   //and goto the next step (no normalization
5799   //ACHTUNG: equidim berechnet bei nicht reduzierten id die eingebetteten
5800   //Komponenten als niederdim Komponenten, waehrend diese bei primdecGTZ
5801   //nicht auftauchen: ideal(x,y)*xy
5802   //this is default for nvars > 2
5803
5804   if( decomp == 2 )
5805   {
5806      withPrim = 0;                 //this is used to check later that prim
5807                                    //contains equidim but not prime components
5808      if( dbg >= 1 )
5809      {
5810         "// We use method 'equidim'";
5811      }
5812      if( typeof(attrib(id,"isEquidimensional"))=="int" )
5813      {
5814         if(attrib(id,"isEquidimensional")==1)
5815         {
5816            prim[1] = id;
5817         }
5818         else
5819         {
5820            prim = equidim(id);
5821         }
5822      }
5823      else
5824      {
5825         prim = equidim(id);
5826      }
5827      if(dbg>=1)
5828      {  "";
5829         "// number of equidimensional components:", size(prim);
5830      }
5831      if ( !noFac )
5832      {
5833        intvec opt = option(get);
5834        option(redSB);
5835        for(j=1; j<=size(prim); j++)
5836        {
5837           keepresult = keepresult+facstd(prim[j]);
5838        }
5839        prim = keepresult;
5840        if ( size(prim) == 0 )
5841        {
5842          prim=ideal(0);     //Bug in facstd, liefert leere Liste bei 0-Ideal
5843        }
5844
5845        if(dbg>=1)
5846        {  "";
5847         "// number of components after application of facstd:", size(prim);
5848        }
5849        option(set,opt);
5850      }
5851   }
5852
5853   //------------------- compute associated primes -------------------------
5854   //the case where withEqui = 0, here the min. ass. primes are computed
5855   //start with the computation of the minimal associated primes:
5856
5857   else
5858   {
5859    if( isPrim )
5860    {
5861      if( dbg >= 0 )
5862      {
5863         "// ** WARNING: result is correct if ideal is prime";
5864         "// or equidimensional (not checked) **";
5865         "// disable option \"isPrim\" to decompose ideal into prime";
5866         "// or equidimensional components";"";
5867      }
5868      if( dbg >= 1 )
5869      {
5870        "// We use method 'isPrim'";"";
5871      }
5872      prim[1]=id;
5873    }
5874    else
5875    {
5876      withPrim = 1;                 //this is used to check later that prim
5877                                    //contains prime but not equidim components
5878      if( dbg >= 1 )
5879      {
5880         "// We use method 'prim'";
5881      }
5882
5883      if( typeof(attrib(id,"isPrim"))=="int" )
5884      {
5885         if(attrib(id,"isPrim")==1)
5886         {
5887            prim[1]=id;
5888         }
5889         else
5890         {
5891            if( noFac )
5892            { prim=minAssGTZ(id,1); }     //does not use factorizing groebner
5893            else
5894            { prim=minAssGTZ(id); }       //uses factorizing groebner
5895         }
5896      }
5897      else
5898      {
5899            if( noFac )
5900            { prim=minAssGTZ(id,1); }
5901            else
5902            { prim=minAssGTZ(id); }
5903      }
5904      if(dbg>=1)
5905      {  "";
5906         "// number of irreducible components:", size(prim);
5907      }
5908    }
5909   }
5910
5911   //----- for each component (equidim or irred) compute normalization -----
5912   int sr, skr, del;
5913   intvec deli;
5914   int sp = size(prim);     //size of list prim (# irred or equidim comp)
5915
5916   for(i=1; i<=sp; i++)
5917   {
5918      if(dbg>=1)
5919      {  "";
5920         "// computing the normalization of component",i;
5921         "   ----------------------------------------";
5922      }
5923      //-------------- first set attributes for components ------------------
5924      attrib(prim[i],"isEquidimensional",1);
5925      if( withPrim )
5926      {
5927         attrib(prim[i],"isPrim",1);
5928      }
5929      else
5930      { attrib(prim[i],"isPrim",0); }
5931
5932      if(attrib(id,"onlySingularAtZero")==1)
5933      { attrib(prim[i],"onlySingularAtZero",1); }
5934      else
5935      { attrib(prim[i],"onlySingularAtZero",0); }
5936
5937      if(attrib(id,"isIsolatedSingularity")==1)
5938      { attrib(prim[i],"isIsolatedSingularity",1); }
5939      else
5940      { attrib(prim[i],"isIsolatedSingularity",0); }
5941
5942      if( attrib(id,"isHypersurface")==1 )
5943      {
5944         attrib(prim[i],"isHypersurface",1);
5945         attrib(prim[i],"isCompleteIntersection",1);
5946         attrib(prim[i],"isCohenMacaulay",1);
5947      }
5948      else
5949      { attrib(prim[i],"isHypersurface",0); }
5950
5951      if ( sp == 1)         //the case of one component: copy attribs from id
5952      {
5953        if(attrib(id,"isRegInCodim2")==1)
5954        {attrib(prim[i],"isRegInCodim2",1); }
5955        else
5956        {attrib(prim[i],"isRegInCodim2",0); }
5957
5958        if(attrib(id,"isCohenMacaulay")==1)
5959        {attrib(prim[i],"isCohenMacaulay",1); }
5960        else
5961        {attrib(prim[i],"isCohenMacaulay",0); }
5962
5963        if(attrib(id,"isCompleteIntersection")==1)
5964        {attrib(prim[i],"isCompleteIntersection",1); }
5965        else
5966        {attrib(prim[i],"isCompleteIntersection",0); }
5967      }
5968      else
5969      {
5970        attrib(prim[i],"isRegInCodim2",0);
5971        attrib(prim[i],"isCohenMacaulay",0);
5972        attrib(prim[i],"isCompleteIntersection",0);
5973      }
5974
5975      //------ Now compute the normalization of each component ---------
5976      //note: for equidimensional components the "splitting tools" can
5977      //create further decomposition
5978      //We now start normalizationPrimes with
5979      //ihp = partial normalisation map = identity map = maxideal(1)
5980      //del = partial delta invariant = 0
5981      //deli= intvec of partial delta invariants of components
5982      //in normalizationPrimes all the work is done:
5983
5984      keepresult = normalizationPrimes(prim[i],maxideal(1),0,0);
5985
5986      for(j=1; j<=size(keepresult)-1; j++)
5987      {
5988         result=insert(result,keepresult[j]);
5989      }
5990      skr = size(keepresult);
5991
5992      //compute delta:
5993      if( del >= 0 && keepresult[skr][1] >=0 )
5994      {
5995         del = del + keepresult[skr][1];
5996      }
5997      else
5998      {
5999         del = -1;
6000      }
6001      deli = keepresult[skr][2],deli;
6002
6003      if ( dbg>=1 )
6004      {
6005           "// delta of component",i; keepresult[skr][1];
6006      }
6007   }
6008   sr = size(result);
6009
6010   // -------------- Now compute intersection multiplicities -------------
6011   //intersection multiplicities of list prim, sp=size(prim).
6012      if ( dbg>=1 )
6013      {
6014        "// Sum of delta for all components"; del;
6015        if ( sp>1 )
6016        {
6017           "// Compute intersection multiplicities of the components";
6018        }
6019      }
6020
6021      if ( sp > 1 )
6022      {
6023        int mul = iMult(prim);
6024        if ( mul < 0 )
6025        {
6026           del = -1;
6027        }
6028        else
6029        {
6030           del = del + mul;
6031        }
6032      }
6033   deli = deli[1..size(deli)-1];
6034   result = result,list(deli,del);
6035
6036//--------------- Finally print comments and return ------------------
6037   if ( dbg >= 0)
6038   {"";
6039"// 'normalC' created a list, say nor, of two lists:
6040// To see the result, type
6041      nor;
6042
6043// * nor[1] is a list of",sr,"ring(s).
6044// To access the i-th ring nor[1][i] give it a name, say Ri, and type e.g.
6045      def R1 = nor[1][1];  setring R1;  norid;  normap;
6046// and similair for the other rings nor[1][i];
6047// Ri/norid is the affine algebra of the normalization of r/P_i  (where P_i
6048// is an associated prime or an equidimensional part of the input ideal id)
6049// and normap the normalization map from the basering to Ri/norid;
6050
6051// * nor[2] shows the delta-invariant of each component and of id
6052// (-1 means infinite, 0 that r/P_i resp. r/id is normal, and -2 that delta
6053// of a component was not computed).";
6054   }
6055   return(result);
6056}
6057
6058example
6059{ "EXAMPLE:";
6060   printlevel = printlevel+1;
6061   echo = 2;
6062   ring s = 0,(x,y),dp;
6063   ideal i = (x2-y3)*(x2+y2)*x;
6064
6065   list nor = normalC(i);
6066
6067   nor;
6068   // 2 branches have delta = 1, and 1 branch has delta = 0
6069   // the total delta invariant is 13
6070
6071   def R2 = nor[1][2];  setring R2;
6072   norid; normap;
6073
6074   echo = 0;
6075   printlevel = printlevel-1;
6076   pause("   hit return to continue"); echo=2;
6077
6078   ring r = 2,(x,y,z),dp;
6079   ideal i = z3-xy4;
6080   nor = normalC(i);  nor;
6081   // the delta invariant is infinite
6082   // xy2z/z2 and xy3/z2 generate the integral closure of r/i as r/i-module
6083   // in its quotient field Quot(r/i)
6084
6085   // the normalization as affine algebra over the ground field:
6086   def R = nor[1][1]; setring R;
6087   norid; normap;
6088
6089   echo = 0;
6090   pause("   hit return to continue");echo = 2;
6091
6092   setring r;
6093   nor = normalC(i, "withGens", "prim");    // a different algorithm
6094   nor;
6095}
6096
6097//////////////////////////////////////////////////////////////////////////////
6098//closureRingtower seems not to be used anywhere
6099static proc closureRingtower(list L)
6100"USAGE:    closureRingtower(list L); L a list of rings
6101CREATE:   rings R(1),...,R(n) such that R(i)=L[i] for all i
6102EXAMPLE:  example closureRingtower; shows an example
6103"
6104{
6105  int n=size(L);
6106  for (int i=1;i<=n;i++)
6107    {
6108      if (defined(R(i)))
6109      {
6110        string s="Fixed name R("+string(i)+") leads to conflict with existing "
6111              +"object having this name";
6112        ERROR(s);
6113      }
6114      def R(i)=L[i];
6115      export R(i);
6116    }
6117
6118  return();
6119}
6120example
6121{
6122  "EXAMPLE:"; echo=2;
6123  ring R=0,(x,y),dp;
6124  ideal I=x4,y4;
6125  list L=primeClosure(ReesAlgebra(I)[1]);
6126  L=delete(L,size(L));
6127  L;
6128  closureRingtower(L);
6129  R(1);
6130  R(4);
6131  kill R(1),R(2),R(3),R(4);
6132}
6133
6134//                Up to here: procedures for normalC
6135///////////////////////////////////////////////////////////////////////////////
6136
6137///////////////////////////////////////////////////////////////////////////////
6138//                From here: miscellaneous procedures
6139
6140// Used for timing and comparing the different normalization procedures.
6141// Option (can be entered in any order)
6142// "normal"   -> uses the new algortihm (normal)
6143// "normalP"  -> uses normalP
6144// "normalC"  -> uses normalC, without "withGens" option
6145// "primCl"   -> uses normalC, with option "withGens".
6146// "111"      -> checks the output of normalM using norTest.
6147// "p"        -> compares the output of norM with the output of normalP
6148//               ("normalP" option must also be set).
6149// "pc"       -> compares the output of norM with the output of normalC with
6150//               option "withGens"
6151//               ("primCl" option must also be set).
6152
6153proc timeNormal(ideal I, list #)
6154{
6155  def r = basering;
6156
6157  //--------------------------- define the method ---------------------------
6158  int isPrim, useRing;
6159  int decomp = -1;
6160  int norM, norC, norP, primCl;
6161  int checkP, check111, checkPC;
6162  int i;
6163  ideal U1, U2, W;
6164  poly c1, c2;
6165  int ch;
6166  string check;
6167  string method;                //make all options one string in order to use
6168                                //all combinations of options simultaneously
6169  for ( i=1; i <= size(#); i++ )
6170  {
6171    if ( typeof(#[i]) == "string" )
6172    {
6173      method = method + #[i];
6174    }
6175  }
6176  if ( find(method, "normal"))
6177  {norM = 1;}
6178  if ( find(method, "normalP") and (char(basering) > 0))
6179  {norP = 1;}
6180  if ( find(method, "normalC"))
6181  {norC = 1;}
6182  if ( find(method, "primCl"))
6183  {primCl = 1;}
6184  if ( find(method, "isprim") or find(method,"isPrim") )
6185  {decomp = 0;}
6186  if ( find(method, "p") )
6187  {checkP = 1;}
6188  if ( find(method, "pc") )
6189  {checkPC = 1;}
6190  if ( find(method, "111") )
6191  {check111 = 1;}
6192
6193  int tt;
6194  if(norM)
6195  {
6196    tt = timer;
6197    if(decomp == 0)
6198    {
6199      "Running normal(useRing, isPrim)...";
6200      list a1 = normal(I, "useRing", "isPrim");
6201      "Time normal(useRing, isPrim): ", timer - tt;
6202    }
6203    else
6204    {
6205      "Running normal(useRing)...";
6206      list a1 = normal(I, "useRing");
6207      "Time normal(useRing): ", timer - tt;
6208    }
6209    "";
6210  }
6211  if(norP)
6212  {
6213    tt = timer;
6214    if(decomp == 0)
6215    {
6216      "Running normalP(isPrim)...";
6217      list a2 = normalP(I, "isPrim");
6218      "Time normalP(isPrim): ", timer - tt;
6219    }
6220    else
6221    {
6222      "Running normalP()...";
6223      list a2 = normalP(I);
6224      "Time normalP(): ", timer - tt;
6225    }
6226    "";
6227  }
6228
6229  if(norC)
6230  {
6231    tt = timer;
6232    if(decomp == 0)
6233    {
6234      "Running normalC(isPrim)...";
6235      list a3 = normalC(I, "isPrim");
6236      "Time normalC(isPrim): ", timer - tt;
6237    }
6238    else
6239    {
6240      "Running normalC()...";
6241      list a3 = normalC(I);
6242      "Time normalC(): ", timer - tt;
6243    }
6244    "";
6245  }
6246
6247  if(primCl)
6248  {
6249    tt = timer;
6250    if(decomp == 0)
6251    {
6252      "Running normalC(withGens, isPrim)...";
6253      list a4 = normalC(I, "isPrim", "withGens");
6254      "Time normalC(withGens, isPrim): ", timer - tt;
6255    }
6256    else
6257    {
6258      "Running normalC(withGens)...";
6259      list a4 = normalC(I, "withGens");
6260      "Time normalC(withGens): ", timer - tt;
6261    }
6262    "";
6263  }
6264
6265  if(check111 and norM)
6266  {
6267    "Checking output with norTest...";
6268    "WARNING: this checking only works if the original ideal was prime.";
6269    norTest(I, a1);
6270    "";
6271  }
6272
6273  if(checkP and norP and norM)
6274  {
6275    "Comparing with normalP output...";
6276    if(size(a2) > 0)
6277    {
6278      "WARNING: this checking only works if the original ideal was prime.";
6279      U1 = a1[2][1];
6280      c1 = U1[size(U1)];
6281      U2 = a2[1][1];
6282      c2 = a2[1][1][size(a2[1][1])];
6283      W = changeDenominator(U1, c1, c2, groebner(I));
6284      qring q = groebner(I);
6285      ideal U2 = fetch(r, U2);
6286      ideal W = fetch(r, W);
6287      ch = 0;
6288      if(size(reduce(U2, groebner(W))) == 0)
6289      {
6290        "U2 c U1";
6291        ch = 1;
6292      }
6293      if(size(reduce(W, groebner(U2))) == 0)
6294      {
6295        "U1 c U2";
6296        ch = ch + 1;
6297      }
6298      if(ch == 2)
6299      {
6300        "Output of normalP is equal.";
6301      }
6302      else
6303      {
6304        "ERROR: Output of normalP is different.";
6305      }
6306      setring r;
6307      kill q;
6308    }
6309    else
6310    {
6311      "normalP returned no output. Comparison is not possible.";
6312    }
6313    "";
6314  }
6315
6316  if(checkPC and norM and primCl)
6317  {
6318    "Comparing with primeClosure output...";
6319    if(size(a4) > 0)
6320    {
6321      "WARNING: this checking only works if the original ideal was prime.";
6322      // primeClosure check
6323      U1 = a1[2][1];
6324      c1 = U1[size(U1)];
6325      U2 = a4[2][1];
6326      c2 = a4[2][1][size(a4[2][1])];
6327      W = changeDenominator(U1, c1, c2, groebner(I));
6328      qring q = groebner(I);
6329      ideal U2 = fetch(r, U2);
6330      ideal W = fetch(r, W);
6331      ch = 0;
6332      if(size(reduce(U2, groebner(W))) == 0)
6333      {
6334        "U2 c U1";
6335        ch = 1;
6336      }
6337      if(size(reduce(W, groebner(U2))) == 0)
6338      {
6339        "U1 c U2";
6340        ch = ch + 1;
6341      }
6342      if(ch == 2)
6343      {
6344        "Output of normalC(withGens) is equal.";
6345      }
6346      else
6347      {
6348        "ERROR: Output of normalC(withGens) is different.";
6349      }
6350      setring r;
6351      kill q;
6352    }
6353    else
6354    {
6355      "normalC(withGens) returned no output. Comparison is not possible.";
6356    }
6357    "";
6358  }
6359}
6360
6361///////////////////////////////////////////////////////////////////////////
6362static proc sqroot(int n);
6363{
6364  int s = 1;
6365  while(s*s < n) { s++; }
6366  return(s);
6367}
6368
6369///////////////////////////////////////////////////////////////////////////
6370proc norTest (ideal i, list nor, list #)
6371"USAGE:   norTest(i,nor,[n]); i=prime ideal, nor=list, n=optional integer
6372ASSUME:  nor is the output of normal(i) (any options) or
6373         normalP(i,"withRing") or normalC(i) (any options).
6374         In particular, the ring nor[1][1] contains the ideal norid
6375         and the map normap: basering/i --> nor[1][1]/norid.
6376RETURN:  an intvec v such that:
6377@format
6378         v[1] = 1 if the normap is injective and 0 otherwise
6379         v[2] = 1 if the normap is finite and 0 otherwise
6380         v[3] = 1 if nor[1][1]/norid is normal and 0 otherwise
6381@end format
6382         If n=1 (resp n=2) only v[1] (resp. v[2]) is computed and returned
6383THEORY:  The procedure can be used to test whether the computation of the
6384         normalization was correct: basering/i --> nor[1][1]/norid is the
6385         normalization of basering/i if and only if v=1,1,0.
6386NOTE:    For big examples it can be hard to fully test correctness; the
6387         partial test norTest(i,nor,2) is usually fast
6388EXAMPLE: example norTest; shows an example
6389"
6390{
6391//### Sollte erweitert werden auf den reduziblen Fall: einen neuen affinen
6392// Ring nor[1][1]+...+nor[1][r] (direkte Summe) erzeugen, map dorthin
6393// definieren und dann testen.
6394
6395    int prl = printlevel - voice + 2;
6396    int a,b,d;
6397    int n,ii;
6398    if (size(#) > 0) {  n = #[1];  }
6399
6400    def BAS = basering;
6401
6402    //### make a copy of nor to have a cpoy of nor[1][1]  (not a reference to)
6403    // in order not to override norid and normap.
6404    // delete nor[2] (if it contains the module generators, which are not used)
6405    // s.t. newnor does not belong to a ring.
6406
6407    list newnor = nor;
6408    if ( size(newnor) == 3 )
6409    {
6410       newnor = delete(newnor,2);
6411    }
6412    def R = newnor[1][1];
6413    qring QAS = std(i);
6414
6415
6416    setring R;
6417    int nva = nvars(R);
6418    string svars = varstr(R);
6419    string svar;
6420
6421    norid = interred(norid);
6422
6423    //--------- create new ring with one dp block keeping weights ------------
6424    list LR = ringlist(R);
6425    list g3 = LR[3];
6426    int n3 = size(g3);
6427    list newg3;
6428    intvec V;
6429
6430    //--------- check first whether variables Z(i),...,A(i) exist -----------
6431    for (ii=90; ii>=65; ii--)
6432    {
6433       if ( find(svars,ASCII(ii)+"(") == 0 )
6434       {
6435          svar = ASCII(ii);  break;
6436       }
6437    }
6438    if ( size(svar) != 0 )
6439    {
6440        for ( ii = 1; ii <= nva; ii++ )
6441        {
6442            LR[2][ii] = svar+"("+string(ii)+")";
6443            V[ii] = 1;
6444        }
6445    }
6446    else
6447    {
6448        for ( ii = 1; ii <= nva; ii++ )
6449        {
6450           LR[2][ii] = "Z("+string(100*nva+ii)+")";
6451           V[ii] = 1;
6452        }
6453    }
6454
6455    if ( g3[n3][1]== "c" or g3[n3][1] == "C" )
6456    {
6457       list gm = g3[n3];       //last blockis module ordering
6458       newg3[1] = list("dp",V);
6459       newg3 = insert(newg3,gm,size(newg3));
6460    }
6461    else
6462    {
6463       list gm = g3[1];              //first block is module ordering
6464       newg3[1] = list("dp",V);
6465       newg3 = insert(newg3,gm);
6466    }
6467    LR[3] = newg3;
6468//LR;"";
6469    def newR = ring(LR);
6470
6471    setring newR;
6472    ideal norid = fetch(R,norid);
6473    ideal normap = fetch(R,normap);
6474    if( defined(lnorid) )  { kill lnorid; }     //um ** redefinig zu beheben
6475    if( defined(snorid) )  { kill snorid; }     //sollte nicht noetig sein
6476
6477    //----------- go to quotient ring for checking injectivity -------------
6478//"mstd";
6479    list lnorid = mstd(norid);
6480    ideal snorid = lnorid[1];
6481//"size mstdnorid:", size(snorid),size(lnorid[2]);
6482//"size string mstdnorid:", size(string(snorid)),size(string(lnorid[2]));
6483    qring QR = snorid;
6484    ideal qnormap = fetch(newR,normap);
6485    //ideal qnormap = imap(newR,normap);
6486    //ideal qnormap = imap(R,normap);
6487    map Qnormap = QAS,qnormap;    //r/id --> R/norid
6488
6489    //------------------------ check injectivity ---------------------------
6490//"injective:";
6491    a = is_injective(Qnormap,QAS);          //a. Test for injectivity of Qnormap
6492    dbprint ( prl, "injective: "+string(a) );
6493    if ( n==1 ) { return (a); }
6494   a;
6495
6496    //------------------------ check finiteness ---------------------------
6497    setring newR;
6498    b = mapIsFinite(normap,BAS,lnorid[2]);  //b. Test for finiteness of normap
6499    dbprint ( prl, "finite: "+string(b) );
6500    if ( n==2 ) { return (intvec(a,b)); }
6501   b;
6502
6503    //------------------------ check normality ---------------------------
6504    list testnor = normal(lnorid[2],"isPrim","noFac", "withDelta");
6505    //### Problem: bei mehrfachem Aufruf von norTest gibt es
6506    // ** redefining norid & ** redefining normap
6507    //Dies produziert Fehler, da alte norid und normap ueberschrieben werden
6508    //norid und normap werden innnerhalb von proc computeRing ueberschrieben
6509    //Die Kopie newR scheint das Problem zu loesen
6510
6511    printlevel=prl;
6512
6513    d = testnor[3][2];             //d = delta
6514    kill testnor;                              //### sollte ueberfluessig sein
6515    int d1 = (d==0);                           //d1=1 if delta=0
6516    dbprint ( prl, "delta: "+string(d) );
6517    return(intvec(a,b,d1));
6518}
6519example
6520{ "EXAMPLE:"; echo = 2;
6521   int prl = printlevel;
6522   printlevel = -1;
6523   ring r = 0,(x,y),dp;
6524   ideal i = (x-y^2)^2 - y*x^3;
6525   list nor = normal(i);
6526   norTest(i,nor);                //1,1,1 means that normal was correct
6527
6528   nor = normalC(i);
6529   norTest(i,nor);                //1,1,1 means that normal was correct
6530
6531   ring s = 2,(x,y),dp;
6532   ideal i = (x-y^2)^2 - y*x^3;
6533   nor = normalP(i,"withRing");
6534   norTest(i,nor);               //1,1,1 means that normalP was correct
6535   printlevel = prl;
6536}
6537
6538///////////////////////////////////////////////////////////////////////////
6539//
6540//                            EXAMPLES
6541//
6542///////////////////////////////////////////////////////////////////////////
6543/*
6544//commands for computing the normalization:
6545// options for normal:  "equidim", "prim"
6546//                      "noDeco", "isPrim", "noFac"
6547//                       (prim by default)
6548// options for normalP: "withRing", "isPrim" or "noFac"
6549// options for normalC: "equidim", "prim", "withGens",
6550//                      "noDeco", "isPrim", "noFac"
6551
6552//Commands for testing 'normal'
6553 list nor = normal(i); nor;
6554 list nor = normal(i,"isPrim");nor;
6555 list nor = normal(i,"equidim");nor;
6556 list nor = normal(i,"prim");nor;
6557 list nor = normal(i,"equidim","noFac");nor;
6558 list nor = normal(i,"prim","noFac");nor;
6559
6560//Commands for testing 'normalP' in positive char
6561 list nor = normalP(i);nor;              //withGens but no ringstructure
6562 list nor = normalP(i,"withRing"); nor;  //compute the ringstructure
6563 list nor = normalP(i,"isPrim"); nor;    //if i is known to be prime
6564
6565//Commands for testing 'normalC'
6566 list nor = normal(i); nor;
6567 list nor = normal(i,"withGens");nor;
6568 list nor = normal(i,"isPrim");nor;
6569 list nor = normal(i,"equidim");nor;
6570 list nor = normal(i,"prim");nor;
6571 list nor = normal(i,"equidim","noFac");nor;
6572 list nor = normal(i,"prim","noFac");nor;
6573
6574//Commands for testing correctness (i must be prime):
6575list nor = normalP(i,"withRing","isPrim");
6576list nor = normal(i,"isPrim");
6577norTest(i,nor);       //full test for not too big examples (1,1,1 => ok)
6578norTest(i,nor,2);     //partial test for big examples (1,1 => ok)
6579factorize(i[1]);      //checks for irreducibility
6580
6581/////////////////////////////////////////////////////////////////////////////
6582
6583//----------------------Examples for normal (new algorithm)------------------
6584// Timings with Computeserver Dual AMD Opteron 242 1.60GHz.
6585// Examples from "Normalization of Rings" paper.
6586
6587// Example 1
6588// char 0 : normal = 0 secs (7 steps) - normalC = 75 secs
6589// char 2 : normal = 0 secs (7 steps) - normalP = 0 secs - normalC = 0 secs
6590// char 5 : normal = 1 secs (7 steps) - normalP = 71 - normalC = 1 secs
6591// char 11 : normal = 2 secs (7 steps) - normalP = 12 secs - normalC doesn't finish
6592// char 32003 : normal = 1 secs (7 steps) - normalP doesn't finish - normalC = 1 sec
6593LIB"normal.lib";
6594ring r = 2, (x, y), dp;
6595ideal i = (x-y)*x*(y+x^2)^3-y^3*(x^3+x*y-y^2);
6596timeNormal(i, "normal", "normalC", "normalP", "isPrim", "p");
6597
6598// Example 2
6599// char 0  : normal = 1 sec (7 steps) - normalC doesn't finish
6600// char 3 : normal = 1 secs (8 steps) - normalP = 0 secs - normalC = 4 secs
6601// char 13 : normal = 1 sec (7 steps) - normalP doesn't finish - normalC = 13 secs
6602// char 32003 : normal = 1 secs (7 steps) - normalP doesn't finish - normalC = 10 sec
6603//Example is reducible in char 5 and 7
6604LIB"normal.lib";
6605ring r = 3, (x, y), dp;
6606ideal i = 55*x^8+66*y^2*x^9+837*x^2*y^6-75*y^4*x^2-70*y^6-97*y^7*x^2;
6607timeNormal(i, "normal", "normalC", "normalP", "p", "isPrim");
6608
6609// Example 3
6610// char 0 : normal = 3 secs (6 steps) - normalC doesn't finish
6611// char 2 : normal = 1 secs (13 steps) - normalP = 0 secs - normalC doesn't finish
6612// char 5 : normal = 0 secs (6 steps) - normalP = 8 secs - normalC doesn't finish
6613LIB"normal.lib";
6614ring r=5,(x, y),dp;
6615ideal i=y9+y8x+y8+y5+y4x+y3x2+y2x3+yx8+x9;
6616timeNormal(i, "normal", "normalC", "normalP", "isPrim");
6617
6618// Example 4
6619// char 0 : normal = 0 secs (1 step) - normalC = 0 secs
6620// char 5 : normal = 0 secs (1 step) - normalP = 3 secs - normalC = 0 secs
6621// char 11 : normal = 0 secs (1 step) - normalP doesn't finish - normalC = 0 secs
6622// char 32003 : normal = 0 secs (1 step) - normalP doesn't finish - normalC = 0 secs
6623LIB"normal.lib";
6624ring r=5,(x,y),dp;   // genus 0 4 nodes and 6 cusps im P2
6625ideal i=(x2+y^2-1)^3 +27x2y2;
6626timeNormal(i, "normal", "normalC", "normalP", "isPrim");
6627
6628// Example 5
6629// char 0 : normal = 0 secs (1 step) - normalC = 0 secs
6630// char 5 : normal = 1 secs (3 step) - normalP doesn't finish - normalC doesn't finish
6631// char 11 : normal = 0 secs (1 step) - normalP 0 secs - normalC = 0 secs
6632// char 32003 : normal = 0 secs (1 step) - normalP doesn't finish - normalC = 0 secs
6633LIB"normal.lib";
6634ring r=11,(x,y),dp;    //24 sing, delta 24
6635ideal i=-x10+x8y2-x6y4-x2y8+2y10-x8+2x6y2+x4y4-x2y6-y8+2x6-x4y2+x2y4+2x4+2x2y2-y4-x2+y2-1;
6636timeNormal(i, "normal", "normalC", "normalP", "isPrim", "p");
6637
6638// Example 6
6639// char 2 : normal = 5 secs (2 steps) - normalP = 25 secs - normalC = 166 secs
6640LIB"normal.lib";
6641ring r=2,(v,u,z,y,x),dp;
6642ideal i = z3+zyx+y3x2+y2x3, uyx+z2,uz+z+y2x+yx2, u2+u+zy+zx, v3+vux+vz2+vzyx+vzx+uz3+uz2y+z3+z2yx2;
6643timeNormal(i, "normal", "normalC", "normalP", "isPrim", "p");
6644
6645// Example 7
6646// char 0 : normal = 11 secs (6 steps) - normalC = 11 secs
6647// char 2 : normal = 11 secs (6 steps) - normalP = 0 secs - normalC = 11 secs
6648// char 5 : normal = 11 secs (6 steps) - normalP = 3 secs - normalC = 11 secs
6649// char 11 : normal = 11 secs (6 steps) - normalP = 43 secs - normalC = 11 secs
6650// char 32003 : normal = 11 secs (6 steps) - normalP doesn't finish - normalC = 11 secs
6651LIB"normal.lib";
6652ring r=11,(x,y,z,w,t),dp;   //dim 2, dim s_locus 1
6653ideal i= x2+zw, y3+xwt, xw3+z3t+ywt2, y2w4-xy2z2t-w3t3;
6654timeNormal(i, "normal", "normalC", "normalP", "isPrim");
6655
6656////////////////////////////////////////////////////////////////////////////////
6657
6658// Other examples with new algorithm
6659
6660// Example 1
6661// char 0 : normal = 1 secs (13 steps) - normalC doesn't finish
6662// char 2 : normal = 1 secs (13 steps) - normalP = 0 secs - normalC doesn't finish
6663// char 5 : normal = 1 secs (13 steps) - normalP = 29 secs - normalC doesn't finish
6664ring r=2,(x,y),dp;  //genus 35
6665ideal i=y30+y13x+x4y5+x3*(x+1)^2;
6666timeNormal(i, "normal", "normalC", "normalP");
6667
6668// Example 2
6669// char 0 : normal = 1 secs (13 steps) - normalC doesn't finish
6670// char 3 : normal = 2 secs (13 steps) - normalP = 0 secs - normalC doesn't finish
6671ring r=3,(x,y),dp;  //genus 19, delta 21
6672ideal i=y20+y13x+x4y5+x3*(x+1)^2;
6673timeNormal(i, "normal", "normalC", "normalP");
6674
6675// Example 3
6676// Very fast with all algorithms
6677ring r = 3, (x, y), dp;
6678ideal I = (x-y^2)^2-x*y^3;
6679timeNormal(I, "normal", "normalC", "normalP", "primCl", "111", "p", "pc");
6680
6681
6682
6683//----------------------Test Example for charp -------------------
6684//Zu tun:
6685//### nach minor nur std statt mstd verwenden
6686//***hat bei keinem Beisp etwas gebracht -> wieder zurueck
6687//### wenn interred ok, dann wieder einsetzen (am Schluss)
6688//### bottelnecks bei maps beheben
6689//### minor verbessern
6690//### preimage verbessern (Ist imm Kern map oder imap verwendet?)
6691//### Gleich in Ordnung dp wechseln, ringlist verwenden
6692//### interred ev nur zum Schluss
6693//    (z.B. wenn nacher std; wenn nacher minor: testen )
6694
6695//Zeiten mit normalV5.lib (mstd aktiv, interred inaktiv)
6696
6697//SWANSON EXAMPLES: (Macaulay2, icFracP=normalP, icFractions<->normal)
6698//---------------------------------------------------------------------
6699//1. Series Fp[x,y,u,v]/(x2v-y2u)
6700//-------------------------------
6701//characteristic p   2   3    5    7    11   13   17   37   97
6702//icFracP          0.04 0.03 0.04 0.04 0.04 0.05 0.05 0.13 0.59  Mac
6703//normalP           0   0    0    0     0    0    0    0   1    Sing
6704//icFractions      0.08 0.09 0.09 0.09 0.14 0.15 0.15 0.15 0.15  Mac
6705//normal             0   0    0    0     0    0    0    0    0   Sing
6706
67072. Series Fp[u, v, w, x, y, z]/u2x4+uvy4+v2z4
6708//--------------------------------------------
6709//characteristic p 2    3    5    7   11
6710//icFracP         0.07 0.22 9.67 143 12543
6711//normalP          0    0    5   42  1566
6712//icFractions     1.16   *    *   *    *       *: > 6h
6713//normal            0    0    0   0    0
6714
6715//3. Series Fp[u, v, w, x, y, z]/(u2xp+uvyp+v2zp)
6716//-----------------------------------------------
6717//characteristic p  2    3    5    7    11   13  17 19 23
6718//icFracP          0.06 0.07 0.09 0.27 1.81 4.89 26 56 225
6719//normalP          0     0    0    0    1    2  6  10  27
6720//icFractions      0.16 1.49 75.00 4009 *    *   *  *  *
6721//normal            0     0    2   836
6722//normal(neu)       0     0    1   2    10  155
6723//### p=7 normal braucht 807 sec in:
6724// ideal endid  = phi1(endid);      //### bottelneck'
6725
6726//1.
6727int p = 2;  ring r = p,(u,v,x,y,z),dp; ideal i = x2v-y2u;
6728//2.
6729int p = 7; ring r=p,(u,v,w,x,y,z),dp; ideal i=u2x4+uvy4+v2z4;
6730//3.
6731int p=11; ring r=p,(u,v,w,x,y,z),dp; ideal i=u2*x^p+uv*y^p+v2*z^p;
6732
6733//IRREDUCIBLE EXAMPLES:
6734//---------------------
6735//timing for MacBookPro 2.2GHz Intel Core 2 Duo, 4GB Ram
6736//Sing. ix86Mac-darwin version 3-1-0 (3100-2008101314)  Oct 13 2008 14:46:59
6737//if no time is given: < 1  sec
6738
6739//Apply:
6740list nor = normal(i,"isPrim"); nor;
6741list nor = normalP(i,"withRing","isPrim"); nor;
6742def R=nor[1][1]; setring R; norid; normap;
6743setring r;
6744norTest(i,nor);
6745
6746int tt = timer;
6747list nor = normalP(i,"withRing","isPrim"); nor;
6748timer-tt;
6749int tt = timer;
6750list nor = normal(i,"isPrim");
6751timer-tt;
6752
6753ring r=19,(x,y,u,v),dp;    //delta -1
6754ideal i=x2v-y2u;
6755//norTest 2 sec
6756
6757ring r=2,(y,x2,x1),lp;     //delta -1
6758ideal i=y^4+y^2*x2*x1+x2^3*x1^2+x2^2*x1^3;
6759//### norid hat 1 Element nach interred
6760
6761ring r  = 11,(x,y,z),wp(2,1,2); //alles < 1 sec
6762ideal i=z3 - xy4 + x2;          //not reduced, delta =0 ok
6763ideal i=y4+x5+y2x;              //not reduced, delta -1
6764//interred verkleinert norid
6765
6766ring r=3,(u,v,x,y,z),dp;   //delta -1
6767ideal i=u2x3+uvy3+v2z3;
6768
6769ring r=3,(u,v,x,y,z),dp;   //delta -1
6770ideal i=u2x4+uvy4+v2z4;
6771//norTest(i,nor);  0 sec, norTest(i,nor) haengt!
6772
6773ring r=5,(u,v,x,y,z),dp;   //delta -1
6774ideal i=u2x6+uvy6+v2z6;
6775//normalP 5sec, normalC 1sec
6776//V5: norTest(i,nor); 45 sec bei normalP, V6 12 sec
6777//28 sec bei normal
6778
6779ring r=5,(u,v,x,y,z),dp;   //delta -1
6780ideal i=u2x5+uvy5+v2z5;
6781//normalP 1sec, normalC 1 sec,
6782//norTest lange: minor(jacob(I),h,J) 193 (308)sec, haengt dann bei M = std(M);
6783//norTest(i,nor,2); verwenden!
6784//Sing 3.0-4 orig  >9h! haengt bei Q = mstd(Q)[2];
6785
6786ring r=2,(y,x),wp(12,5);  //delta 3
6787ideal i=y5+y2x4+y2x+yx2+x12;
6788//normalP 0 sec (Test 0 sec), normalC 2 sec (Test 2 sec)
6789//normalC withGens (ohne interred) 0sec
6790
6791ring r=2,(y,x),dp;       //delta= 22
6792ideal i=y9+y8x+y8+y5+y4x+y3x2+y2x3+yx8+x9;
6793//normalP 1sec, interred verkleinert norid betraechtlich
6794//normalC haengt bei minor, ideal im loop wird zu gross ###
6795//interred bei normalC vergroeesert string um Faktor 4000!
6796//withGens haengt bei interred in loop 4 (> 10 h) oder
6797//(nach Ausschalten von interred) bei
6798//int delt=vdim(std(modulo(f,ideal(p)))); (>?h)
6799
6800//Leonard1: (1. Komponente von Leonard),  delta -1
6801ring r=2,(v,u,z,y,x),dp;
6802ideal i = z3+zyx+y3x2+y2x3, uyx+z2,uz+z+y2x+yx2, u2+u+zy+zx,
6803          v3+vux+vz2+vzyx+vzx+uz3+uz2y+z3+z2yx2;
6804//normalP 5 sec (withRing 9 sec), norTest(i,nor,2); 45 sec
6805//normalC 102sec, 99sec
6806//### Zeit wird bei ideal Ann = quotient(SM[2],SL[1]); und bei
6807// f  = quotient(p*J,J); verbraucht
6808//withGens (ohne interred) 131sec, norTest(i,nor,2); 2min25sec
6809//norTest(i,nor,2);  45 sec
6810
6811 ring r=2,(y,x),wp(25,21); //Leonard2, delta 232
6812 ring r=2,(y,x),dp;
6813 ideal i=
6814 y^21+y^20*x +y^18*(x^3+x+1) +y^17*(x^3+1) +y^16*(x^4+x)
6815 +y^15*(x^7+x^6+x^3+x+1) +y^14*x^7 +y^13*(x^8+x^7+x^6+x^4+x^3+1)
6816 +y^12*(x^9+x^8+x^4+1) +y^11*(x^11+x^9+x^8+x^5+x^4+x^3+x^2)
6817 +y^10*(x^12+x^9+x^8+x^7+x^5+x^3+x+1)
6818 +y^9*(x^14+x^13+x^10+x^9+x^8+x^7+x^6+x^3+x^2+1)
6819 +y^8*(x^13+x^9+x^8+x^6+x^4+x^3+x) +y^7*(x^16+x^15+x^13+x^12+x^11+x^7+x^3+x)
6820 +y^6*(x^17+x^16+x^13+x^9+x^8+x) +y^5*(x^17+x^16+x^12+x^7+x^5+x^2+x+1)
6821 +y^4*(x^19+x^16+x^15+x^12+x^6+x^5+x^3+1)
6822 +y^3*(x^18+x^15+x^12+x^10+x^9+x^7+x^4+x)
6823 +y^2*(x^22+x^21+x^20+x^18+x^13+x^12+x^9+x^8+x^7+x^5+x^4+x^3)
6824 +y*(x^23+x^22+x^20+x^17+x^15+x^14+x^12+x^9)
6825 +(x^25+x^23+x^19+x^17+x^15+x^13+x^11+x^5);
6826//normalP: dp 2sec withRing 8sec,
6827//wp 4sec, withRing:51sec Zeit in lin = subst(lin, var(ii), vip); in elimpart ),
6828//norTest(i,nor,2): haengt bei mstd(norid);
6829//### normalC: (m. interred): haengt bei endid = interred(endid);
6830//GEFIXTES INTERRED ABWARTEN. Dann interred aktivieren
6831//interred(norid) haengt u. mst(norid) zu lange
6832//(o.interred): haengt bei  haengt bei list SM = mstd(i);
6833//ideal in der Mitte zu gross
6834//i = Ideal (size 118, 13 var) fuer die neue Normalisierung
6835//normal(neu) haengt bei return(std(i)) (offensichtlich in eineranderen lib)
6836
6837REDUCIBLE EXAMPLES:
6838------------------
6839//Apply:
6840int tt = timer;
6841list nor=normalP(i,"isPrim","withRing");
6842timer-tt;
6843
6844list nor = normal(i); nor;
6845list nor = normalC(i); nor;
6846list nor = normalC(i, "withGens"); nor;
6847list nor = normalP(i,"withRing"); nor;
6848list nor = normalP(i); nor;
6849def R=nor[1][1]; setring R; norid; normap;
6850
6851//Leonhard 4 Komponenten, dim=2, delta: 0,0,0,-1
6852ring r=2,(v,u,z,y,x),dp;      //lp zu lange
6853ideal i=z3+zyx+y3x2+y2x3, uyx+z2, v3+vuyx+vux+vzyx+vzx+uy3x2+uy2x+zy3x+zy2x2;
6854//normalP: 19 sec, withRing: 22 sec
6855//normalC ohne (mit) interred: 112 (113)sec, equidim: 99sec
6856//normalC 1. mal 111 sec, (2.mal) 450sec!! 3.mal 172 sec
6857//(unterschiedlich lange primdec, mit Auswirkungen)
6858//char 19: normalC: 15sec , withGens: 14sec (o.interr.)
6859
6860//----------------------Test Example for special cases -------------------
6861int tt = timer;
6862list nor=normalP(i,"withRing");nor;
6863//list nor=normalP(i,"withRing", "isPrim");nor;
6864timer-tt;
6865def R1 = nor[1][1]; setring R1;  norid; normap; interred(norid);
6866setring r;
6867
6868int tt = timer;
6869list nor=normal(i,"isPrim");nor;
6870timer-tt;
6871
6872ring r = 29,(x,y,z),dp;
6873ideal i = x2y2,x2z2;       //Nicht equidimensional, equidim reduziert nicht, ok
6874ideal i  = xyz*(z3-xy4);   //### interred(norid) verkuerzt
6875//je 0 sec
6876
6877ideal j = x,y;
6878ideal i = j*xy;
6879equidim(i);
6880//hat eingebettete Komponente, equidim rechnet wie in Beschreibung (ok)
6881
6882ring r  = 19,(x,y),dp;
6883   ideal i = x3-y4;                   //delta = 3
6884   ideal i = y*x*(x3-y4);             //delta = 11; 0,0,3
6885   ideal i = (x2-y3)*(x3-y4);         //delta = 13; 1,3
6886   ideal i = (x-y)*(x3+y2)*(x3-y4);   //delta = 23; 0,1,3
6887   ideal i = (x-1)*(x3+y2)*(x2-y3);   //delta = 16; 0,1,1
6888   ideal i = (x-y^2)^2 - y*x^3;       //delta = 3
6889   //singularities at not only at 0, hier rechnet equidim falsch
6890
6891// -------------------------- General Examples  ---------------------------//Huneke, irred., delta=2 (Version 3-0-4: < 1sec)
6892//Version 3-0-6 default: 1sec, mit gens 2sec, mit delta 5 sec
6893//(prim,noFac):ca 7 Min, prim:ca 10 min(wg facstd)
6894//
6895// "equidim" < 1sec irred. 5sec
6896// ring r=31991,(a,b,c,d,e),dp;
6897ring r=2,(a,b,c,d,e),dp;                    //delta=2
6898ideal i=
68995abcde-a5-b5-c5-d5-e5,
6900ab3c+bc3d+a3be+cd3e+ade3,
6901a2bc2+b2cd2+a2d2e+ab2e2+c2de2,
6902abc5-b4c2d-2a2b2cde+ac3d2e-a4de2+bcd2e3+abe5,
6903ab2c4-b5cd-a2b3de+2abc2d2e+ad4e2-a2bce3-cde5,
6904a3b2cd-bc2d4+ab2c3e-b5de-d6e+3abcd2e2-a2be4-de6,
6905a4b2c-abc2d3-ab5e-b3c2de-ad5e+2a2bcde2+cd2e4,
6906b6c+bc6+a2b4e-3ab2c2de+c4d2e-a3cde2-abd3e2+bce5;
6907//normalC: char 2, 31991: 0 sec (isPrim); char 2, equidim: 7 sec
6908//norTest(i,nor,2); 1sec
6909//normalP char 2: 1sec (isPrim)
6910//size(norid); size(string(norid));21 1219 interred(norid): 21 1245 (0 sec)
6911
6912int tt = timer;
6913list nor=normalC(i);nor;
6914timer-tt;
6915
6916list nor = normalP(i,"isPrim");
6917
6918//Vasconcelos irred., delta -1 (dauert laenger)
6919//auf macbook pro = 20 sec mit alter Version,
6920//Sing 3-0-6:
6921// Char 32003: "equidim" 30 sec, "noFac": 30sec
6922//gens: nach 9 min abgebr (haengt in Lin = ideal(T*syzf);) !!!! Hans zu tun
6923//Char 2: default (charp) 2 sec, normalC ca 30 sec
6924//ring r=32003,(x,y,z,w,t),dp;   //dim 2, dim s_locus 1
6925ring r=2,(x,y,z,w,t),dp;   //dim 2, dim s_locus 1
6926ideal i= x2+zw, y3+xwt, xw3+z3t+ywt2, y2w4-xy2z2t-w3t3;
6927//normalC: char 2: 22,  sec (mit und ohne isPrim)
6928//normalP char 2: 0sec (isPrim)      o. interred
6929//char 32003: ### haengt in ideal endid  = phi1(endid);
6930
6931//-------------------------------------------------------
6932//kleine Beispiele:
6933
6934//Theo1, irred, delta=-1
6935//normalC: 1sec, normalP: 3 sec
6936ring r=32003,(x,y,z),wp(2,3,6); //dim 2,dim slocus 1
6937ideal i=zy2-zx3-x6;
6938//normalC: char 2,19,32003: 0  sec (isPrim)
6939//normalP (isPrim) char 2,19: 0sec, char 29: 1sec
6940
6941//Theo1a, CohenMacaulay regular in codim 2, dim slocus=1, delta=0
6942//normalC: 0 sec, normalP: haegt in K=preimage(R,phi,L);
6943ring r=32003,(x,y,z,u),dp;
6944ideal i=zy2-zx3-x6+u2;
6945//normalC: char 2,32003: 0  sec (isPrim)
6946//normalP (isPrim) char 2: 0sec, char 19: haengt in K = preimage(Q,phi,L);
6947
6948//Theo2, irreduzibel, reduziert, < 1sec, delta -1
6949ring r=0,(x,y,z),wp(3,4,12);
6950ideal i=z*(y3-x4)+x8;
6951//normalC: char 2,32003,0: 0  sec (isPrim)
6952//normalP (isPrim) char 2: 0 1sec, char 19: 1sec char 29: 7 sec
6953
6954//Theo2a, reduiziert, 2-dim, dim_slocus=1, alte Version 3 sec,
6955//normalP ca 30 sec, normalC ca 4sec, delta -1
6956//ring r=32003,(T(1..4)),wp(3,4,12,17);
6957//ring r=11,(T(1..4)),dp;
6958ring r=11,(T(1..4)),wp(3,4,12,17);
6959ideal i=
6960T(1)^8-T(1)^4*T(3)+T(2)^3*T(3),
6961T(1)^4*T(2)^2-T(2)^2*T(3)+T(1)*T(4),
6962T(1)^7+T(1)^3*T(2)^3-T(1)^3*T(3)+T(2)*T(4),
6963T(1)^6*T(2)*T(3)+T(1)^2*T(2)^4*T(3)+T(1)^3*T(2)^2*T(4)-T(1)^2*T(2)*T(3)^2+T(4)^2;
6964//normalC: char 2,32003: 0  sec (isPrim)
6965//normalP (isPrim) char 2: 0sec, char 11 2se, char 19: 13sec
6966//norTest 48sec in char11
6967//### interred verkuerzt
6968//char 29: haengt in K = preimage(Q,phi,L);
6969
6970//Theo3, irred, 2-dim, 1-dim sing, < 1sec
6971ring r=11,(x,y,z),wp(3,5,15);
6972ideal i=z*(y3-x5)+x10;
6973//normalC: char 2,0: 0  sec (withRing)
6974//normalP (withRing) char 2,11: 0sec, char 19: 13sec norTest 12sec(char 11)
6975
6976//Theo4 reducible, delta (0,0,0) -1
6977ring r=29,(x,y,z),dp;
6978ideal i=(x-y)*(x-z)*(y-z);
6979//normalC: char 2,32003: 0  sec
6980//normalP char withRing 2, 29: 0sec, 6sec
6981
6982//Theo6
6983ring r=32003,(x,y,z),dp;
6984ideal i=x2y2+x2z2+y2z2;
6985//normalC: char 2,32003: 0  sec
6986//normalP char withRing 2, 29: 0sec, 4sec
6987
6988//Sturmfels, CM, 15 componenten, alle glatt
6989ring r=0,(b,s,t,u,v,w,x,y,z),dp;
6990ideal i= bv+su, bw+tu, sw+tv, by+sx, bz+tx, sz+ty,uy+vx,uz+wx,vz+wy,bvz;
6991//normalC car 11, 0: 1sec, normalP 0 sec
6992
6993//riemenschneider, , dim 3, 5 Komp. delta (0,0,0,0,0), -1
6994ring r=2,(p,q,s,t,u,v,w,x,y,z),wp(1,1,1,1,1,1,2,1,1,1);
6995ideal i=xz,vx,ux,su,qu,txy,stx,qtx,uv2z-uwz,uv3-uvw,puv2-puw;
6996//alles 0 sec in char 2
6997
6998//4 Komponenten, alle glatt, 0sec
6999ring r=11,(x,y,z,t),dp;
7000ideal i=x2z+xzt,xyz,xy2-xyt,x2y+xyt;
7001
7002//dim 3, 2 Komponenten delta (-1,0), -1
7003ring r=2,(u,v,w,x,y,z),wp(1,1,1,3,2,1);
7004ideal i=wx,wy,wz,vx,vy,vz,ux,uy,uz,y3-x2;
7005//alles 0 sec in char 2
7006//---------------------------------------------------------
7007int tt = timer;
7008list nor=normalP(i,"normalC","withRing");nor;
7009timer-tt;
7010
7011//St_S/Y, 3 Komponenten, 2 glatt, 1 normal
7012//charp haengt (in char 20) in K=preimage(R,phi,L);
7013//ring r=32003,(b,s,t,u,v,w,x,y,z),dp;
7014ring r=11,(b,s,t,u,v,w,x,y,z),dp;
7015ideal i=wy-vz,vx-uy,tv-sw,su-bv,tuy-bvz;
7016//normalC: char 2,32003: 0  sec
7017//normalP char withRing 2: 1sec, char 11: 40sec
7018
7019//Horrocks: cahr 0: 17 (8 in char 11) Komponenten alle normal, delta 1
7020//char 11: 8 Komponenten alle normal, delta -1
7021ring r=0,(a,b,c,d,e,f),dp;
7022//ring r=11,(a,b,c,d,e,f),dp; //Charp bis p = 200 ca 3sec
7023ideal i=
7024adef-16000be2f+16001cef2, ad2f+8002bdef+8001cdf2, abdf-16000b2ef+16001bcf2,
7025a2df+8002abef+8001acf2, ad2e-8000bde2-7999cdef, acde-16000bce2+16001c2ef,
7026a2de-8000abe2-7999acef, acd2+8002bcde+8001c2df, abd2-8000b2de-7999bcdf,
7027a2d2+9603abde-10800b2e2-9601acdf+800bcef+11601c2f2,
7028abde-8000b2e2-acdf-16001bcef-8001c2f2, abcd-16000b2ce+16001bc2f,
7029a2cd+8002abce+8001ac2f, a2bd-8000ab2e-7999abcf, ab3f-3bdf3,
7030a2b2f-2adf3-16000bef3+16001cf4, a3bf+4aef3, ac3e-10668cde3,
7031a2c2e+10667ade3+16001be4+5334ce3f, a3ce+10669ae3f, bc3d+8001cd3e,
7032ac3d+8000bc3e+16001cd2e2+8001c4f, b2c2d+16001ad4+4000bd3e+12001cd3f,
7033b2c2e-10668bc3f-10667cd2ef, abc2e-cde2f, b3cd-8000bd3f, b3ce-10668b2c2f-10667bd2ef, abc2f-cdef2, a2bce-16000be3f+16001ce2f2,
7034ab3d-8000b4e-8001b3cf+16000bd2f2, ab2cf-bdef2,
7035a2bcf-16000be2f2+16001cef3, a4d-8000a3be+8001a3cf-2ae2f2;
7036//normalC: char 0: 1sec char 11: 0sec
7037//normalP: char 11: 0sec
7038
7039//2sec mit normalC, in char 2 ebenfalls (char 20 mit charp >1 min)
7040//4 Komp. in char 2, delta (0,0,0,0) -1, char 11:delta (-1,0,0,0) -1
7041ring r=32003,(b,s,t,u,v,w,x,y,z),dp;
7042ideal i=
7043wx2y3-vx2y2z+wx2yz2+wy3z2-vx2z3-vy2z3,
7044vx3y2-ux2y3+vx3z2-ux2yz2+vxy2z2-uy3z2,
7045tvx2y2-swx2y2+tvx2z2-swx2z2+tvy2z2-swy2z2,
7046sux2y2-bvx2y2+sux2z2-bvx2z2+suy2z2-bvy2z2,
7047tux2y3-bvx2y2z+tux2yz2+tuy3z2-bvx2z3-bvy2z3;
7048//normalC: char 2,32003: 1 sec
7049//normalP char withRing 2: 1sec, char 11: 40sec
7050
7051//---------------------------------------------------------
7052//genus:
7053int tt = timer;
7054list nor=normal(i, "noFac");nor;
7055timer-tt;
7056
7057//Yoshihiko Sakai, irred, 0sec, delta = 8
7058ring r=0,(x,y),dp;                    //genus 0 4 nodes and 6 cusps im P2
7059//ring r=7,(x,y),dp;                  //charp haengt in K = preimage(Q,phi,L)
7060ideal i=(x2+y^2-1)^3 +27x2y2;
7061
7062ring r=0,(x,y),dp;   //genus 0
7063ideal i=(x-y^2)^2 - y*x^3;
7064
7065ring r=0,(x,y),dp;  //genus 4
7066ideal i=y3-x6+1;
7067
7068int m=9;           // q=9: genus 0
7069int p=2;
7070int q=9;//2,...,9
7071ring r=0,(x,y),dp;
7072ideal i=y^m - x^p*(x - 1)^q;
7073
7074ring r=0,(x,y),dp;  //genus 19
7075ideal i=55*x^8+66*y^2*x^9+837*x^2*y^6-75*y^4*x^2-70*y^6-97*y^7*x^2;
7076
7077ring r=23,(x,y),dp;  //genus 34, delta 2
7078ideal i=y10+(-2494x2+474)*y8+(84366+2042158x4-660492)*y6
7079        +(128361096x4-47970216x2+6697080-761328152x6)*y4
7080        +(-12024807786x4-506101284x2+15052058268x6+202172841-3212x8)*y2
7081        +34263110700x4-228715574724x6+5431439286x2+201803238
7082        -9127158539954x10-3212722859346x8;
7083//normalC, normalP 0 sec
7084
7085//Rob Koelman
7086//ring r=0,(x,y,z),dp;      //dim sing = 1 (nach ca 15 min abgebrochen)
7087ring r=32003,(x,y,z),dp;
7088ideal i=
7089761328152*x^6*z^4-5431439286*x^2*y^8+2494*x^2*z^8+228715574724*x^6*y^4+
7090 9127158539954*x^10-15052058268*x^6*y^2*z^2+3212722859346*x^8*y^2-
7091 134266087241*x^8*z^2-202172841*y^8*z^2-34263110700*x^4*y^6-6697080*y^6*z^4-
7092 2042158*x^4*z^6-201803238*y^10+12024807786*x^4*y^4*z^2-128361096*x^4*y^2*z^4+
7093 506101284*x^2*z^2*y^6+47970216*x^2*z^4*y^4+660492*x^2*z^6*y^2-
7094 z^10-474*z^8*y^2-84366*z^6*y^4;
7095//normalC char 32003: 10 sec, char 0 :
7096
7097//ring r=0,(x,y),dp;//genus 10  with 26 cusps (nach ca 4 min abgebrochen)
7098ring r=32003,(x,y),dp;    //24 sing, delta 24
7099ideal i=9127158539954x10+3212722859346x8y2+228715574724x6y4-34263110700x4y6
7100-5431439286x2y8-201803238y10-134266087241x8-15052058268x6y2+12024807786x4y4
7101+506101284x2y6-202172841y8+761328152x6-128361096x4y2+47970216x2y4-6697080y6
7102-2042158x4+660492x2y2-84366y4+2494x2-474y2-1;
7103//normalC 32003: 4 sec, char 0: abgebrochen bei pr = facstd(i); ###
7104
7105ring r=0,(x,y),dp;   //irred, genus 1  with 5 cusps, delta 5
7106ideal i=57y5+516x4y-320x4+66y4-340x2y3+73y3+128x2-84x2y2-96x2y;
7107//normalC 0 sec
7108
7109ring r=2,(x,y),dp;  //genus 4, 2 Zweige, delta (13,9) 89
7110ideal i=((x2+y3)^2+xy6)*((x3+y2)^2+x10y);
7111//normalC: char 2 : 1sec, char 0: lange
7112//normalP char 2 withRing: 0sec
7113
7114ring r=2,(y,z,w,u),dp; //2 Komp. genus -5
7115ideal i=y2+z2+w2+u2,w4-u4;
7116//normalC: char 2 : 0sec, char 0: 1sec
7117//normalP char 2 withRing: 0sec
7118
7119ring r=0,(y,z,w,u),dp; //irred. genus 9
7120ideal i=y2+z2+w2+u2,z4+w4+u4;
7121//char 0: 0sec
7122
7123ring r=0,(x,y,t),dp;  //irred, delta -1
7124ideal i= 25x8+200x7y+720x6y2+1520x5y3+2064x4y4+1856x3y5+1088x2y6+384xy7+64y8-12x6t2-72x5yt2-184x4y2t2-256x3y3t2-192x2y4t2-64xy5t2-2x4t4-8x3yt4+16xy3t4+16y4t4+4x2t6+8xyt6+8y2t6+t8;
7125//char 0: 0sec
7126
7127ring r=0,(x,y,z,w,u),dp;
7128ideal i=x2+y2+z2+w2+u2,x3+y3+z3,z4+w4+u4;
7129//char 0: 0sec
7130
7131//---------------------------------------------------------
7132//Probleme mit normalC in char 2 und char 0
7133
7134int tt = timer;
7135list nor=normalC(i,"withRing");nor;
7136timer-tt;
7137
7138//Mark van Hoeij
7139ring r=3,(x,y),dp;  //genus 19, delta 21
7140ideal i=y20+y13x+x4y5+x3*(x+1)^2;
7141//normalC: char 2 > 10 min   bei list SM = mstd(i);###
7142//normalP char 2 withRing: 0sec, char 11: haengt bei K = preimage(Q,phi,L);
7143
7144ring r=2,(x,y),dp;  //genus 35
7145ideal i=y30+y13x+x4y5+x3*(x+1)^2;
7146//char 0 abgebrochen bei list SM = mstd(i); ###
7147//char 2 nach ca 30 min
7148//normalC: char 2: abgebr. bei list SM = mstd(i);  //Now the work starts'
7149//normalC, withGens, char 2: abgebrochen bei Q=mstd(Q)[2];
7150//normalP char 2 withRing: 0sec
7151
7152ring r=0,(x,y),dp;   //irred, genus 55, delta 21
7153ideal i=y40+y13x+x4y5+x3*(x+1)^2;
7154//normalC: char 2 lange
7155//normalP char 2 withRing: 0sec
7156
7157ring r=29,(x,y,t),dp; //char 0: genus -5, 4 Komp, delta (-1,-1,0,0), -1
7158ideal i=x8+8x7y+32x6y2+80x5y3+136x4y4+160x3y5+128x2y6+64xy7+16y8+4x6t2+24x5yt2+72x4y2t2+128x3y3t2+144x2y4t2+96xy5t2+32y6t2+14x4t4+56x3yt4+112x2y2t4+112xy3t4+40y4t4+20x2t6+40xyt6+8y2t6+9t8;
7159//normalC: char 29 : 0sec, char 0: 0sec  //char 29 6 Komponenten
7160//normalP char 29 withRing: 1sec
7161
7162//-------------------------- problematic examples ------------------------
7163//ring r=0,(x,y,t),dp;
7164ring r=32003,(x,y,t),dp;
7165ideal i=
716632761x8+786264x7y+8314416x6y2+50590224x5y3+193727376x4y4+478146240x3y5+742996800x2y6+664848000xy7+262440000y8+524176x7t+11007696x6yt+99772992x5y2t+505902240x4y3t+1549819008x3y4t+2868877440x2y5t+2971987200xy6t+1329696000y7t+3674308x6t2+66137544x5yt2+499561128x4y2t2+2026480896x3y3t2+4656222144x2y4t2+5746386240xy5t2+2976652800y6t2+14737840x5t3+221067600x4yt3+1335875904x3y2t3+4064449536x2y3t3+6226336512xy4t3+3842432640y5t3+36997422x4t4+443969064x3yt4+2012198112x2y2t4+4081745520xy3t4+3126751632y4t4+59524208x3t5+535717872x2yt5+1618766208xy2t5+1641991392y3t5+59938996x2t6+359633976xyt6+543382632y2t6+34539344xt7+103618032yt7+8720497t8;
7167//char 0: lange (es liegt an den grossen Zahlen), char 32003: 0 sec
7168
7169//dasselbe Beipiel in char 19: irred
7170ring r=0,(x,y,t),dp;
7171ideal i=
71725x8+6x7y-3x6y2+7x5y3-6x4y4-8x3y5-5x2y6-8y8+4x7t+8x6yt+2x5y2t-6x4y3t+9x3y4t+9x2y5t-xy6t-7x6t2+7x5yt2-x4y2t2+5x3y3t2+7x2y4t2+xy5t2-3y6t2-4x5t3 -3x4yt3+2x3y2t3-7x2y3t3-6xy4t3-3y5t3-5x4t4-3x3yt4-4x2y2t4-8xy3t4 +7y4t4+x3t5+9x2yt5+9xy2t5-8y3t5-2y2t6+4xt7-7yt7-9t8;
7173//normalP: char 2,3: 0sec, norTest 0,2 sec, char 11 haengt bei peimage
7174//normalC: char 3: 0 sec, char 0: 1sec
7175
7176//ring r=0,(x,y),dp;
7177ring r=32003,(x,y),dp;
7178ideal i=
7179x30y21+21x29y20+210x28y19+10x27y19+1330x27y18+190x26y18+5985x26y17
7180+1710x25y17+20349x25y16+45x24y17+9690x24y16+54264x24y15+765x23y16
7181+38760x23y15+116280x23y14+6120x22y15+116280x22y14+120x21y15
7182+203490x22y13+30600x21y14+271320x21y13+1799x20y14+293930x21y12+107100x20y13
7183+503880x20y12+12586x19y13+352716x20y11+278460x19y12+210x18y13+755820x19y11
7184+54509x18y12+352716x19y10+556920x18y11+2723x17y12+923780x18y10+163436x17y11
7185+293930x18y9+875160x17y10+16296x16y11+923780x17y9+359359x16y10+252x15y11
7186+203490x17y8+1093950x16y9+59598x15y10+755820x16y8+598598x15y9+2751x14y10
7187+116280x16y7+1093950x15y8+148610x14y9+503880x15y7+769197x14y8+13650x13y9
7188+54264x15y6+875160x14y7+266805x13y8+210x12y9+271320x14y6+768768x13y7
7189+40635x12y8+20349x14y5+556920x13y6+354816x12y7+1855x11y8+116280x13y5
7190+597597x12y6+80640x11y7+5985x13y4+278460x12y5+353892x11y6+7280x10y7+38760x12y4
7191+358358x11y5+112014x10y6+120x9y7+1330x12y3+107100x11y4+264726x10y5+16660x9y6
7192+9690x11y3+162799x10y4+111132x9y5+805x8y6+210x11y2+30600x10y3+146685x9y4
7193+24500x8y5+1710x10y2+54236x9y3+78750x8y4+2310x7y5+21x10y+6120x9y2+58520x8y3
7194+24010x7y4+45x6y5+190x9y+12509x8y2+39060x7y3+3675x6y4+x9+765x8y+15918x7y2
7195+15680x6y3+204x5y4+10x8+1786x7y+12915x6y2+3500x5y3+45x7+2646x6y+6580x5y2
7196+366x4y3+119x6+2562x5y+1995x4y2+10x3y3+203x5+1610x4y+324x3y2+231x4+630x3y
7197+23x2y2+175x3+141x2y+85x2+16xy+24x+y+4;
7198list nor = normal(i);
7199//normalC: char 0: ### haengt in SB of singular locus JM = mstd(J);
7200//normalC: char 32003,"noFac","equidim": 0sec, "noFac": 1sec
7201// ev neues interred
7202genus(i);         // haengt bei int mu=vdim(std(jacob(f)));
7203                  //### ist das noetig?
7204
7205//Singular rechnet genus richtig, auch im Fall, dass Kurve irreduzibel,
7206//aber nicht absolut irreduzibel ist:
7207ring r = 0,(x,y),dp;
7208ideal i = x2+y2;      //irreduzibel /Q aber reduzibel /C (x-iy)*(x+iy)
7209factorize( x2+y2);    //liefert irreduzibel
7210genus(i);             //sollte 0+0-2+1= -1 sein
7211genus(i,1);           //beides ist korrekt in Singular
7212
7213*/
7214
Note: See TracBrowser for help on using the repository browser.