source: git/Singular/LIB/normal.lib @ 766ae3

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