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

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