source: git/Singular/LIB/normal.lib @ 4083fa

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