source: git/Singular/LIB/normal.lib @ 88615db

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