source: git/Singular/LIB/normal.lib @ 2bb083

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