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

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