source: git/Singular/LIB/normal.lib @ 6f84e21

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