source: git/Singular/LIB/normal.lib @ 57e4a9

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