source: git/Singular/LIB/normal.lib @ 0dd77c2

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