source: git/Singular/LIB/normal.lib @ 11dddeb

spielwiese
Last change on this file since 11dddeb was 11dddeb, checked in by Hans Schönemann <hannes@…>, 20 years ago
*hannes: from V2-0 git-svn-id: file:///usr/local/Singular/svn/trunk@7052 2c84dea3-7e68-4137-9b89-c4e89433aadc
  • Property mode set to 100644
File size: 54.0 KB
Line 
1///////////////////////////////////////////////////////////////////////////////
2version="$Id: normal.lib,v 1.38 2004-02-23 10:19:11 Singular Exp $";
3category="Commutative Algebra";
4info="
5LIBRARY:  normal.lib     Normalization of Affine Rings
6AUTHORS:  G.-M. Greuel,  greuel@mathematik.uni-kl.de,
7@*        G. Pfister,    pfister@mathematik.uni-kl.de
8
9MAIN PROCEDURES:
10 normal(I[,wd]);     computes the normalization of basering/I,
11                     resp. computes the normalization of basering/I and
12                     the delta invariant
13 HomJJ(L);           presentation of End_R(J) as affine ring, L a list
14 genus(I);           computes genus of the projective curve defined by I
15
16AUXILIARY PROCEDURE:
17 deltaLoc(f,S);      (sum of) delta invariant(s) at conjugated singular points
18";
19
20LIB "general.lib";
21LIB "poly.lib";
22LIB "sing.lib";
23LIB "primdec.lib";
24LIB "elim.lib";
25LIB "presolve.lib";
26LIB "inout.lib";
27LIB "ring.lib";
28LIB "hnoether.lib";
29///////////////////////////////////////////////////////////////////////////////
30
31proc HomJJ (list Li)
32"USAGE:   HomJJ (Li);  Li = list: ideal SBid, ideal id, ideal J, poly p
33ASSUME:  R    = P/id,  P = basering, a polynomial ring, id an ideal of P,
34@*       SBid = standard basis of id,
35@*       J    = ideal of P containing the polynomial p,
36@*       p    = nonzero divisor of R
37COMPUTE: Endomorphism ring End_R(J)=Hom_R(J,J) with its ring structure as
38         affine ring, together with the canonical map R --> Hom_R(J,J),
39         where R is the quotient ring of P modulo the standard basis SBid.
40RETURN:  a list l of two objects
41@format
42         l[1] : a polynomial ring, containing two ideals, 'endid' and 'endphi'
43               such that l[1]/endid = Hom_R(J,J) and
44               endphi describes the canonical map R -> Hom_R(J,J)
45         l[2] : an integer which is 1 if phi is an isomorphism, 0 if not
46         l[3] : an integer, the contribution to delta
47@end format
48NOTE:    printlevel >=1: display comments (default: printlevel=0)
49EXAMPLE: example HomJJ;  shows an example
50"
51{
52//---------- initialisation ---------------------------------------------------
53
54   int isIso,isPr,isCo,isRe,isEq,oSAZ,ii,jj,q,y;
55   intvec rw,rw1;
56   list L;
57   y = printlevel-voice+2;  // y=printlevel (default: y=0)
58   def P = basering;
59   ideal SBid, id, J = Li[1], Li[2], Li[3];
60   poly p = Li[4];
61   attrib(SBid,"isSB",1);
62   int homo = homog(Li[2]);               //is 1 if id is homogeneous, 0 if not
63
64//---- set attributes for special cases where algorithm can be simplified -----
65   if( homo==1 )
66   {
67      rw = ringweights(P);
68   }
69   if( typeof(attrib(id,"isPrim"))=="int" )
70   {
71      if(attrib(id,"isPrim")==1)  { isPr=1; }
72   }
73   if( typeof(attrib(id,"onlySingularAtZero"))=="int" )
74   {
75      if(attrib(id,"onlySingularAtZero")==1){oSAZ=1; }
76   }
77   if( typeof(attrib(id,"isIsolatedSingularity"))=="int" )
78   {
79      if(attrib(id,"isIsolatedSingularity")==1) { isIso=1; }
80   }
81   if( typeof(attrib(id,"isCohenMacaulay"))=="int" )
82   {
83      if(attrib(id,"isCohenMacaulay")==1) { isCo=1; }
84   }
85   if( typeof(attrib(id,"isRegInCodim2"))=="int" )
86   {
87      if(attrib(id,"isRegInCodim2")==1) { isRe=1; }
88   }
89   if( typeof(attrib(id,"isEquidimensional"))=="int" )
90   {
91      if(attrib(id,"isEquidimensional")==1) { isEq=1; }
92   }
93//-------------------------- go to quotient ring ------------------------------
94   qring R  = SBid;
95   ideal id = fetch(P,id);
96   ideal J  = fetch(P,J);
97   poly p   = fetch(P,p);
98   ideal f,rf,f2;
99   module syzf;
100//---------- computation of p*Hom(J,J) as R-ideal -----------------------------
101   if ( y>=1 )
102   {
103     "// compute p*Hom(J,J) = p*J:J, p a non-zerodivisor";
104     "//   p is equal to:"; "";
105     p;
106     "";
107   }
108   f  = quotient(p*J,J);
109
110   if ( y>=1 )
111   { "// the module p*Hom(J,J) = p*J:J, p a non-zerodivisor";
112      "// p"; p;
113      "// f=p*J:J";f;
114   }
115   f2 = std(p);
116 
117//---------- Test: Hom(J,J) == R ?, if yes, go home ---------------------------
118
119   rf = interred(reduce(f,f2));       // represents p*Hom(J,J)/p*R = Hom(J,J)/R
120
121   if ( size(rf) == 0 )
122   {
123      if ( homog(f) && find(ordstr(basering),"s")==0 )
124      {
125         ring newR1 = char(P),(X(1..nvars(P))),(a(rw),dp);
126      }
127      else
128      {
129         ring newR1 = char(P),(X(1..nvars(P))),dp;
130      }
131      ideal endphi = maxideal(1);
132      ideal endid = fetch(P,id);
133      L=substpart(endid,endphi,homo,rw);
134      def lastRing=L[1];
135      setring lastRing;
136
137      attrib(endid,"onlySingularAtZero",oSAZ);
138      attrib(endid,"isCohenMacaulay",isCo);
139      attrib(endid,"isPrim",isPr);
140      attrib(endid,"isIsolatedSingularity",isIso);
141      attrib(endid,"isRegInCodim2",isRe);
142      attrib(endid,"isEqudimensional",isEq);
143      attrib(endid,"isCompleteIntersection",0);
144      attrib(endid,"isRad",0);
145      L=lastRing;
146      L = insert(L,1,1);
147      dbprint(y,"// case R = Hom(J,J)");
148      if(y>=1)
149      {
150         "//   R=Hom(J,J)";
151         "   ";
152         lastRing;
153         "   ";
154         "//   the new ideal";
155         endid;
156         "   ";
157         "//   the old ring";
158         "   ";
159         P;
160         "   ";
161         "//   the old ideal";
162         "   ";
163         setring P;
164         id;
165         "   ";
166         setring lastRing;
167         "//   the map";
168         "   ";
169         endphi;
170         "   ";
171         pause();
172         newline;
173      }
174      setring P;
175      L[3]=0;
176      return(L);
177   }
178   if(y>=1)
179   {
180      "// R is not equal to Hom(J,J), we have to try again";
181      pause();
182      newline;
183   }
184//---------- Hom(J,J) != R: create new ring and map from old ring -------------
185// the ring newR1/SBid+syzf will be isomorphic to Hom(J,J) as R-module
186
187   f=mstd(f)[2];
188   ideal ann=quotient(f2,f);
189   int delt;
190   if(isIso&&isEq){delt=vdim(std(modulo(f,ideal(p))));}
191
192   f = p,rf;          // generates pJ:J mod(p), i.e. p*Hom(J,J)/p*R as R-module
193   q = size(f);
194
195   syzf = syz(f);
196
197   if ( homo==1 )
198   {
199      rw1 = rw,0;
200      for ( ii=2; ii<=q; ii++ )
201      {
202         rw  = rw, deg(f[ii])-deg(f[1]);
203         rw1 = rw1, deg(f[ii])-deg(f[1]);
204      }
205      ring newR1 = char(R),(X(1..nvars(R)),T(1..q)),(a(rw1),dp);
206   }
207   else
208   {
209      ring newR1 = char(R),(X(1..nvars(R)),T(1..q)),dp;
210   }
211
212   map psi1 = P,maxideal(1);
213   ideal SBid = psi1(SBid);
214   attrib(SBid,"isSB",1);
215
216   qring newR = std(SBid);
217
218   map psi = R,ideal(X(1..nvars(R)));
219   ideal id = psi(id);
220   ideal f = psi(f);
221   module syzf = psi(syzf);
222   ideal pf,Lin,Quad,Q;
223   matrix T,A;
224   list L1;
225
226//---------- computation of Hom(J,J) as affine ring ---------------------------
227// determine kernel of: R[T1,...,Tq] -> J:J >-> R[1/p]=R[t]/(t*p-1),
228// Ti -> fi/p -> t*fi (p=f1=f[1]), to get ring structure. This is of course
229// the same as the kernel of R[T1,...,Tq] -> pJ:J >-> R, Ti -> fi.
230// It is a fact, that the kernel is generated by the linear and the quadratic
231// relations
232
233   pf = f[1]*f;
234   T = matrix(ideal(T(1..q)),1,q);
235   Lin = ideal(T*syzf);
236   if(y>=1)
237   {
238      "// the ring structure of Hom(J,J) as R-algebra";
239      " ";
240      "//   the linear relations";
241      " ";
242      Lin;
243      "   ";
244   }
245
246   for (ii=2; ii<=q; ii++ )
247   {
248      for ( jj=2; jj<=ii; jj++ )
249      {
250         A = lift(pf,f[ii]*f[jj]);
251         Quad = Quad, ideal(T(jj)*T(ii) - T*A);          // quadratic relations
252      }
253   }
254
255   if(y>=1)
256   {
257      "//   the quadratic relations";
258      "   ";
259      interred(Quad);
260      pause();
261      newline;
262   }
263   Q = Lin,Quad;
264   Q = subst(Q,T(1),1);
265   Q=mstd(Q)[2];
266//---------- reduce number of variables by substitution, if possible ----------
267   if (homo==1)
268   {
269      ring newRing = char(R),(X(1..nvars(R)),T(2..q)),(a(rw),dp);
270   }
271   else
272   {
273      ring newRing = char(R),(X(1..nvars(R)),T(2..q)),dp;
274   }
275
276   ideal endid  = imap(newR,id),imap(newR,Q);
277   ideal endphi = ideal(X(1..nvars(R)));
278
279   L=substpart(endid,endphi,homo,rw);
280
281   def lastRing=L[1];
282   setring lastRing;
283
284   attrib(endid,"onlySingularAtZero",0);
285   map sigma=R,endphi;
286   ideal an=sigma(ann);
287   export(an);  //noetig?
288   ideal te=an,endid;
289   if(isIso&&(size(reduce(te,std(maxideal(1))))==0))
290   {
291      attrib(endid,"onlySingularAtZero",oSAZ);
292   }
293   kill te;
294   attrib(endid,"isCohenMacaulay",isCo);
295   attrib(endid,"isPrim",isPr);
296   attrib(endid,"isIsolatedSingularity",isIso);
297   attrib(endid,"isRegInCodim2",isRe);
298   attrib(endid,"isEquidimensional",isEq);
299   attrib(endid,"isCompleteIntersection",0);
300   attrib(endid,"isRad",0);
301   if(y>=1)
302   {
303      "//   the new ring after reduction of the number of variables";
304      "   ";
305      lastRing;
306      "   ";
307      "//   the new ideal";
308      "   ";
309      endid;
310      "   ";
311      "//   the old ring";
312      "   ";
313      P;
314      "   ";
315      "//   the old ideal";
316      "   ";
317      setring P;
318      id;
319      "   ";
320      setring lastRing;
321      "//   the map";
322      "   ";
323      endphi;
324      "   ";
325      pause();
326      newline;
327   }
328   L = lastRing;
329   L = insert(L,0,1);
330   L[3]=delt;
331   return(L);
332}
333example
334{"EXAMPLE:";  echo = 2;
335  ring r   = 0,(x,y),wp(2,3);
336  ideal id = y^2-x^3;
337  ideal J  = x,y;
338  poly p   = x;
339  list Li = std(id),id,J,p;
340  list L   = HomJJ(Li);
341  def end = L[1];    // defines ring L[1], containing ideals endid, endphi
342  setring end;       // makes end the basering
343  end;
344  endid;             // end/endid is isomorphic to End(r/id) as ring
345  map psi = r,endphi;// defines the canonical map r/id -> End(r/id)
346  psi;
347}
348
349///////////////////////////////////////////////////////////////////////////////
350
351proc normal(ideal id, list #)
352"USAGE:   normal(i [,choose]);  i a radical ideal, choose empty, 1 or \"wd\"
353         if choose=1 the normalization of the associated primes is computed
354         (which is sometimes more efficient);
355         if @code{choose=\"wd\"} the delta invariant is computed
356         simultaneously; this may take much more time in the reducible case,
357         since the factorizing standard basis algorithm cannot be used.
358ASSUME:  The ideal must be radical, for non-radical ideals the output may
359         be wrong (i=radical(i); makes i radical)
360RETURN:  a list of rings, say nor and in case of @code{choose=\"wd\"} an
361         integer at the end of the list.
362         Each ring @code{nor[i]} contains two ideals with given names
363         @code{norid} and @code{normap} such that@*
364         - the direct sum of the rings @code{nor[i]/norid} is the
365         normalization of basering/id;@*
366         - @code{normap} gives the normalization map from basering/id to
367         @code{nor[i]/norid} (for each i).
368NOTE:    to use the i-th ring type: @code{def R=nor[i]; setring R;}.
369@*       Increasing printlevel displays more comments (default: printlevel=0).
370@*       Not implemented for local or mixed orderings.
371@*       If the input ideal i is weighted homogeneous a weighted ordering may
372         be used (qhweight(i); computes weights).
373KEYWORDS: normalization; delta invariant.
374EXAMPLE: example normal; shows an example
375"
376{
377   int i,j,y,withdelta;
378   string sr;
379   list result,prim,keepresult;
380   y = printlevel-voice+2;
381   if(size(#)>0)
382   {
383     if(typeof(#[1])=="string")
384     {
385       kill #;
386       list #;
387       withdelta=1;
388     }
389   }
390   attrib(id,"isRadical",1);
391   if ( ord_test(basering) != 1)
392   {
393     "";
394     "// Not implemented for this ordering,";
395     "// please change to global ordering!";
396     return(result);
397   }
398   if( typeof(attrib(id,"isCompleteIntersection"))=="int" )
399   {
400      if(attrib(id,"isCompleteIntersection")==1)
401      {
402         attrib(id,"isCohenMacaulay",1);
403         attrib(id,"isEquidimensional",1);
404      }
405   }
406   if( typeof(attrib(id,"isCohenMacaulay"))=="int" )
407   {
408      if(attrib(id,"isCohenMacaulay")==1)
409      {
410         attrib(id,"isEquidimensional",1);
411      }
412   }
413   if( typeof(attrib(id,"isPrim"))=="int" )
414   {
415      if(attrib(id,"isPrim")==1)
416      {
417         attrib(id,"isEquidimensional",1);
418      }
419   }
420   if(size(#)==0)
421   {
422      if( typeof(attrib(id,"isEquidimensional"))=="int" )
423      {
424         if(attrib(id,"isEquidimensional")==1)
425         {
426            prim[1]=id;
427         }
428         else
429         {
430            prim=equidim(id);
431         }
432      }
433      else
434      {
435         prim=equidim(id);
436      }
437      if(y>=1)
438      {
439         "// we have ",size(prim),"equidimensional components";
440      }
441      if(withdelta &&(size(prim)>1))
442      {
443         withdelta=0;
444         "WARNING!  cannot compute delta,";
445         "the ideal is not equidimensional";
446      }
447      if(!withdelta)
448      {
449         option(redSB);
450         for(j=1;j<=size(prim);j++)
451         {
452            keepresult=keepresult+facstd(prim[j]);
453         }
454         prim=keepresult;
455         option(noredSB);
456      }
457   }
458   else
459   {
460      if( typeof(attrib(id,"isPrim"))=="int" )
461      {
462         if(attrib(id,"isPrim")==1)
463         {
464            prim[1]=id;
465         }
466         else
467         {
468            prim=minAssPrimes(id);
469         }
470      }
471      else
472      {
473         prim=minAssPrimes(id);
474      }
475      if(y>=1)
476      {
477         "// we have ",size(prim),"irreducible components";
478      }
479   }
480   for(i=1; i<=size(prim); i++)
481   {
482      if(y>=1)
483      {
484         "// we are in loop ",i;
485      }
486      attrib(prim[i],"isCohenMacaulay",0);
487      if(size(#)!=0)
488      {
489         attrib(prim[i],"isPrim",1);
490      }
491      else
492      {
493         attrib(prim[i],"isPrim",0);
494      }
495      attrib(prim[i],"isRegInCodim2",0);
496      attrib(prim[i],"isIsolatedSingularity",0);
497      attrib(prim[i],"isEquidimensional",1);
498      attrib(prim[i],"isCompleteIntersection",0);
499      attrib(prim[i],"onlySingularAtZero",0);
500      if( typeof(attrib(id,"onlySingularAtZero"))=="int" )
501      {
502            if(attrib(id,"onlySingularAtZero")==1)
503             {attrib(prim[i],"onlySingularAtZero",1); }
504      }
505
506      if( typeof(attrib(id,"isIsolatedSingularity"))=="int" )
507      {
508            if(attrib(id,"isIsolatedSingularity")==1)
509             {attrib(prim[i],"isIsolatedSingularity",1); }
510      }
511
512      if( typeof(attrib(id,"isCompleteIntersection"))=="int" )
513      {
514            if((attrib(id,"isIsolatedSingularity")==1)&&(size(#)==0))
515             {attrib(prim[i],"isIsolatedSingularity",1); }
516      }
517      keepresult=normalizationPrimes(prim[i],maxideal(1),0);
518
519      for(j=1;j<=size(keepresult)-1;j++)
520      {
521         result=insert(result,keepresult[j]);
522      }
523      sr = string(size(result));     
524   }
525   if(withdelta)
526   {
527      sr = string(size(keepresult)-1);
528      result=keepresult;
529   }
530      dbprint(y+1,"
531// 'normal' created a list of "+sr+" ring(s).");
532      if(withdelta)
533      {
534        dbprint(y+1,"// nor["+sr+"+1] is the delta-invariant.");
535      }
536      dbprint(y+1,"// To see the rings, type (if the name of your list is nor):
537     show( nor);
538// To access the 1-st ring and map (similar for the others), type:
539     def R = nor[1]; setring R;  norid; normap;
540// R/norid is the 1-st ring of the normalization and
541// normap the map from the original basering to R/norid");
542
543      //kill endphi,endid;
544      return(result);
545}
546example
547{ "EXAMPLE:"; echo = 2;
548   ring r=32003,(x,y,z),wp(2,1,2);
549   ideal i=z3-xy4;
550   list nor=normal(i);
551   show(nor);
552   def r1=nor[1];
553   setring r1;
554   norid;
555   normap;
556
557   ring s=0,(x,y),dp;
558   ideal i=(x-y^2)^2 - y*x^3;
559   nor=normal(i,"wd");
560   //the delta-invariant
561   nor[size(nor)];
562}
563
564///////////////////////////////////////////////////////////////////////////////
565static proc normalizationPrimes(ideal i,ideal ihp,int delt, list #)
566"USAGE:   normalizationPrimes(i,ihp[,si]);  i equidimensional ideal, ihp map
567         (partial normalization),delta partial delta-invariant,
568          # ideal of singular locus
569RETURN:   a list of rings, say nor, and an integer, the delta-invariant
570          at the end of the list.
571          each ring nor[i] contains two ideals
572          with given names norid and normap such that
573           - the direct sum of the rings nor[i]/norid is
574             the normalization of basering/id;
575           - normap gives the normalization map from basering/id
576             to nor[i]/norid (for each i)
577EXAMPLE: example normalizationPrimes; shows an example
578"
579{
580
581   int y = printlevel-voice+2;  // y=printlevel (default: y=0)
582
583   if(y>=1)
584   {
585     "";
586     "// START a normalization loop with the ideal";  "";
587     i;  "";
588     basering;  "";
589     pause();
590     newline;
591   }
592
593   def BAS=basering;
594   list result,keepresult1,keepresult2;
595   ideal J,SB,MB;
596   int depth,lauf,prdim;
597   int ti=timer;
598
599   if(size(i)==0)
600   {
601      if(y>=1)
602      {
603          "// the ideal was the zero-ideal";
604      }
605         execute("ring newR7="+charstr(basering)+",("+varstr(basering)+"),("
606                      +ordstr(basering)+");");
607         ideal norid=ideal(0);
608         ideal normap=fetch(BAS,ihp);
609         export norid;
610         export normap;
611         result=newR7;
612         result[size(result)+1]=delt;
613         setring BAS;
614         return(result);
615   }
616
617   if(y>=1)
618   {
619     "// SB-computation of the input ideal";
620   }
621   list SM=mstd(i);                //here the work starts
622   int dimSM =  dim(SM[1]);        //dimension of variety to normalize
623  // Case: Get an ideal containing a unit
624   if( dimSM == -1)
625   {  "";
626      "      // A unit ideal was found.";
627      "      // Stop with partial result computed so far";"";
628
629         MB=SM[2];
630         intvec rw;
631         list LL=substpart(MB,ihp,0,rw);
632         def newR6=LL[1];
633         setring newR6;
634         ideal norid=endid;
635         ideal normap=endphi;
636         kill endid,endphi;
637         export norid;
638         export normap;
639         result=newR6;
640         result[size(result)+1]=delt;
641         setring BAS;
642         return(result);
643   }
644
645   if(y>=1)
646   {
647      "//   the dimension is:"; "";
648      dimSM;"";
649   }
650   if(size(#)>0)
651   {
652      if(attrib(i,"onlySingularAtZero"))
653      {
654         list JM=maxideal(1),maxideal(1);
655         attrib(JM[1],"isSB",1);
656         attrib(JM[2],"isRad",1);
657      }
658      else
659      {
660         ideal te=#[1],SM[2];
661         list JM=mstd(te);
662         kill te;
663         if( typeof(attrib(#[1],"isRad"))!="int" )
664         {
665            attrib(JM[2],"isRad",0);
666         }
667      }
668   }
669
670   if(attrib(i,"isPrim")==1)
671   {
672      attrib(SM[2],"isPrim",1);
673   }
674   else
675   {
676      attrib(SM[2],"isPrim",0);
677   }
678   if(attrib(i,"isIsolatedSingularity")==1)
679   {
680      attrib(SM[2],"isIsolatedSingularity",1);
681   }
682   else
683   {
684      attrib(SM[2],"isIsolatedSingularity",0);
685   }
686   if(attrib(i,"isCohenMacaulay")==1)
687   {
688      attrib(SM[2],"isCohenMacaulay",1);
689   }
690   else
691   {
692      attrib(SM[2],"isCohenMacaulay",0);
693   }
694   if(attrib(i,"isRegInCodim2")==1)
695   {
696      attrib(SM[2],"isRegInCodim2",1);
697   }
698   else
699   {
700      attrib(SM[2],"isRegInCodim2",0);
701   }
702   if(attrib(i,"isEquidimensional")==1)
703   {
704      attrib(SM[2],"isEquidimensional",1);
705   }
706   else
707   {
708      attrib(SM[2],"isEquidimensional",0);
709   }
710   if(attrib(i,"isCompleteIntersection")==1)
711   {
712      attrib(SM[2],"isCompleteIntersection",1);
713   }
714   else
715   {
716      attrib(SM[2],"isCompleteIntersection",0);
717   }
718   if(attrib(i,"onlySingularAtZero")==1)
719   {
720      attrib(SM[2],"onlySingularAtZero",1);
721   }
722   else
723   {
724      attrib(SM[2],"onlySingularAtZero",0);
725   }
726   if((attrib(SM[2],"isIsolatedSingularity")==1)&&(homog(SM[2])==1))
727   {
728      attrib(SM[2],"onlySingularAtZero",1);
729   }
730
731   //the smooth case
732   if(size(#)>0)
733   {
734      if(dim(JM[1])==-1)
735      {
736         if(y>=1)
737         {
738            "// the ideal was smooth";
739         }
740         MB=SM[2];
741         intvec rw;;
742         list LL=substpart(MB,ihp,0,rw);
743         def newR6=LL[1];
744         setring newR6;
745         ideal norid=endid;
746         ideal normap=endphi;
747         kill endid,endphi;
748         export norid;
749         export normap;
750         result=newR6;
751         result[size(result)+1]=delt;
752         setring BAS;
753         return(result);
754     }
755   }
756
757   //the zero-dimensional case
758   if((dim(SM[1])==0)&&(homog(SM[2])==1))
759   {
760      if(y>=1)
761      {
762         "// the ideal was zero-dimensional and homogeneous";
763      }
764      MB=maxideal(1);
765      intvec rw;
766      list LL=substpart(MB,ihp,0,rw);
767      def newR5=LL[1];
768      setring newR5;
769      ideal norid=endid;
770      ideal normap=endphi;
771      kill endid,endphi;
772      export norid;
773      export normap;
774      result=newR5;
775      result[size(result)+1]=delt;
776      setring BAS;
777      return(result);
778   }
779
780   //the one-dimensional case
781   //in this case it is a line because
782   //it is irreducible and homogeneous
783   if((dim(SM[1])==1)&&(attrib(SM[2],"isPrim")==1)
784        &&(homog(SM[2])==1))
785   {
786      if(y>=1)
787      {
788         "// the ideal defines a line";
789      }
790      MB=SM[2];
791      intvec rw;
792      list LL=substpart(MB,ihp,0,rw);
793      def newR4=LL[1];
794      setring newR4;
795      ideal norid=endid;
796      ideal normap=endphi;
797      kill endid,endphi;
798      export norid;
799      export normap;
800      result=newR4;
801      result[size(result)+1]=delt;
802      setring BAS;
803      return(result);
804   }
805
806   //the higher dimensional case
807   //we test first of all CohenMacaulay and
808   //complete intersection
809   if(((size(SM[2])+dim(SM[1]))==nvars(basering))&&(homog(SM[2])==1))
810   {
811      //test for complete intersection
812      attrib(SM[2],"isCohenMacaulay",1);
813      attrib(SM[2],"isCompleteIntersection",1);
814      attrib(SM[2],"isEquidimensional",1);
815      if(y>=1)
816      {
817         "// the ideal is a complete intersection";
818      }
819   }
820   if((attrib(SM[2],"onlySingularAtZero")==0)&&(size(i)==1))
821   {
822      int tau=vdim(std(i+jacob(i)));
823      if(tau>=0)
824      {
825        execute("ring BASL="+charstr(BAS)+",("+varstr(BAS)+"),ds;");
826        ideal i=imap(BAS,i);
827        int tauloc=vdim(std(i+jacob(i)));
828        setring BAS;
829        attrib(SM[2],"onlySingularAtZero",(tau==tauloc));
830        kill BASL;
831      }
832   }
833
834   //compute the singular locus
835   if((attrib(SM[2],"onlySingularAtZero")==0)&&(size(#)==0))
836   {
837      J=minor(jacob(SM[2]),nvars(basering)-dim(SM[1]));
838      if(y >=1 )
839      {
840         "// SB of singular locus will be computed";
841      }
842      ideal sin=J,SM[1];
843      list JM=mstd(sin);
844      attrib(JM[1],"isSB",1);
845
846      //JM[1] SB of singular locus, JM[2]=minbasis of singular locus
847      //SM[1] SB of the input ideal, SM[2] minbasis
848      if(y>=1)
849      {
850         "//   the dimension of the singular locus is:";"";
851         dim(JM[1]); "";
852      }
853
854      if(dim(JM[1])==-1)
855      {
856         if(y>=1)
857         {
858            "// the ideal is smooth";
859         }
860         MB=SM[2];
861         intvec rw;
862         list LL=substpart(MB,ihp,0,rw);
863         def newR3=LL[1];
864         setring newR3;
865         ideal norid=endid;
866         ideal normap=endphi;
867         kill endid,endphi;
868         export norid;
869         export normap;
870         result=newR3;
871         result[size(result)+1]=delt;
872         setring BAS;
873         return(result);
874      }
875      if(dim(JM[1])==0)
876      {
877         attrib(SM[2],"isIsolatedSingularity",1);
878         if(homog(SM[2])){attrib(SM[2],"onlySingularAtZero",1);}
879      }
880      if(dim(JM[1])<=dim(SM[1])-2)
881      {
882         attrib(SM[2],"isRegInCodim2",1);
883      }
884   }
885   else
886   {
887     if(size(#)==0)
888     {
889        list JM=maxideal(1),maxideal(1);
890
891        attrib(JM[1],"isSB",1);
892        if(dim(SM[1])>=2){attrib(SM[2],"isRegInCodim2",1);}
893     }
894   }
895   if((attrib(SM[2],"isRegInCodim2")==1)&&(attrib(SM[2],"isCohenMacaulay")==1))
896   {
897      if(y>=1)
898      {
899            "// the ideal was CohenMacaulay and regular in codimension 2";
900      }
901      MB=SM[2];
902      intvec rw;
903      list LL=substpart(MB,ihp,0,rw);
904      def newR6=LL[1];
905      setring newR6;
906      ideal norid=endid;
907      ideal normap=endphi;
908      kill endid,endphi;
909      export norid;
910      export normap;
911      result=newR6;
912      result[size(result)+1]=delt;
913      setring BAS;
914      return(result);
915   }
916
917   //if it is an isolated singularity only at 0 things are easier
918   //JM ideal of singular locus, SM ideal of variety
919   if(attrib(SM[2],"onlySingularAtZero"))         
920   {
921      attrib(SM[2],"isIsolatedSingularity",1);
922      ideal SL=simplify(reduce(maxideal(1),SM[1]),2);
923      //vars not contained in ideal
924      ideal Ann=quotient(SM[2],SL[1]);
925      ideal qAnn=simplify(reduce(Ann,SM[1]),2);
926      //qAnn=0 ==> the first var(=SL[1]) not contained in SM is a nzd of R/SM
927      if(size(qAnn)==0)
928      {
929         if(y>=1)
930         {
931            "";
932            "//   the ideal rad(J):";
933            "";
934            maxideal(1);
935            newline;
936         }
937         //again test for normality
938         //Hom(I,R)=R
939         list RR;
940         RR=SM[1],SM[2],maxideal(1),SL[1];
941
942         RR=HomJJ(RR,y);
943         if(RR[2]==0)
944         {
945            def newR=RR[1];
946            setring newR;
947            map psi=BAS,endphi;
948            list tluser=normalizationPrimes(endid,psi(ihp),delt+RR[3],an);
949            setring BAS;
950            return(tluser);
951         }
952         MB=SM[2];
953         execute("ring newR7="+charstr(basering)+",("+varstr(basering)+"),("
954                      +ordstr(basering)+");");
955         ideal norid=fetch(BAS,MB);
956         ideal normap=fetch(BAS,ihp);
957         delt=delt+RR[3];
958         export norid;
959         export normap;
960         result=newR7;
961         result[size(result)+1]=delt;
962         setring BAS;
963         return(result);
964
965       }
966      //Now the case where qAnn!=0, i.e.SL[1] is a zero divisor of R/SM
967      //and we have found a splitting: id and id1
968      //id=Ann defines components of R/SM in the complement of V(SL[1])
969      //id1 defines components of R/SM in the complement of V(id)
970       else
971       {
972          ideal id=Ann;
973          attrib(id,"isCohenMacaulay",0);
974          attrib(id,"isPrim",0);
975          attrib(id,"isIsolatedSingularity",1);
976          attrib(id,"isRegInCodim2",0);
977          attrib(id,"isCompleteIntersection",0);
978          attrib(id,"isEquidimensional",0);
979          attrib(id,"onlySingularAtZero",1);
980
981          ideal id1=quotient(SM[2],Ann);
982          //ideal id=SL[1],SM[2];
983          attrib(id1,"isCohenMacaulay",0);
984          attrib(id1,"isPrim",0);
985          attrib(id1,"isIsolatedSingularity",1);
986          attrib(id1,"isRegInCodim2",0);
987          attrib(id1,"isCompleteIntersection",0);
988          attrib(id1,"isEquidimensional",0);
989          attrib(id1,"onlySingularAtZero",1);
990         
991          ideal t1=id,id1;
992          int mul=vdim(std(t1));
993          kill t1;
994
995          keepresult1=normalizationPrimes(id,ihp,0);
996
997          keepresult2=normalizationPrimes(id1,ihp,0);
998           
999          delt=delt+mul+keepresult1[size(keepresult1)]
1000                         +keepresult1[size(keepresult1)];
1001
1002          for(lauf=1;lauf<=size(keepresult2)-1;lauf++)
1003          {
1004             keepresult1=insert(keepresult1,keepresult2[lauf]);
1005          }
1006          keepresult1[size(keepresult1)]=delt;
1007          return(keepresult1);
1008       }
1009   }
1010
1011   //test for non-normality
1012   //Hom(I,I)<>R
1013   //we can use Hom(I,I) to continue
1014   ideal SL=simplify(reduce(JM[2],SM[1]),2);
1015   ideal Ann=quotient(SM[2],SL[1]);
1016   ideal qAnn=simplify(reduce(Ann,SM[1]),2);
1017
1018   if(size(qAnn)==0)
1019   {
1020      list RR;
1021      list RS;
1022      //now we have to compute the radical
1023      if(y>=1)
1024      {
1025         "// radical computation of singular locus";
1026      }
1027
1028      J=radical(JM[2]);   //the singular locus
1029      JM=mstd(J);
1030     
1031      if((vdim(JM[1])==1)&&(size(reduce(J,std(maxideal(1))))==0))
1032      {
1033         attrib(SM[2],"onlySingularAtZero",1);
1034      }
1035      if(y>=1)
1036      {
1037        "//   radical is equal to:";"";
1038        J;
1039        "";
1040      }
1041
1042      if(deg(SL[1])>deg(J[1]))
1043      {
1044         Ann=quotient(SM[2],J[1]);
1045         qAnn=simplify(reduce(Ann,SM[1]),2);
1046         if(size(qAnn)==0){SL[1]=J[1];}
1047      }
1048
1049      //evtl. fuer SL[1] anderen Nichtnullteiler aus J waehlen
1050      RR=SM[1],SM[2],JM[2],SL[1];
1051
1052      //   evtl eine geeignete Potenz von JM?
1053     if(y>=1)
1054     {
1055        "// compute Hom(rad(J),rad(J))";
1056     }
1057
1058     RS=HomJJ(RR,y);
1059
1060      if(RS[2]==1)
1061      {
1062         def lastR=RS[1];
1063         setring lastR;
1064         map psi1=BAS,endphi;
1065         ideal norid=endid;
1066         ideal normap=psi1(ihp);
1067         kill endid,endphi;
1068         export norid;
1069         export normap;
1070         result=lastR;
1071         result[size(result)+1]=delt+RS[3];
1072         setring BAS;
1073         return(result);
1074      }
1075      int n=nvars(basering);
1076      ideal MJ=JM[2];
1077
1078      def newR=RS[1];
1079      setring newR;
1080
1081      map psi=BAS,endphi;
1082      list tluser=
1083             normalizationPrimes(endid,psi(ihp),delt+RS[3],psi(MJ));
1084      setring BAS;
1085      return(tluser);
1086   }
1087    // A component with singular locus the whole component found
1088   if( Ann == 1)
1089   {
1090      "// Input appeared not to be a radical ideal!";
1091      "// A (everywhere singular) component with ideal";
1092      "// equal to its Jacobian ideal was found";
1093      "// Procedure will stop with partial result computed so far";"";
1094
1095         MB=SM[2];
1096         intvec rw;
1097         list LL=substpart(MB,ihp,0,rw);
1098         def newR6=LL[1];
1099         setring newR6;
1100         ideal norid=endid;
1101         ideal normap=endphi;
1102         kill endid,endphi;
1103         export norid;
1104         export normap;
1105         result=newR6;
1106         result[size(result)+1]=delt;
1107         setring BAS;
1108         return(result);
1109   }
1110   else
1111   {
1112      int equi=attrib(SM[2],"isEquidimensional");
1113      int oSAZ=attrib(SM[2],"onlySingularAtZero");
1114      int isIs=attrib(SM[2],"isIsolatedSingularity");
1115
1116      ideal new1=Ann;
1117      ideal new2=quotient(SM[2],Ann);
1118      //ideal new2=SL[1],SM[2];
1119
1120      int mul;
1121      if(equi&&isIs)
1122      {
1123          ideal t2=new1,new2;
1124          mul=vdim(std(t2));
1125      }
1126      execute("ring newR1="+charstr(basering)+",("+varstr(basering)+"),("
1127                      +ordstr(basering)+");");
1128      if(y>=1)
1129      {
1130         "// zero-divisor found";
1131      }
1132      ideal vid=fetch(BAS,new1);
1133      ideal ihp=fetch(BAS,ihp);
1134      attrib(vid,"isCohenMacaulay",0);
1135      attrib(vid,"isPrim",0);
1136      attrib(vid,"isIsolatedSingularity",isIs);
1137      attrib(vid,"isRegInCodim2",0);
1138      attrib(vid,"onlySingularAtZero",oSAZ);
1139      attrib(vid,"isEquidimensional",equi);     
1140      attrib(vid,"isCompleteIntersection",0);
1141
1142      keepresult1=normalizationPrimes(vid,ihp,0);
1143      int delta1=keepresult1[size(keepresult1)];
1144      setring BAS;
1145
1146      execute("ring newR2="+charstr(basering)+",("+varstr(basering)+"),("
1147                      +ordstr(basering)+");");
1148
1149      ideal vid=fetch(BAS,new2);
1150      ideal ihp=fetch(BAS,ihp);
1151      attrib(vid,"isCohenMacaulay",0);
1152      attrib(vid,"isPrim",0);
1153      attrib(vid,"isIsolatedSingularity",isIs);
1154      attrib(vid,"isRegInCodim2",0);
1155      attrib(vid,"isEquidimensional",equi);     
1156      attrib(vid,"isCompleteIntersection",0);
1157      attrib(vid,"onlySingularAtZero",oSAZ);
1158
1159      keepresult2=normalizationPrimes(vid,ihp,0);
1160      int delta2=keepresult2[size(keepresult2)];
1161
1162      setring BAS;
1163     
1164      for(lauf=1;lauf<=size(keepresult2)-1;lauf++)
1165      {
1166         keepresult1=insert(keepresult1,keepresult2[lauf]);
1167      }
1168      keepresult1[size(keepresult1)]=delt+mul+delta1+delta2;
1169      return(keepresult1);
1170   }
1171}
1172example
1173{ "EXAMPLE:";echo = 2;
1174   // Huneke
1175   ring qr=31991,(a,b,c,d,e),dp;
1176   ideal i=
1177   5abcde-a5-b5-c5-d5-e5,
1178   ab3c+bc3d+a3be+cd3e+ade3,
1179   a2bc2+b2cd2+a2d2e+ab2e2+c2de2,
1180   abc5-b4c2d-2a2b2cde+ac3d2e-a4de2+bcd2e3+abe5,
1181   ab2c4-b5cd-a2b3de+2abc2d2e+ad4e2-a2bce3-cde5,
1182   a3b2cd-bc2d4+ab2c3e-b5de-d6e+3abcd2e2-a2be4-de6,
1183   a4b2c-abc2d3-ab5e-b3c2de-ad5e+2a2bcde2+cd2e4,
1184   b6c+bc6+a2b4e-3ab2c2de+c4d2e-a3cde2-abd3e2+bce5;
1185
1186   list pr=normalizationPrimes(i);
1187   def r1=pr[1];
1188   setring r1;
1189   norid;
1190   normap;
1191}
1192///////////////////////////////////////////////////////////////////////////////
1193static proc substpart(ideal endid, ideal endphi, int homo, intvec rw)
1194
1195"//Repeated application of elimpart to endid, until no variables can be
1196//directy substituded. homo=1 if input is homogeneous, rw contains
1197//original weights, endphi (partial) normalization map";
1198
1199{
1200   def newRing=basering;
1201   int ii,jj;
1202   map phi = basering,maxideal(1);
1203
1204   list Le = elimpart(endid);
1205                                     //this proc and the next loop try to
1206   int q = size(Le[2]);              //substitute as many variables as possible
1207   intvec rw1 = 0;                   //indices of substituted variables
1208   rw1[nvars(basering)] = 0;
1209   rw1 = rw1+1;
1210
1211   while( size(Le[2]) != 0 )
1212   {
1213      endid = Le[1];
1214      map ps = newRing,Le[5];
1215
1216      phi = ps(phi);
1217      for(ii=1;ii<=size(Le[2])-1;ii++)
1218      {
1219         phi=phi(phi);
1220      }
1221      //eingefuegt wegen x2-y2z2+z3
1222      kill ps;
1223
1224      for( ii=1; ii<=size(rw1); ii++ )
1225      {
1226         if( Le[4][ii]==0 )
1227         {
1228            rw1[ii]=0;                             //look for substituted vars
1229         }
1230      }
1231      Le=elimpart(endid);
1232      q = q + size(Le[2]);
1233   }
1234   endphi = phi(endphi);
1235
1236//---------- return -----------------------------------------------------------
1237// in the homogeneous case put weights for the remaining vars correctly, i.e.
1238// delete from rw those weights for which the corresponding entry of rw1 is 0
1239
1240   if (homo==1 && nvars(newRing)-q >1 && size(endid) >0 )
1241   {
1242      jj=1;
1243      for( ii=2; ii<size(rw1); ii++)
1244      {
1245         jj++;
1246         if( rw1[ii]==0 )
1247         {
1248            rw=rw[1..jj-1],rw[jj+1..size(rw)];
1249            jj=jj-1;
1250         }
1251      }
1252      if( rw1[1]==0 ) { rw=rw[2..size(rw)]; }
1253      if( rw1[size(rw1)]==0 ){ rw=rw[1..size(rw)-1]; }
1254
1255      ring lastRing = char(basering),(T(1..nvars(newRing)-q)),(a(rw),dp);
1256   }
1257   else
1258   {
1259      ring lastRing = char(basering),(T(1..nvars(newRing)-q)),dp;
1260   }
1261
1262   ideal lastmap;
1263   q = 1;
1264   for(ii=1; ii<=size(rw1); ii++ )
1265   {
1266      if ( rw1[ii]==1 ) { lastmap[ii] = T(q); q=q+1; }
1267      if ( rw1[ii]==0 ) { lastmap[ii] = 0; }
1268   }
1269   map phi1 = newRing,lastmap;
1270   ideal endid  = phi1(endid);
1271   ideal endphi = phi1(endphi);
1272   export(endid);
1273   export(endphi);
1274   list L = lastRing;
1275   setring newRing;
1276   return(L);
1277}
1278/////////////////////////////////////////////////////////////////////////////
1279
1280proc genus(ideal I,list #)
1281"USAGE:   genus(I) or genus(i,1); I a 1-dimensional ideal
1282RETURN:  an integer, the geometric genus p_g = p_a - delta of the projective
1283         curve defined by I, where p_a is the arithmetic genus.
1284NOTE:    delta is the sum of all local delta-invariants of the singularities,
1285         i.e. dim(R'/R), R' the normalization of the local ring R of the
1286         singularity.
1287         genus(i,1) uses the normalization to compute delta. Usually this
1288         is slow but sometimes not.
1289EXAMPLE: example genus; shows an example
1290"
1291{
1292   int w = printlevel-voice+2;  // w=printlevel (default: w=0)
1293
1294   def R=basering;
1295
1296   if(homog(I))
1297   {
1298      execute("ring newR=("+charstr(R)+"),("+varstr(R)+"),dp;");
1299      ideal I=imap(R,I); 
1300   }
1301   else
1302   {
1303      execute("ring newR=("+charstr(R)+"),("+varstr(R)+",@t),dp;");
1304      ideal I=imap(R,I); 
1305      I=homog(std(I),@t);
1306   }
1307   ideal J=std(I);
1308   if((dim(J)!=2)||((nvars(basering)==2)&&(dim(J)!=1)))
1309   {
1310      ERROR("This is not a curve");
1311   }
1312   if((nvars(basering)<=3)&&(size(J)>1))
1313   {
1314       ERROR("This is not equidimensional");
1315   }
1316   
1317   intvec hp=hilbPoly(J);
1318   int p_a=1-hp[1];
1319   int d=hp[2];
1320
1321   if(w>=1)
1322   {
1323      "";"The ideal of the projective curve:";"";J;"";
1324      "The coefficients of the Hilbert polynomial";hp;
1325      "arithmetic genus:";p_a;
1326      "degree:";d;"";
1327   }
1328   
1329   intvec v = hilb(J,1);
1330   int o,i;
1331   
1332   if(nvars(basering)>3)
1333   {
1334      map phi=newR,maxideal(1);
1335      int de;
1336      ideal K,L;
1337      poly m=var(4);
1338      for(i=5;i<=nvars(basering);i++){m=m*var(i);}
1339      K=eliminate(J,m,v);
1340      if(size(K)==1){de=deg(K[1]);}
1341      m=var(1);
1342      for(i=2;i<=nvars(basering)-3;i++){m=m*var(i);}
1343      i=0;
1344      while(d!=de)
1345      {
1346         o=1;
1347         i++;
1348         K=phi(J);
1349         K=eliminate(K,m,v);
1350         if(size(K)==1){de=deg(K[1]);}
1351         if(i==5)
1352         {
1353            K=reduce(equidimMax(J),J);
1354            if(size(K)!=0){ERROR("This is not equidimensional");}
1355          }
1356          if(i==10){ERROR("did not find a good projection");}
1357          L=sparsetriag(nvars(newR),nvars(newR),80-5*i,i)*transpose(maxideal(1));
1358          phi=newR,L;
1359      }
1360      J=K;
1361   }
1362   poly p=J[1];
1363   
1364   if(nvars(basering)==2)
1365   {
1366      if(deg(squarefree(p))<deg(p)){ERROR("Curve is not reduced");}
1367      return(-deg(p)+1);
1368   }
1369   
1370   execute("ring S=("+charstr(R)+"),(x,y,t),dp;");
1371   ideal L=maxideal(1);
1372   execute("ring C=("+charstr(R)+"),(x,y),ds;");
1373   ideal I;
1374   execute("ring A=("+charstr(R)+"),(x,t),dp;");
1375   map phi=S,1,x,t;
1376   map psi=S,x,1,t;
1377   poly g,h;
1378   ideal I,I1;
1379   execute("ring B=("+charstr(R)+"),(x,t),ds;");
1380   
1381   setring S;
1382   if(o)
1383   {
1384     for(i=1;i<=nvars(newR)-3;i++){L[i]=0;}
1385     L=L,maxideal(1);
1386   }   
1387   map sigma=newR,L;
1388   poly F=sigma(p);
1389   if(w>=1){"the projected curve:";"";F;"";}
1390   
1391   kill newR;
1392   
1393   int genus=(d-1)*(d-2)/2;
1394   if(w>=1){"the arithmetic genus of the plane curve:";genus;pause();}
1395 
1396   int delt,deltaloc,deltainf,tau,tauinf,cusps,iloc,iglob,l,nsing,
1397       tauloc,tausing,k,rat,nbranchinf,nbranch,nodes,cuspsinf,nodesinf;
1398   list inv;
1399
1400   if(w>=1)
1401     {"";"analyse the singularities at oo";"";"singular locus at (1,x,0):";"";}
1402   setring A;       
1403   g=phi(F);
1404   h=psi(F);
1405   I=g,jacob(g),var(2);
1406   I=std(I);
1407   if(deg(I[1])>0)
1408   {
1409      list qr=minAssGTZ(I);
1410      if(w>=1){qr;"";}
1411     
1412      for(k=1;k<=size(qr);k++)
1413      {
1414         if(w>=1){ nsing=nsing+vdim(std(qr[k]));}
1415         inv=deltaLoc(g,qr[k]);
1416         deltainf=deltainf+inv[1];
1417         tauinf=tauinf+inv[2];
1418         l=vdim(std(qr[k]));
1419         if(inv[2]==l){nodesinf=nodesinf+l;}
1420         if(inv[2]==2*l){cuspsinf=cuspsinf+l;}         
1421         nbranchinf=nbranchinf+inv[3];
1422      }
1423   }
1424   else
1425   {
1426     if(w>=1){"            the curve is smooth at (1,x,0)";"";}
1427   }
1428   if(w>=1){"singular locus at (0,1,0):";"";}
1429   inv=deltaLoc(h,maxideal(1));
1430   if((w>=1)&&(inv[2]!=0)){ nsing++;}
1431   deltainf=deltainf+inv[1];
1432   tauinf=tauinf+inv[2];
1433   if(inv[2]==1){nodesinf=nodeainf++;}
1434   if(inv[2]==2){cuspsinf=cuspsinf++;}         
1435   
1436   if((w>=1)&&(inv[2]==0)){"            the curve is smooth at (0,1,0)";"";}
1437   if(inv[2]>0){nbranchinf=nbranchinf+inv[3];}
1438 
1439   if(w>=1)
1440   {
1441      if(tauinf==0)
1442      {
1443        "            the curve is smooth at oo";"";
1444      }
1445      else
1446      {
1447         "number of singularities at oo:";nsing;
1448         "nodes at oo:";nodesinf;
1449         "cusps at oo:";cuspsinf;
1450         "branches at oo:";nbranchinf;
1451         "Tjurina number at oo:";tauinf;
1452         "delta at oo:";deltainf;
1453         "Milnor number at oo:";2*deltainf-nbranchinf+nsing;
1454         pause();
1455      }
1456      "singularities at (x,y,1):";"";
1457   }
1458   execute("ring newR=("+charstr(R)+"),(x,y),dp;");
1459   //the singularities at the affine part
1460   map sigma=S,var(1),var(2),1;
1461   ideal I=sigma(F);
1462
1463   if(size(#)!=0)     
1464   {                              //uses the normalization to compute delta
1465      list nor=normal(I,"wd");
1466      delt=nor[size(nor)];
1467      genus=genus-delt-deltainf;
1468      setring R;
1469      return(genus);
1470   }
1471
1472   ideal I1=jacob(I);
1473   matrix Hess[2][2]=jacob(I1);
1474   ideal ID=I+I1+ideal(det(Hess));//singular locus of I+I1
1475   
1476   ideal radID=std(radical(ID));//the non-nodal locus
1477   if(w>=1){"the non-nodal locus:";"";radID;pause();"";}
1478   if(deg(radID[1])==0)
1479   {
1480     ideal IDsing=1;
1481   }
1482   else
1483   {
1484     ideal IDsing=minor(jacob(ID),2)+radID;//singular locus of ID
1485   }
1486   
1487   iglob=vdim(std(IDsing));
1488
1489   if(iglob!=0)//computation of the radical of IDsing
1490   {
1491      ideal radIDsing=reduce(IDsing,radID);
1492      if(size(radIDsing)==0)
1493      {
1494         radIDsing=radID;
1495         attrib(radIDsing,"isSB",1);
1496      }
1497      else
1498      {
1499         radIDsing=std(radical(IDsing));
1500      }
1501      iglob=vdim(radIDsing);
1502      if((w>=1)&&(iglob))
1503          {"the non-nodal-cuspidal locus:";radIDsing;pause();"";}
1504   }
1505   cusps=vdim(radID)-iglob;
1506   nsing=nsing+cusps;
1507   
1508   if(iglob==0)
1509   {
1510      if(w>=1){"             there are only cusps and nodes";"";}
1511      tau=vdim(std(I+jacob(I)));
1512      tauinf=tauinf+tau;
1513      nodes=tau-2*cusps;
1514      delt=nodes+cusps;
1515      nbranch=2*tau-3*cusps;
1516      nsing=nsing+nodes;
1517   }
1518   else
1519   {
1520       if(w>=1){"the non-nodal-cuspidal singularities";"";}
1521       setring C;                     
1522       ideal I1=imap(newR,IDsing);
1523       iloc=vdim(std(I1));
1524       if(iglob==iloc)
1525       {
1526          if(w>=1){"only cusps and nodes outside (0,0,1)";}
1527          setring newR;
1528          tau=vdim(std(I+jacob(I)));
1529          tauinf=tauinf+tau;
1530          inv=deltaLoc(I[1],maxideal(1));
1531          delt=inv[1];
1532          tauloc=inv[2];
1533          nodes=tau-tauloc-2*cusps;
1534          nsing=nsing+nodes;
1535          nbranch=inv[3]+ 2*nodes+cusps;         
1536          delt=delt+nodes+cusps;
1537          if((w>=1)&&(inv[2]==0)){"smooth at (0,0,1)";}
1538        }
1539        else
1540        {
1541           setring newR;
1542           list pr=minAssGTZ(IDsing);
1543           if(w>=1){pr;}
1544           
1545           for(k=1;k<=size(pr);k++)
1546           {
1547              if(w>=1){nsing=nsing+vdim(std(pr[k]));}
1548              inv=deltaLoc(I[1],pr[k]);
1549              delt=delt+inv[1];
1550              tausing=tausing+inv[2];
1551              nbranch=nbranch+inv[3];
1552           }
1553           tau=vdim(std(I+jacob(I)));
1554           tauinf=tauinf+tau;
1555           nodes=tau-tausing-2*cusps;
1556           nsing=nsing+nodes;
1557           delt=delt+nodes+cusps; 
1558           nbranch=nbranch+2*nodes+cusps;           
1559        }
1560   }
1561   genus=genus-delt-deltainf;
1562   if(w>=1)
1563   {
1564      "The projected plane curve has locally:";"";
1565      "singularities:";nsing;
1566      "branches:";nbranch+nbranchinf;
1567      "nodes:"; nodes+nodesinf;
1568      "cusps:";cusps+cuspsinf;
1569      "Tjurina number:";tauinf;
1570      "Milnor number:";2*(delt+deltainf)-nbranch-nbranchinf+nsing;
1571      "delta of the projected curve:";delt+deltainf;
1572      "delta of the curve:";p_a-genus;
1573      "genus:";genus;
1574      "====================================================";
1575      "";
1576   }
1577   setring R;
1578   return(genus);
1579}
1580example
1581{ "EXAMPLE:"; echo = 2;
1582   ring r=0,(x,y),dp;
1583   ideal i=y^9 - x^2*(x - 1)^9;
1584   genus(i);
1585}
1586
1587///////////////////////////////////////////////////////////////////////////////
1588proc deltaLoc(poly f,ideal singL)
1589"USAGE:  deltaLoc(f,J);  f poly, J ideal
1590ASSUME: f is reduced bivariate polynomial; basering has exactly two variables;
1591        J is irreducible prime component of the singular locus of f (e.g., one
1592        entry of the output of @code{minAssGTZ(I);}, I = <f,jacob(f)>).
1593RETURN:  list L:
1594@texinfo
1595@table @asis
1596@item @code{L[1]}; int:
1597         the sum of (local) delta invariants of f at the (conjugated) singular
1598         points given by J.
1599@item @code{L[2]}; int:
1600         the sum of (local) Tjurina numbers of f at the (conjugated) singular
1601         points given by J.
1602@item @code{L[3]}; int:
1603         the sum of (local) number of branches of f at the (conjugated)
1604         singular points given by J.
1605@end table
1606@end texinfo
1607NOTE:    procedure makes use of @code{execute}; increasing printlevel displays
1608         more comments (default: printlevel=0).
1609SEE ALSO: delta, tjurina
1610KEYWORDS: delta invariant; Tjurina number
1611EXAMPLE: example deltaLoc;  shows an example
1612"
1613{
1614   option(redSB);
1615   def R=basering;
1616   execute("ring S=("+charstr(R)+"),(x,y),lp;");
1617   map phi=R,x,y;
1618   ideal singL=phi(singL);
1619   singL=std(singL);
1620   int d=vdim(singL);
1621   poly f=phi(f);
1622   int i;
1623   int w = printlevel-voice+2;  // w=printlevel (default: w=0)
1624   if(d==1)
1625   {
1626      map alpha=S,var(1)-singL[2][2],var(2)-singL[1][2];
1627      f=alpha(f);
1628
1629      execute("ring C=("+charstr(S)+"),("+varstr(S)+"),ds;");
1630      poly f=imap(S,f);
1631      ideal singL=imap(S,singL);
1632      if((w>=1)&&(ord(f)>=2))
1633      {
1634        "local analysis of the singularities";"";
1635        basering;
1636        singL;
1637        f;
1638        pause();
1639      }
1640   }
1641   else
1642   {
1643      poly p;
1644      poly c;
1645      map psi;
1646      number co;
1647     
1648      while((deg(lead(singL[1]))>1)&&(deg(lead(singL[2]))>1))
1649      {
1650         psi=S,x,y+random(-100,100)*x;
1651         singL=psi(singL);
1652         singL=std(singL);
1653          f=psi(f);
1654      }
1655     
1656      if(deg(lead(singL[2]))==1)
1657      {
1658         p=singL[1];
1659         c=singL[2]-lead(singL[2]);
1660         co=leadcoef(singL[2]);
1661      }
1662      if(deg(lead(singL[1]))==1)
1663      {
1664         psi=S,y,x;
1665         f=psi(f);
1666         singL=psi(singL);
1667         p=singL[2];
1668         c=singL[1]-lead(singL[1]);;
1669         co=leadcoef(singL[1]);
1670      }
1671     
1672      execute("ring B=("+charstr(S)+"),a,dp;");
1673      map beta=S,a,a;
1674      poly p=beta(p);
1675     
1676      execute("ring C=("+charstr(S)+",a),("+varstr(S)+"),ds;");
1677      number p=number(imap(B,p));
1678     
1679      minpoly=p;
1680      //number c=number(imap(S,c));
1681      map iota=S,a,a;
1682      number c=number(iota(c));
1683      number co=iota(co);
1684     
1685      map alpha=S,x-c/co,y+a;
1686      poly f=alpha(f);
1687      f=cleardenom(f);
1688      if((w>=1)&&(ord(f)>=2))
1689      {
1690        "local analysis of the singularities";"";
1691        basering;
1692        alpha;
1693        f;
1694        pause();
1695        "";
1696      }
1697   }
1698   option(noredSB);
1699   ideal fstd=std(ideal(f)+jacob(f));
1700   poly hc=highcorner(fstd);
1701   int tau=vdim(fstd);     
1702   int o=ord(f);
1703   int delt,nb;
1704   
1705   if(tau==0)                 //smooth case
1706   {
1707      setring R;
1708      return(list(0,0,1));
1709   }
1710   if((char(basering)>=181)||(char(basering)==0))
1711   {
1712      if(o==2)                //A_k-singularity
1713      {
1714        if(w>=1){"A_k-singularity";"";}       
1715         setring R;
1716         delt=(tau+1)/2;
1717         return(list(d*delt,d*tau,d*(2*delt-tau+1)));   
1718      }
1719      if((lead(f)==var(1)*var(2)^2)||(lead(f)==var(1)^2*var(2)))
1720      {
1721        if(w>=1){"D_k- singularity";"";}
1722       
1723         setring R;
1724         delt=(tau+2)/2;
1725         return(list(d*delt,d*tau,d*(2*delt-tau+1)));
1726      }
1727
1728      int mu=vdim(std(jacob(f)));
1729      poly g=f+var(1)^mu+var(2)^mu;  //to obtain a convenient Newton-polygon
1730 
1731      list NP=newtonpoly(g);
1732      if(w>=1){"Newton-Polygon:";NP;"";}
1733      int s=size(NP);
1734       
1735      if(is_NND(f,mu,NP))     
1736      { // the Newton-polygon is non-degenerate                           
1737        // compute nb, the number of branches
1738        for(i=1;i<=s-1;i++)
1739        {
1740          nb=nb+gcd(NP[i][2]-NP[i+1][2],NP[i][1]-NP[i+1][1]);
1741        }
1742        if(w>=1){"Newton-Polygon is non-degenerated";"";}
1743        return(list(d*(mu+nb-1)/2,d*tau,d*nb));
1744      }
1745
1746      if(w>=1){"Newton-Polygon is degenerated";"";}
1747
1748      // the following can certainly be made more efficient when replacing
1749      // 'reddevelop' (used only for computing number of branches) by
1750      // successive blowing-up + test if Newton polygon degenerate:
1751      if(s>2)    //  splitting of f
1752      {
1753         if(w>=1){"Newton polygon can be used for splitting";"";}
1754         intvec v=NP[1][2]-NP[2][2],NP[2][1];
1755         int de=w_deg(g,v);
1756         int st=w_deg(hc,v)+v[1]+v[2];
1757         poly f1=var(2)^NP[2][2];
1758         poly f2=jet(g,de,v)/var(2)^NP[2][2];
1759         poly h=g-f1*f2;
1760         de=w_deg(h,v);
1761         poly k;
1762         ideal wi=var(2)^NP[2][2],f2;
1763         matrix li;
1764         while(de<st)
1765         {
1766           k=jet(h,de,v);
1767           li=lift(wi,k);
1768           f1=f1+li[2,1];
1769           f2=f2+li[1,1];
1770           h=g-f1*f2;
1771           de=w_deg(h,v);
1772         }
1773         nb=deltaLoc(f1,maxideal(1))[3]+deltaLoc(f2,maxideal(1))[3];
1774         return(list(d*(mu+nb-1)/2,d*tau,d*nb));
1775      }
1776
1777      f=jet(f,deg(hc)+2);
1778      if(w>=1){"now we have to use Hamburger-Noether (Puiseux) expansion";}
1779      list hne=reddevelop(f);
1780      nb=size(hne);
1781      setring R;
1782      kill HNEring;       
1783      return(list(d*(mu+nb-1)/2,d*tau,d*nb));
1784   }
1785   else             //the case of small characteristic
1786   {
1787      f=jet(f,deg(hc)+2);
1788      if(w>=1){"now we have to use Hamburger-Noether (Puiseux) expansion";}
1789      delt=delta(f);
1790      return(list(d*delt,d*tau,d));
1791   }
1792}
1793example
1794{ "EXAMPLE:"; echo = 2;
1795  ring r=0,(x,y),dp;
1796  poly f=(x2+y^2-1)^3 +27x2y2;
1797  ideal I=f,jacob(f);
1798  I=std(I);
1799  list qr=minAssGTZ(I);
1800  size(qr);
1801  // each component of the singular locus either describes a cusp or a pair
1802  // of conjugated nodes:
1803  deltaLoc(f,qr[1]);
1804  deltaLoc(f,qr[2]);
1805  deltaLoc(f,qr[3]);
1806  deltaLoc(f,qr[4]);
1807  deltaLoc(f,qr[5]);
1808  deltaLoc(f,qr[6]);
1809}
1810///////////////////////////////////////////////////////////////////////////////
1811// compute the weighted degree of p
1812static proc w_deg(poly p, intvec v)
1813{
1814   if(p==0){return(-1);}
1815   int d=0;
1816   while(jet(p,d,v)==0){d++;}
1817   d=(transpose(leadexp(jet(p,d,v)))*v)[1];
1818   return(d); 
1819}
1820
1821//proc hilbPoly(ideal J)
1822//{ 
1823//   poly hp;
1824//   int i;
1825//   if(!attrib(J,"isSB")){J=std(J);}
1826//   intvec v = hilb(J,2);
1827//   for(i=1; i<=size(v); i++){ hp=hp+v[i]*(var(1)-i+2);}
1828//   return(hp);
1829//}
1830
1831///////////////////////////////////////////////////////////////////////////
1832
1833/*
1834                           Examples:
1835LIB"normal.lib";
1836//Huneke
1837ring qr=31991,(a,b,c,d,e),dp;
1838ideal i=
18395abcde-a5-b5-c5-d5-e5,
1840ab3c+bc3d+a3be+cd3e+ade3,
1841a2bc2+b2cd2+a2d2e+ab2e2+c2de2,
1842abc5-b4c2d-2a2b2cde+ac3d2e-a4de2+bcd2e3+abe5,
1843ab2c4-b5cd-a2b3de+2abc2d2e+ad4e2-a2bce3-cde5,
1844a3b2cd-bc2d4+ab2c3e-b5de-d6e+3abcd2e2-a2be4-de6,
1845a4b2c-abc2d3-ab5e-b3c2de-ad5e+2a2bcde2+cd2e4,
1846b6c+bc6+a2b4e-3ab2c2de+c4d2e-a3cde2-abd3e2+bce5;
1847
1848
1849//Vasconcelos (dauert laenger: 70 sec)
1850ring r=32003,(x,y,z,w,t),dp;
1851ideal i=
1852x2+zw,
1853y3+xwt,
1854xw3+z3t+ywt2,
1855y2w4-xy2z2t-w3t3;
1856
1857//Theo1
1858ring r=32003,(x,y,z),wp(2,3,6);
1859ideal i=zy2-zx3-x6;
1860
1861//Theo1a (CohenMacaulay and regular in codimension 2)
1862ring r=32003,(x,y,z,u),wp(2,3,6,6);
1863ideal i=zy2-zx3-x6+u2;
1864
1865
1866//Theo2
1867ring r=32003,(x,y,z),wp(3,4,12);
1868ideal i=z*(y3-x4)+x8;
1869
1870//Theo2a
1871ring r=32003,(T(1..4)),wp(3,4,12,17);
1872ideal i=
1873T(1)^8-T(1)^4*T(3)+T(2)^3*T(3),
1874T(1)^4*T(2)^2-T(2)^2*T(3)+T(1)*T(4),
1875T(1)^7+T(1)^3*T(2)^3-T(1)^3*T(3)+T(2)*T(4),
1876T(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;
1877
1878//Theo3
1879ring r=32003,(x,y,z),wp(3,5,15);
1880ideal i=z*(y3-x5)+x10;
1881
1882
1883//Theo4
1884ring r=32003,(x,y,z),dp;
1885ideal i=(x-y)*(x-z)*(y-z);
1886
1887//Theo5
1888ring r=32003,(x,y,z),wp(2,1,2);
1889ideal i=z3-xy4;
1890
1891//Theo6
1892ring r=32003,(x,y,z),dp;
1893ideal i=x2y2+x2z2+y2z2;
1894
1895ring r=32003,(a,b,c,d,e,f),dp;
1896ideal i=
1897bf,
1898af,
1899bd,
1900ad;
1901
1902//ist CM
1903//Sturmfels
1904ring r=32003,(b,s,t,u,v,w,x,y,z),dp;
1905ideal i=
1906bv+su,
1907bw+tu,
1908sw+tv,
1909by+sx,
1910bz+tx,
1911sz+ty,
1912uy+vx,
1913uz+wx,
1914vz+wy,
1915bvz;
1916
1917//J S/Y
1918ring r=32003,(x,y,z,t),dp;
1919ideal i=
1920x2z+xzt,
1921xyz,
1922xy2-xyt,
1923x2y+xyt;
1924
1925//St_S/Y
1926ring r=32003,(b,s,t,u,v,w,x,y,z),dp;
1927ideal i=
1928wy-vz,
1929vx-uy,
1930tv-sw,
1931su-bv,
1932tuy-bvz;
1933
1934//Horrocks:
1935ring r=32003,(a,b,c,d,e,f),dp;
1936ideal i=
1937adef-16000be2f+16001cef2,
1938ad2f+8002bdef+8001cdf2,
1939abdf-16000b2ef+16001bcf2,
1940a2df+8002abef+8001acf2,
1941ad2e-8000bde2-7999cdef,
1942acde-16000bce2+16001c2ef,
1943a2de-8000abe2-7999acef,
1944acd2+8002bcde+8001c2df,
1945abd2-8000b2de-7999bcdf,
1946a2d2+9603abde-10800b2e2-9601acdf+800bcef+11601c2f2,
1947abde-8000b2e2-acdf-16001bcef-8001c2f2,
1948abcd-16000b2ce+16001bc2f,
1949a2cd+8002abce+8001ac2f,
1950a2bd-8000ab2e-7999abcf,
1951ab3f-3bdf3,
1952a2b2f-2adf3-16000bef3+16001cf4,
1953a3bf+4aef3,
1954ac3e-10668cde3,
1955a2c2e+10667ade3+16001be4+5334ce3f,
1956a3ce+10669ae3f,
1957bc3d+8001cd3e,
1958ac3d+8000bc3e+16001cd2e2+8001c4f,
1959b2c2d+16001ad4+4000bd3e+12001cd3f,
1960b2c2e-10668bc3f-10667cd2ef,
1961abc2e-cde2f,
1962b3cd-8000bd3f,
1963b3ce-10668b2c2f-10667bd2ef,
1964abc2f-cdef2,
1965a2bce-16000be3f+16001ce2f2,
1966ab3d-8000b4e-8001b3cf+16000bd2f2,
1967ab2cf-bdef2,
1968a2bcf-16000be2f2+16001cef3,
1969a4d-8000a3be+8001a3cf-2ae2f2;
1970
1971
1972ring r=32003,(b,s,t,u,v,w,x,y,z),dp;
1973ideal k=
1974wy-vz,
1975vx-uy,
1976tv-sw,
1977su-bv,
1978tuy-bvz;
1979ideal j=x2y2+x2z2+y2z2;
1980ideal i=mstd(intersect(j,k))[2];
1981
1982
1983ring r=32003,(b,s,t,u,v,w,x,y,z),dp;
1984ideal i=
1985wx2y3-vx2y2z+wx2yz2+wy3z2-vx2z3-vy2z3,
1986vx3y2-ux2y3+vx3z2-ux2yz2+vxy2z2-uy3z2,
1987tvx2y2-swx2y2+tvx2z2-swx2z2+tvy2z2-swy2z2,
1988sux2y2-bvx2y2+sux2z2-bvx2z2+suy2z2-bvy2z2,
1989tux2y3-bvx2y2z+tux2yz2+tuy3z2-bvx2z3-bvy2z3;
1990
1991
1992//riemenschneider 
1993ring r=32000,(p,q,s,t,u,v,w,x,y,z),wp(1,1,1,1,1,1,2,1,1,1);
1994ideal i=
1995xz,
1996vx,
1997ux,
1998su,
1999qu,
2000txy,
2001stx,
2002qtx,
2003uv2z-uwz,
2004uv3-uvw,
2005puv2-puw;
2006
2007ring r=0,(u,v,w,x,y,z),wp(1,1,1,3,2,1);
2008ideal i=wx,wy,wz,vx,vy,vz,ux,uy,uz,y3-x2;
2009
2010//Yoshihiko Sakai
2011ring r=0,(x,y),dp;   //genus 0 4 nodes and 6 cusps   
2012ideal i=(x2+y^2-1)^3 +27x2y2;
2013
2014ring r=0,(x,y),dp;   //genus 0
2015ideal i=(x-y^2)^2 - y*x^3;
2016
2017ring r=0,(x,y),dp;  //genus 4
2018ideal i=y3-x6+1;
2019
2020int m=9;           // q=9: genus 0
2021int p=2;
2022int q=9;//2,...,9
2023ring r=0,(x,y),dp; 
2024ideal i=y^m - x^p*(x - 1)^q;
2025
2026ring r=0,(x,y),dp;  //genus 19
2027ideal 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;
2028
2029
2030ring r=0,(x,y),dp;  //genus 34
2031ideal i=y10+(-2494x2+474)*y8+(84366+2042158x4-660492)*y6
2032        +(128361096x4-47970216x2+6697080-761328152x6)*y4
2033        +(-12024807786x4-506101284x2+15052058268x6+202172841-3212x8)*y2
2034        +34263110700x4-228715574724x6+5431439286x2+201803238
2035        -9127158539954x10-3212722859346x8;
2036
2037//Rob Koelman
2038ring r=0,(x,y,z),dp;//genus 10  with 26 cusps
2039ideal i=
2040761328152*x^6*z^4-5431439286*x^2*y^8+2494*x^2*z^8+228715574724*x^6*y^4+
2041 9127158539954*x^10-15052058268*x^6*y^2*z^2+3212722859346*x^8*y^2-
2042 134266087241*x^8*z^2-202172841*y^8*z^2-34263110700*x^4*y^6-6697080*y^6*z^4-
2043 2042158*x^4*z^6-201803238*y^10+12024807786*x^4*y^4*z^2-128361096*x^4*y^2*z^4+
2044 506101284*x^2*z^2*y^6+47970216*x^2*z^4*y^4+660492*x^2*z^6*y^2-
2045 z^10-474*z^8*y^2-84366*z^6*y^4;
2046
2047ring r=0,(x,y),dp;//genus 10  with 26 cusps
2048ideal i=9127158539954x10+3212722859346x8y2+228715574724x6y4-34263110700x4y6
2049-5431439286x2y8-201803238y10-134266087241x8-15052058268x6y2+12024807786x4y4
2050+506101284x2y6-202172841y8+761328152x6-128361096x4y2+47970216x2y4-6697080y6
2051-2042158x4+660492x2y2-84366y4+2494x2-474y2-1;
2052
2053
2054ring r=0,(x,y),dp;   // genus 1  with 5 cusps
2055ideal i=57y5+516x4y-320x4+66y4-340x2y3+73y3+128x2-84x2y2-96x2y;
2056
2057//Mark van Hoeij
2058ring r=0,(x,y),dp;  //genus 19
2059ideal i=y20+y13x+x4y5+x3*(x+1)^2;
2060
2061ring r=0,(x,y),dp;  //genus 35
2062ideal i=y30+y13x+x4y5+x3*(x+1)^2;
2063
2064ring r=0,(x,y),dp;   //genus 55
2065ideal i=y40+y13x+x4y5+x3*(x+1)^2;
2066
2067ring r=0,(x,y),dp;  //genus 4
2068ideal i=((x2+y3)^2+xy6)*((x3+y2)^2+x10y);
2069
2070ring r=0,(y,z,w,u),dp; //genus -5
2071ideal i=y2+z2+w2+u2,w4-u4;
2072
2073ring r=0,(x,y,t),dp; //genus -5
2074ideal 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;
2075
2076ring r=0,(y,z,w,u),dp; //genus 9
2077ideal i=y2+z2+w2+u2,z4+w4+u4;
2078
2079ring r=0,(x,y,t),dp;
2080ideal i=
208125x8+200x7y+720x6y2+1520x5y3+2064x4y4+1856x3y5+1088x2y6+384xy7+64y8-12x6t2-72x5yt2-184x4y2t2-256x3y3t2-192x2y4t2-64xy5t2-2x4t4-8x3yt4+16xy3t4+16y4t4+4x2t6+8xyt6+8y2t6+t8;
2082
2083ring r=0,(x,y,t),dp;
2084ideal i=
208532761x8+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;
2086
2087ring r=32003,(x,y,z,w,u),dp;
2088ideal i=x2+y2+z2+w2+u2,x3+y3+z3,z4+w4+u4;
2089
2090*/
2091
Note: See TracBrowser for help on using the repository browser.