source: git/Singular/LIB/paraplanecurves.lib @ 15bbde9

spielwiese
Last change on this file since 15bbde9 was 15bbde9, checked in by Hans Schoenemann <hannes@…>, 3 years ago
suppress prints in paraplancure.lib except in top level
  • Property mode set to 100644
File size: 101.0 KB
Line 
1//////////////////////////////////////////////////////////////////////////////
2version="version paraplanecurves.lib 4.1.2.0 Feb_2019 "; // $Id$
3category="Algebraic Geometry";
4info="
5LIBRARY:  paraplanecurves.lib Rational parametrization of rational plane curves
6
7AUTHORS:  J. Boehm, boehm at mathematik.uni-kl.de @*
8          W. Decker, decker at mathematik.uni-kl.de @*
9          S. Laplagne, slaplagn at dm.uba.ar @*
10          F. Seelisch, seelisch at mathematik.uni-kl.de
11
12OVERVIEW:
13
14Suppose C = {f(x,y,z)=0} is a rational plane curve, where f is homogeneous
15of degree n with coefficients in Q and absolutely irreducible (these
16conditions are checked automatically.) @*
17After a first step, realized by a projective automorphism in the procedure
18adjointIdeal, C satisfies: @*
19- C does not have singularities at infinity z=0. @*
20- C does not contain the point (0:1:0) (that is, the dehomogenization of f
21  with respect to z is monic as a polynomial in y). @*
22Considering C in the chart z<>0, the algorithm regards x as transcendental
23and y as algebraic and computes an integral basis in C(x)[y] of the integral
24closure of C[x] in C(x,y) using the  normalization algorithm from
25@ref{normal_lib}: see @ref{integralbasis_lib}. In a future edition of the
26library, also van Hoeij's algorithm for computing the integral basis will
27be available. @*
28From the integral basis, the adjoint ideal is obtained by linear algebra.
29Alternatively, the algorithm starts with a local analysis of the singular
30locus of C. Then, for each  primary component of the singular locus which
31does not correspond to ordinary multiple points or cusps, the integral
32basis algorithm is applied separately. The ordinary multiple points and
33cusps, in turn, are addressed by a straightforward direct algorithm. The
34adjoint ideal is obtained by intersecting all ideals obtained locally.
35The local variant of the algorithm is used by default. @*
36The linear system corresponding to the adjoint ideal maps the curve
37birationally to a rational normal curve in P^(n-2). @*
38Iterating the anticanonical map, the algorithm projects the rational normal
39curve to PP1 for n odd resp. to a conic C2 in PP2 for n even. @*
40In case n is even, the algorithm tests whether there is a rational point on
41C2 and if so gives a parametrization of C2 which is defined over Q. Otherwise,
42the parametrization given is defined over a quadratic field extension of Q. @*
43By inverting the birational map of C to PP1 resp. to C2, a parametrization
44of C is obtained (defined over Q or the quadratic field extension).
45
46REFERENCES:
47
48Janko Boehm: Parametrisierung rationaler Kurven, Diploma Thesis,
49http://www.math.uni-sb.de/ag/schreyer/jb/diplom%20janko%20boehm.pdf
50
51Janko Boehm,  Wolfram Decker, Santiago Laplagne, Gerhard Pfister:
52Local to global algorithms for the Gorenstein adjoint ideal of a curve,
53Algorithmic and Experimental Methods in Algebra, Geometry, and Number Theory, Springer 2018
54
55Theo de Jong: An algorithm for computing the integral closure,
56Journal of Symbolic Computation 26 (3) (1998), p. 273-277
57
58Gert-Martin Greuel, Santiago Laplagne, Frank Seelisch: Normalization of Rings,
59Journal of Symbolic Computation 9 (2010), p. 887-901
60
61Mark van Hoeij: An Algorithm for Computing an Integral Basis in an Algebraic
62Function Field, Journal of Symbolic Computation 18 (1994), p. 353-363,
63http://www.math.fsu.edu/~hoeij/papers/comments/jsc1994.html
64
65
66KEYWORDS:
67Curves; Parametrization; Rational curves; Adjoint ideal; Geometric genus
68
69
70PROCEDURES:
71
72adjointIdeal(poly, [...]);        Adjoint ideal of a plane curve
73invertBirMap(ideal,ideal);        Invert a birational map of algebraic
74                                  varieties
75paraPlaneCurve(poly, [...]);      Compute a rational parametrization of a
76                                  rational plane curve
77rncAntiCanonicalMap(ideal);       Anticanonical map of a rational normal curve
78rationalPointConic(poly);         Finds a point on the conic. This point has
79                                  either coefficients in Q or in a quadratic
80                                  extension field of Q
81mapToRatNormCurve(poly,ideal);    Map a plane rational curve to a rational
82                                  normal curve (RNC)
83rncItProjOdd(ideal);              Map a RNC via successive anticanonical maps
84                                  to PP1
85rncItProjEven(ideal);             Map a RNC via successive anticanonical maps
86                                  to a conic in PP2
87paraConic(poly);                  Compute a rational parametrization of a conic
88testParametrization(poly,ring);   Checks whether a given curve is parametrized
89                                  by a given rational map (defined in the
90                                  given ring)
91testPointConic(poly,ring);        Checks whether a given point (defined in the
92                                  given ring) lies on the given conic.
93";
94
95LIB "elim.lib";
96LIB "general.lib";
97LIB "primdec.lib";
98LIB "absfact.lib";
99LIB "matrix.lib";
100LIB "random.lib";
101LIB "homolog.lib";
102LIB "integralbasis.lib";
103LIB "normal.lib";
104
105
106///////////////////////////////////////////////////////////////////////////////
107proc invertBirMap(ideal phi, ideal I)
108"USAGE: invertBirMap(phi, I); phi ideal, I ideal
109ASSUME: The ideal phi in the basering R represents a birational map of the
110        variety given by the ideal I in R to its image in projective space
111        P = PP^(size(phi)-1).
112NOTE:   The procedure might fail or give a wrong output if phi does
113        not define a birational map.
114RETURN: ring, the coordinate ring of P, with an ideal named J and an ideal
115        named psi.@*
116        The ideal J defines the image of phi.@*
117        The ideal psi gives the inverse of phi.@*
118        Note that the entries of psi should be considered as representatives
119        of classes in the quotient ring R/J.@*
120THEORY: We compute the ideal I(G) in R**S of the graph G of phi.@*
121        The ideal J is given by the intersection of I(G) with S.@*
122        The map psi is given by a relation mod J of those relations
123        in I(G) which are linear in the variables of R.@*
124KEYWORDS: birational map, image, inverse.
125EXAMPLE: example invertBirMap; shows an example
126"
127{
128   def Roriginal = basering;
129   int n = nvars(Roriginal);
130   int m = size(phi);
131   /*phi: P^(n-1) --> P^(m-1)*/
132   list rl = ringlist(Roriginal);
133   int k;
134   for(k = 1; k <= n; k++)
135     {
136        rl[2][k] = "x("+string(k)+")";
137     }
138   for(k = 1; k <= m; k++)
139     {
140        rl[2][k+n] = "y("+string(k)+")";
141     }
142   rl[3]= list(list("dp",1:(n+m)),list("C",0));
143   /*Use Hilbert driven Buchberger*/
144   def Rbig0 = ring(rl);
145   setring Rbig0;
146   ideal I = fetch(Roriginal,I);
147   ideal phi = fetch(Roriginal,phi);
148   ideal mi = maxideal(1);
149   ideal xv = mi[1..n];
150   ideal yv  = mi[n+1..n+m];
151   matrix HM[2][m] = concat(transpose(yv),transpose(phi));
152   ideal graph = sat(I+minor(HM,2),phi)[1];
153   graph = sat(graph,xv)[1];
154   intvec Hgraph = hilb(graph,1);
155   setring Roriginal;
156   rl[3]= list(list("dp",1:n),list("dp",1:m),list("C",0));
157   def Rbig = ring(rl);
158   setring Rbig;
159   ideal graph = imap(Rbig0,graph);
160   graph = std(graph,Hgraph);
161   ideal xv = imap(Rbig0,xv);
162   /*The ideal J defines the image of phi*/
163   ideal J = graph;
164   for(k = 1; k <= n; k++)
165     {
166        J = subst(J,xv[k],0);
167     }
168   J = compress(J);
169   /*now we start inverting phi to psi*/
170   matrix relpsi = diff(xv,graph);
171   for(k = 1; k <= n; k++)
172     {
173        relpsi = subst(relpsi,xv[k],0);
174     }
175    relpsi = compress(relpsi);
176    list rl = ringlist(Rbig);
177    list rl2 = rl[2];
178    rl[2] = list(rl2[n+1..n+m]);
179    rl[3]= list(list("dp",1:m),list("C",0));
180    def Rtarget = ring(rl);
181    setring Rtarget;
182    ideal J = imap(Rbig,J);
183    qring RtargetmodJ = std(J);
184    matrix relpsi = imap(Rbig,relpsi);
185    relpsi = syz(transpose(relpsi));
186    ideal psi = submat(relpsi,1..nrows(relpsi),1);
187    setring Rtarget;
188    ideal psi = imap(RtargetmodJ,psi);
189    export(J,psi);
190    int p = printlevel - voice + 3;
191    dbprint(p,"// 'invertBirMap' created a ring together with two ideals J and psi.");
192    dbprint(p,"// Supposing you typed, say,  def RPn = invertBirMap(phi,I);");
193    dbprint(p,"// you may access the ideals by typing");
194    dbprint(p,"//      setring RPn; J; psi;");
195    return(Rtarget);
196 }
197
198example
199{ "EXAMPLE:"; echo=2;
200  ring R = 0,(x,y,z),dp;
201  poly f = y^8-x^3*(z+x)^5;
202  ideal adj = adjointIdeal(f);
203  def Rn = invertBirMap(adj,ideal(f));
204  setring(Rn);
205  J;
206  psi;
207}
208
209///////////////////////////////////////////////////////////////////////////////
210static proc checkAssumptions(poly f)
211"USAGE:  checkAssumptions(f); f poly
212RETURN:  1 if assumptions are satisfied, 0 otherwise.@*
213         Assumptions checked are: basering is polynomial ring in 3 variables
214         with coefficients in Q, f is homogeneous and absolutely irreducible
215"
216{
217  def Roriginal = basering;
218  list rl = ringlist(Roriginal);
219  rl[3] = list(list("dp",1:3),list("C",0));
220  if(size(rl[1])>1){ERROR("ground field is not Q");}
221  if(rl[1]!=0){ERROR("ground field is not Q");}
222  if(nvars(Roriginal)!=3)
223  { ERROR("not a projective plane curve: wrong number of variables"); }
224  if(homog(f)==0)
225  { ERROR("not a projective plane curve: polynomial is not homogeneous"); }
226  def RP2 = ring(rl);
227  setring RP2;
228  poly f = fetch(Roriginal,f);
229  if(isIrreducible(f)==0){ERROR("curve is not absolutely irreducible");}
230  setring Roriginal;
231}
232
233///////////////////////////////////////////////////////////////////////////////
234proc paraPlaneCurve(poly f, list #)
235"USAGE:  paraPlaneCurve(f [, s]); f poly , s optional string@*
236         optional string s can be: @*
237         'normal': compute integral basis via normalization. @*
238         'local':  make local analysis of singularities first and apply
239                   normalization separately. @*
240         The default is 2. @*
241ASSUME:  The basering must be a polynomial ring in three variables, say x,y,z,
242         with coefficients in Q. @*
243         The polynomial f must be homogeneous and absolutely irreducible. @*
244         The curve C = {f = 0} must be rational, i.e., have geometric genus 0
245         (see @ref{genus}). @*
246         These conditions will be checked automatically.
247RETURN:  ring with an ideal PARA which contains a rational parametrization of
248         the rational plane curve given by f; the ground field of the returned
249         polynomial ring is either Q or some algebraic extension Q(a); PARA
250         consists of three generators that parametrize the three coordinates
251         of the rational curve
252THEORY:  After a first step, realized by a projective automorphism in the
253         procedure adjointIdeal, C satisfies: @*
254- C does not have singularities at infinity z=0. @*
255- C does not contain the point (0:1:0) (that is, the dehomogenization of f
256  with respect to z is monic as a polynomial in y). @*
257Considering C in the chart z<>0, the algorithm regards x as transcendental
258and y as algebraic and computes an integral basis in C(x)[y] of the integral
259closure of C[x] in C(x,y) using the normalization algorithm from @ref{normal_lib}:
260see @ref{integralbasis_lib}. In a future edition of the library, also van Hoeij's
261algorithm for computing the integral basis will be available. @*
262From the integral basis, the adjoint ideal is obtained by linear algebra.
263Alternatively, the algorithm starts with a local analysis of the singular
264locus of C. Then, for each  primary component of the singular locus which
265does not correspond to ordinary multiple points or cusps, the integral
266basis algorithm is applied separately. The ordinary multiple points and
267cusps, in turn, are addressed by a straightforward direct algorithm. The
268adjoint ideal is obtained by intersecting all ideals obtained locally.
269The local variant of the algorithm is used by default. @*
270The linear system corresponding to the adjoint ideal maps the curve
271birationally to a rational normal curve in P^(n-2). @*
272Iterating the anticanonical map, the algorithm projects the rational normal
273curve to PP1 for n odd resp. to a conic C2 in PP2 for n even. @*
274In case n is even, the algorithm tests whether there is a rational point on C2
275and if so gives a parametrization of C2 which is defined over Q. Otherwise the
276parametrization is defined over a quadratic field extension of Q. @*
277By inverting the birational map of C to PP1 resp. to C2, a parametrization of
278C is obtained (defined over Q or the quadratic field extension).
279KEYWORDS: rational curves, rational parametrization of rational curves.
280EXAMPLE:  example paraPlaneCurve; shows an example
281"
282{
283  int choice = 2;
284  if (size(#) != 0)
285  {
286    if (typeof(#[1]) == "string")
287    {
288      string s = string(#[1]);
289      if (s == "normal") { choice = 1; }
290      else
291      {
292        if (s == "local") { choice = 2; }
293        else { ERROR("expected optional argument to be either"
294                   + " 'local' or 'normal'"); }
295      }
296    }
297    else { ERROR("expected optional argument to be a string"); }
298  }
299  def Roriginal = basering;
300  /*checking assumptions and handling the conic case*/
301  checkAssumptions(f);
302  list rl = ringlist(Roriginal);
303  rl[2] = list("x","y","z");
304  rl[3] = list(list("dp",1:3),list("C",0));
305  def RP2 = ring(rl);
306  setring RP2;
307  poly f = fetch(Roriginal,f);
308  int d = deg(f);
309  if(d==2)
310    {
311      def RP1 = paraConic(f); // (ring, PARACONIC)
312      setring RP1;
313      ideal PARA = PARACONIC;
314      export(PARA);
315      int p = printlevel - voice + 3;
316      dbprint(p,"// 'paraPlaneCurve' created a ring together with an ideal PARA.
317// Supposing you typed, say,  def RP1 = paraPlaneCurve(f);
318// you may access the ideal by typing
319//      setring RP1; PARA;");
320      return(RP1);
321    }
322  int k;
323  /*the adjoint ideal*/
324  ideal AI = adjointIdeal(f,list(choice,"rattestyes/firstchecksdone"));
325  /*rattestyes -> causes error message if curve is not rational*/
326  /*firstchecksdone -> prevents that check of assumptions will be done again*/
327  /*mapping the curve to a rational normal curve V(RNC) in Proj(Rrnc) via AI*/
328  def Rrnc = mapToRatNormCurve(f, AI);  // ring containing ideal RNC
329  setring Rrnc;
330  int m = d-1;  // the size of AI
331  /*the odd dimensional case*/
332  if((d mod 2) == 1)
333    {
334      /*mapping the rational normal curve to P^1 creating PHI*/
335      ideal PHI = rncItProjOdd(RNC);
336      /*composing the maps AI and PHI*/
337      def Rbig = Rrnc + RP2;
338      setring Rbig;
339      ideal AI = imap(RP2,AI);
340      ideal PROJ = imap(Rrnc,PHI);
341      for(k = 1; k <= m; k++)
342        {
343          PROJ = subst(PROJ,var(k),AI[k]);
344        }
345      setring RP2;
346      ideal If = ideal(fetch(Roriginal,f));
347      ideal PROJ = imap(Rbig,PROJ);
348      /*inverting the composed map to psi*/
349      def rp1 = invertBirMap(PROJ,If); // ring containing ideal psi
350      setring rp1;
351      list rl1 = ringlist(rp1);
352      rl1[2] = list("s","t");
353      def RP1 = ring(rl1);
354      setring RP1;
355      ideal PARA = fetch(rp1,psi);
356      export(PARA);
357      int p = printlevel - voice + 3;
358      dbprint(p,"// 'paraPlaneCurve' created a ring together with an ideal PARA.
359// Supposing you typed, say,  def RP1 = paraPlaneCurve(f);
360// you may access the ideal by typing
361//      setring RP1; PARA;");
362      return(RP1);
363    }
364  /*the even dimensional case*/
365  /*mapping the rational normal curve to a CONIC in P^2* creating PHI*/
366  def RP2conic = rncItProjEven(RNC);  // exports PHI, returns ring
367                                      // containing CONIC
368  setring RP2conic;
369  /*mapping the conic to P^1 via pencil defined by Ipoint*/
370  def RP2conicNew = projConic(CONIC);  // ring containing ideal Ipoint
371                               // possibly defined over algebraic number field
372                               // variables u,v,w
373  /*composing the maps AI and PHI and Ipoint in two steps*/
374  def Rbig = RP2conicNew + Rrnc;
375  setring Rbig;
376  ideal PHI = imap(Rrnc,PHI);
377  ideal PROJ = imap(RP2conicNew,Ipoint);
378  for(k = 1; k <= 3; k++)
379    {
380      PROJ = subst(PROJ,var(k),PHI[k]);
381    }
382  ideal AI = fetch(RP2,AI);
383  for(k = 1; k <= m; k++)
384    {
385       PROJ = subst(PROJ,var(k+3),AI[k]);
386    }
387  setring RP2conicNew;
388  ideal If = ideal(fetch(Roriginal,f));
389  ideal PROJ = imap(Rbig,PROJ);
390  /*inverting the composed map to psi*/
391  def rp1 = invertBirMap(PROJ,If); // (ring, (J,psi))
392  setring rp1;
393  list rl1 = ringlist(rp1);
394  rl1[2] = list("s","t");
395  def RP1 = ring(rl1);
396  setring RP1;
397  ideal PARA = fetch(rp1,psi);
398  export(PARA);
399  int p = printlevel - voice + 3;
400  dbprint(p,"// 'paraPlaneCurve' created a ring together with an ideal PARA.
401// Supposing you typed, say,  def RP1 = paraPlaneCurve(f);
402// you may access the ideal by typing
403//      setring RP1; PARA;");
404  return(RP1);
405}
406
407example
408{ "EXAMPLE:"; echo=2;
409  ring R = 0,(x,y,z),dp;
410  poly f1 = 1/2*x^5+x^2*y*z^2+x^3*y*z+1/2*x*y^2*z^2-2*x*y^3*z+y^5;
411  def Rp1 = paraPlaneCurve(f1);
412  setring Rp1;
413  PARA;
414  setring R;
415  poly f2 = x6+3x4y2+3x2y4+y6-4x4z2-34x3yz2-7x2y2z2+12xy3z2+6y4z2;
416  f2 = f2+36x2z4+36xyz4+9y2z4;
417  def Rp2 = paraPlaneCurve(f2);
418  setring Rp2;
419  PARA;
420}
421
422///////////////////////////////////////////////////////////////////////////////
423// compute the weighted degree of p;
424// this code is an exact copy of the proc in paraplanecurves.lib
425// (since we do not want to make it non-static)
426static proc w_deg(poly p, intvec v)
427{
428   if(p==0){return(-1);}
429   int d=0;
430   while(jet(p,d,v)==0){d++;}
431   d=(transpose(leadexp(jet(p,d,v)))*v)[1];
432   return(d);
433}
434
435///////////////////////////////////////////////////////////////////////////////
436static proc findCoordChange(poly f, ideal JAC)
437"USAGE:  findCoordChange(f, JAC); f poly, JAC ideal.
438ASSUME:  The polynomial f is homogeneous in three variables, JAC is
439         the Jacobi ideal of f.
440RETURN:  intvec, say a,b,c. After the coordinate change
441         var(3) --> a*var(1)+b*var(2)+c*var(3), the curve {f=0}
442         has no singularities at infinity {var(3)=0}.
443"
444{
445  int h = 2;
446  int a,b,c;
447  ideal Jfinfty;
448  while(h)
449    {
450      c = 1;
451      while(c<=h)
452         {
453           b = 0;
454           while(b<=(h-c))
455              {
456                a = h-b-c;
457                Jfinfty = JAC,a*var(1)+b*var(2)+c*var(3);
458                if(dim(std(Jfinfty)) == 0)
459                  {
460                    return(a,b,c);
461                  }
462                b = b+1;
463              }
464            c = c+1;
465          }
466       h = h+1;
467    }
468}
469
470///////////////////////////////////////////////////////////////////////////////
471proc adjointIdeal(poly f, list #)
472"USAGE:  adjointIdeal(f [, choices]); f polynomial in three variables, choices
473         optional list consisting of one integer or of one string or of one
474         integer followed by one string. @*
475         Optional integer can be: @*
476         1: compute integral basis via normalization. @*
477         2: make local analysis of singularities first and apply normalization
478            separately. @*
479         3: normalization via ideal quotient. @*
480         4: normalization via local ideal quotient. @*
481         The default is 2. @*
482         Optional string may contain substrings: @*
483         - rattestyes -> causes error message if curve is not rational. @*
484         - firstchecksdone -> prevents that check of assumptions will be done
485           more than once.
486ASSUME:  The basering must be a polynomial ring in three variables, say x,y,z,
487         with coefficients in Q. @*
488         The polynomial f must be homogeneous and absolutely irreducible.@*
489         All these conditions will be checked automatically.@*
490RETURN:  ideal, the adjoint ideal of the curve defined by f.
491THEORY:  Considering C in the chart z<>0, the algorithm regards x as
492transcendental and y as algebraic and computes an integral basis in C(x)[y] of
493the integral closure of C[x] in C(x,y) using the normalization algorithm
494from @ref{normal_lib}: see @ref{integralbasis_lib}. In a future edition of the library,
495also van Hoeij's algorithm for computing the integral basis will be available.@*
496From the integral basis, the adjoint ideal is obtained by linear algebra.
497Alternatively, the algorithm starts with a local analysis of the singular
498locus of C. Then, for each  primary component of the singular locus which
499does not correspond to ordinary multiple points or cusps, the integral
500basis algorithm is applied separately. The ordinary multiple points and
501cusps, in turn, are addressed by a straightforward direct algorithm. The
502adjoint ideal is obtained by intersecting all ideals obtained locally.
503The local variant of the algorithm is used by default. @*
504KEYWORDS: integral basis; normalization.
505EXAMPLE: example adjointIdeal; shows an example
506"
507{
508  list choices = #;
509  if(size(#)==0)
510    {
511      checkAssumptions(f);
512      choices = list(2, "rattestno");
513    }
514  if(size(#)==1)
515    {
516      if(typeof(choices[1])=="int")
517        {
518          checkAssumptions(f);
519          choices = list(choices[1], "rattestno");
520        }
521      else
522         {
523           if(not(find(choices[1], "firstchecksdone")))
524             {
525               checkAssumptions(f);
526             }
527           else
528             {
529               choices = list(2, choices[1]);
530             }
531        }
532    }
533  if(size(#) == 2)
534    {
535      if(not(find(choices[2],"firstchecksdone")))
536        {
537          checkAssumptions(f);
538        }
539    }
540  ideal JAC = diff(maxideal(1),ideal(f));
541  ideal Jfinfty = JAC,var(3);
542  /*applying a change of coordinates if (f=0) has singularities at infinity*/
543  int bb1;
544  if(dim(std(Jfinfty)) >= 1)
545    {
546       bb1 = 1;
547       int a,b,c  = findCoordChange(f,JAC);
548       f = subst(f,var(3),var(3)-number(a)/c*var(1)-number(b)/c*var(2));
549    }
550  /*applying a change of coordinates if the point (0:1:0) lies on the curve*/
551  matrix co = coeffs(f,var(2));
552  int bb2 = ((size(co)-1) != deg(f));
553  if(bb2)
554    {
555       co = coeffs(f,var(1));
556       int bb2x = ((size(co)-1) == deg(f));
557       if(bb2x)
558         {
559           map perm = basering, var(2), var(1), var(3);
560           f = perm(f);
561         }
562       else
563         {
564           number cc=1;
565           int tst=0;
566           poly ff;
567           while (tst==0){
568              ff = subst(f,var(1),var(1)+cc*var(2));
569              tst=((size(coeffs(ff,var(2)))-1) == deg(ff));
570              if (tst==0){cc=cc+1;}
571           }
572           f = subst(f,var(1),var(1)+cc*var(2));
573         }
574    }
575  co = coeffs(f,var(2));
576  f = f/co[size(co),1];
577  /*the actual computation*/
578  ideal AI = adjointIdealAtWork(f,choices);
579  /*reversing the changes of coordinates if needed*/
580  if(bb2)
581    {
582       if(bb2x)
583         {
584           perm = basering, var(2), var(1), var(3);
585           AI = mstd(perm(AI))[2];
586         }
587       else
588         {
589           AI = mstd(substitute(AI,var(1),var(1)-cc*var(2)))[2];
590         }
591
592    }
593  if(bb1==1)
594   {
595      AI = mstd(substitute(AI,var(3),var(3)+number(a)/c*var(1)+number(b)/c*var(2)))[2];
596    }
597  return(AI);
598}
599
600example
601{ "EXAMPLE:"; echo=2;
602  ring R = 0,(x,y,z),dp;
603  poly f = y^8-x^3*(z+x)^5;
604  adjointIdeal(f);
605}
606
607///////////////////////////////////////////////////////////////////////////////
608static proc adjointIdealAtWork(poly f, list choices)
609"USAGE:  adjointIdealAtWork(f, choices); f polynomial in three variables,
610         choices list consisting of one integer followed by one string. @*
611         integer can be: @*
612         1: compute integral basis via normalization. @*
613         2: make local analysis of singularities first and apply normalization
614            separately. @*
615         3: normalization via ideal quotient. @*
616         4: normalization via local ideal quotient. @*
617         The default is 2. @*
618         string  may contain substring: @*
619         - rattestyes -> causes error message if curve is not rational. @*
620ASSUME:  The basering must be a polynomial ring in three variables, say x,y,z,
621         with coefficients in Q. @*
622         The polynomial f must be homogeneous and absolutely irreducible. @*
623         Its dehomogenization with respect to the third variable must be monic
624         as a polynomial in the second variable (that is, C does not contain
625         the point (0:1:0)).@*
626         The curve C is not allowed to have singularities
627         at infinity (z = 0). @*
628RETURN:  ideal, the adjoint ideal of the curve defined by f.
629"
630{
631  def Roriginal = basering;
632  list rl = ringlist(Roriginal);
633  rl[3] = list(list("dp",1:nvars(Roriginal)),list("C",0));
634  def RP2 = ring(rl);
635  setring RP2;
636  poly f = imap(Roriginal,f);
637  poly dhf = subst(f,var(3),1);
638  int n = deg(f);
639  if((choices[1]==1) || (choices[1]==3)) // no local analysis of singularities
640  {
641    ideal AI;
642    if (choices[1]==1)
643    { AI = adjointIdealIB(f,insert(choices,ideal(0),size(choices))); }
644    else
645    { AI = adjointIdealIQ(f,insert(choices,ideal(0),size(choices))); }
646    AI = homog(std(AI),var(3));
647    AI = sat(AI, maxideal(1))[1];
648    AI = minbase(AI);
649    setring Roriginal;
650    return(imap(RP2,AI));
651  }
652  list LL = geomGenusLA(f);  // local analysis of singularities
653  int sizeLL2 = size(LL[2]);
654  int sizeLL3 = size(LL[3]);
655  list LL3 = LL[3];
656  ideal LL4 = LL[4];
657  if((LL[1]!=0) && (find(choices[2],"rattestyes")))
658  { ERROR("not a rational curve"); }
659  if((LL[2]==0) && (sizeLL3==0)  && (LL4[1]==1))  // smooth case
660  {
661    setring Roriginal;
662    return(ideal(1));
663  }
664  int j,k;
665  list rl = ringlist(RP2);
666  rl[2] = list(var(1), var(2));
667  rl[3] = list(list("dp",1:2),list("C",0));
668  def Rdummy = ring(rl);
669  ideal B;
670  if(sizeLL3==0){B = 1;} // no ordinary multiple points
671                               // (except possibly nodes)
672  else                         // there are ordinary multiple points
673                               // (other than nodes)
674  {
675    setring Rdummy;
676    list OMP = imap(RP2,LL3);
677    int ub;
678    for(k=1;k<=size(OMP);k++)
679    {
680      if(OMP[k][1]>ub)
681      {
682        ub = OMP[k][1];
683      }
684    }
685    int lb = ub;
686    for(k=1;k<=size(OMP);k++)
687    {
688      if(OMP[k][1]<lb)
689      {
690        lb = OMP[k][1];
691      }
692    }
693    for(k=lb;k<=ub;k++)
694    {
695      ideal A(k) = 1;
696    }
697    for(k=1;k<=size(OMP);k++)
698    {
699      A(OMP[k][1]) = intersect(A(OMP[k][1]), OMP[k][2]);
700    }
701    int i = ub;
702    setring RP2;
703    for(k=lb;k<=ub;k++)
704    {
705      ideal A(k) = homog(std(fetch(Rdummy,A(k))),var(3));
706    }
707    B = maxideal(n-i);
708    ideal A;
709    while(i>=lb)
710    {
711      A = A(i)**(i-1);
712      j=1;
713      while(j<=ncols(A))
714      {
715        if(deg(A[j]>(n-2)))
716        {
717          A = sat(A, maxideal(1))[1];
718          break;
719        }
720        j = j+1;
721      }
722      B = intersect(B,A);
723      i = i-1;
724    }
725  }  //end else
726  B = intersect(B,homog(std(LL4),var(3)));  // add nodes and cusps
727  if(sizeLL2==0)  // ordinary multiple points plus cusps only
728  {
729    ideal AI = sat(B, maxideal(1))[1];
730    AI = minbase(AI);
731    setring Roriginal;
732    return(imap(RP2,AI));
733  }
734  setring Rdummy;
735  poly f = imap(RP2,dhf);
736  ideal SL = jacob(f),f;
737  SL = sat(SL, fetch(RP2,LL4))[1];
738  if(sizeLL3!=0)
739  {
740    for(k=lb;k<=ub;k++)
741    {
742      SL = sat(SL, A(k))[1];
743    }
744  }
745  list PD = primdecGTZ(SL);  // could be made faster -- see minAssGTZ
746                             // in deltaLocMod -- only one PD needed
747  int pd = size(PD);
748  setring RP2;
749  list PD = imap(Rdummy,PD);
750  ideal AI = 1;
751  for(k=1;k<=pd;k++)
752  {
753    if (choices[1]==2)
754    {
755      AI = intersect(AI,adjointIdealIB(f,insert(choices,PD[k][1],
756                                                 size(choices))));
757    }
758    else
759    {
760      AI = intersect(AI,adjointIdealIQ(f,insert(choices,PD[k][1],
761                                                 size(choices))));
762    }
763  }
764  AI = homog(std(AI),var(3));
765  AI = intersect(AI,B);
766  AI = sat(AI, maxideal(1))[1];
767  AI = minbase(AI);
768  setring Roriginal;
769  return(imap(RP2,AI));
770}
771
772///////////////////////////////////////////////////////////////////////////////
773static proc adjointIdealIB(poly f, list choices)
774"USAGE:  adjointIdealIB(f, choices); f polynomial in three variables, choices
775         list consisting of one integer followed by one string followed by one
776         ideal. @*
777         integer can be: @*
778         1, 2 : compute integral basis via normalization @*
779         The default is 2. @*
780         string  may contain substring: @*
781         - rattestyes -> causes error message if curve is not rational. @*
782         ideal serves as input for @ref integralBasis.
783ASSUME:  The basering must be a polynomial ring in three variables, say x,y,z,
784         with coefficients in Q. @*
785         The polynomial f must be homogeneous and absolutely irreducible.@*
786         Its dehomogenization with respect to the third variable must be monic
787         as a polynomial in the second variable (that is, C does not contain
788         the point (0:1:0)).@*
789         The curve C is not allowed to have singularities
790         at infinity (z = 0). @*
791RETURN:  ideal containing the adjoint ideal of the curve defined by f. @*
792"
793{
794  poly dhf = subst(f,var(3),1);
795  def Roriginal = basering;
796  list rl = ringlist(Roriginal);
797  rl[2] = list(var(1), var(2));
798  rl[3] = list(list("dp",1:2),list("C",0));
799  def Rdummy = ring(rl);
800  setring Rdummy;
801  poly f = imap(Roriginal,dhf);
802  poly d2f = diff(f,var(2));
803  list DATA = imap(Roriginal,choices);
804  /* Creating rings for later use */
805  list rl = ringlist(Rdummy);
806  rl[2] = list(var(2), var(1));
807  rl[3] = list(list("lp",1:2),list("C",0));
808  def Rred = ring(rl);   // make var(2) > var(1)
809  rl = ringlist(Rdummy);
810  rl[1] = list(0,list(var(1)),list(list("dp",1)),ideal(0));
811  rl[2] = list(var(2));
812  rl[3] = list(list("dp",1),list("C",0));
813  def QF = ring(rl);   // make var(1) transcendental
814  list LIntB;
815  if(DATA[1] <= 4)  // use normalization algorithm
816  {
817    LIntB = integralBasis(f, 2, list(list("inputC", DATA[3]),"isIrred"));
818  }
819  else                                 // use van Hoeij's algorithm
820  {
821    LIntB = integralBasisVH(f,DATA[3],2);  // van Hoeij in future version
822                                           // used when DATA[1] = 5
823  }
824  if(find(DATA[2],"rattestyes") && (size(DATA[3])==0))
825  {
826    setring Roriginal;
827    int gg = geomGenusIB(f,imap(Rdummy, LIntB));
828    if(gg!=0){ERROR("not a rational curve");}
829    setring Rdummy;
830  }
831  int i,j,k,l;
832  ideal IB = LIntB[1];
833  poly d = LIntB[2];
834  int sL=size(IB);
835  setring Rred;
836  ideal IB = imap(Rdummy,IB);
837  ideal fred = std(imap(Rdummy,f));
838  IB = reduce(IB,fred);
839  matrix M = coeffs(IB,var(1));
840  setring QF;
841  matrix M = imap(Rred,M);
842  poly d = imap(Rdummy,d);
843  M=1/d*M;
844  list LUM = ludecomp(M);
845  list LS;
846  matrix dummyvector[sL][1];
847  matrix Gij[sL][sL];
848  matrix Tr[sL][sL];
849  setring Rred;
850  poly eiej;
851  list Iij, empty;
852  matrix Gij[sL][sL];
853  for(i = 1; i <= sL; i++)
854  {
855    for(j = i; j <= sL; j++)
856    {
857      setring Rred;
858      Gij = 0;
859      eiej = IB[i]*IB[j];
860      Iij=empty;
861      for(k = 1; k <= sL; k++)
862      {
863        Iij[k] = reduce(eiej*IB[k],fred);
864      }
865      Gij = coeffs(ideal(Iij[1..sL]),var(1));
866      setring QF;
867      Gij = imap (Rred, Gij);
868      for(k = 1; k <= sL; k++)
869      {
870        dummyvector = Gij[1..sL,k];
871        LS = lusolve(LUM[1], LUM[2], LUM[3], dummyvector);
872        Tr[i,j] = Tr[i,j] + 1/d^3*LS[2][k,1];
873      }
874    }
875  }
876  for(i = 1; i <= sL; i++)
877  {
878    for(j = 1; j < i; j++)
879    {
880      Tr[i,j] = Tr[j,i];
881    }
882  }
883  LUM = ludecomp(Tr);
884  setring Rred;
885  poly d2f = imap(Rdummy,d2f);
886  IB = d2f*IB;
887  IB = reduce(IB,fred);
888  setring QF;
889  matrix IB = transpose(matrix(imap(Rred,IB)));
890  IB = 1/d*IB;
891  LS = lusolve(LUM[1], LUM[2], LUM[3], IB);
892  ideal LL = ideal(LS[2]);
893  setring Roriginal;
894  ideal AI = imap(QF,LL);
895  return(AI);
896}
897
898///////////////////////////////////////////////////////////////////////////////
899static proc adjointIdealIQ(poly f, list choices)
900{
901  poly dhf = subst(f,var(3),1);
902  def Roriginal = basering;
903  list rl = ringlist(Roriginal);
904  rl[2] = list(var(1), var(2));
905  rl[3] = list(list("dp",1:2),list("C",0));
906  def Rdummy = ring(rl);
907  setring Rdummy;
908  list DATA = imap(Roriginal,choices);
909  poly f = imap(Roriginal,dhf);
910  list LIntB;
911  if(DATA[1] <= 4)  // use normalization algorithm
912    {
913      LIntB = integralBasis(f, 2, list(list("inputC", DATA[3]),"isIrred"));
914    }
915  else                                 // use van Hoeij's algorithm
916    {
917      LIntB = integralBasisVH(f,DATA[3],2);  // van Hoeij in future version
918                                             // used when DATA[1] = 5
919    }
920  if(find(DATA[2],"rattestyes") && (DATA[3]==0))
921    {
922      setring Roriginal;
923      int gg = geomGenusIB(f,imap(Rdummy, LIntB));
924      if(gg!=0){ERROR("not a rational curve");}
925      setring Rdummy;
926    }
927  int i,j,k,l;
928  ideal IB = LIntB[1];
929  poly d = LIntB[2];
930  ideal fd = f, d;
931  ideal IBf = IB, f;
932  ideal AI = quotient(fd, IBf);
933//"#### IB:"; IB;
934//"#### d:", d;
935  setring Roriginal;
936  ideal AI = imap(Rdummy,AI);
937//"#### AI:"; AI;
938  return(AI);
939}
940
941///////////////////////////////////////////////////////////////////////////////
942proc mapToRatNormCurve(poly f, ideal AI)
943"USAGE:  mapToRatNormCurve(f, AI); f polynomial, AI ideal
944ASSUME:  The polynomial f is homogeneous in three variables and absolutely
945         irreducible.
946         The plane curve C defined by f is rational.
947         The ideal AI is the adjoint ideal of C.
948RETURN:  ring with an ideal RNC.
949EXAMPLE: example mapToRatNormCurve; shows an example
950"
951{
952   int n = size(AI);
953   int k;
954   //if(n!=deg(f)-1){ERROR("not a rational curve");}
955   def Roriginal = basering;
956   ideal IC = f;
957   list rl = ringlist(Roriginal);
958   /* begin workaround elimination*/
959   for(k = 1; k <= 3; k++)
960     {
961        rl[2][k] = "x("+string(k)+")";
962     }
963   for(k = 1; k <= n; k++)
964     {
965        rl[2][k+3] = "y("+string(k)+")";
966     }
967   rl[3]= list(list("dp",1:(3+n)),list("C",0));
968   def Relim = ring(rl);
969   setring Relim;
970   ideal IC = fetch(Roriginal,IC);
971   ideal AI = fetch(Roriginal,AI);
972   ideal J;
973   J = IC;
974   for(k=1;k<=n;k++)
975     {
976       J=J,var(k+3)-AI[k];
977     }
978   ideal SJ = std(J);
979   intvec HJ = hilb(SJ,1);
980   ideal RNC = eliminate(J,x(1)*x(2)*x(3),HJ);
981   list rl = ringlist(Relim);
982   list rl2 = rl[2];
983   rl[2] = list(rl2[4..n+3]);
984   rl[3]= list(list("dp",1:n),list("C",0));
985   def Rtarget = ring(rl);
986   setring Rtarget;
987   ideal RNC = imap(Relim,RNC);
988   /* end workaround elimination*/
989   export(RNC);
990   int p = printlevel - voice + 3;
991   dbprint(p,"//'mapToRatNorm' created a ring together with an ideal RNC.");
992   dbprint(p,"// Supposing you typed, say,  def RPn = mapToRatNorm(f,AI);");
993   dbprint(p,"// you may access the ideal by typing");
994   dbprint(p,"//      setring RPn; RNC;");
995   return(Rtarget);
996}
997
998example
999{ "EXAMPLE:"; echo=2;
1000  ring R = 0,(x,y,z),dp;
1001  poly f = y^8-x^3*(z+x)^5;
1002  ideal adj = adjointIdeal(f);
1003  def Rn = mapToRatNormCurve(f,adj);
1004  setring(Rn);
1005  RNC;
1006}
1007
1008///////////////////////////////////////////////////////////////////////////////
1009proc rncAntiCanonicalMap(ideal I)
1010"USAGE:  rncAntiCanonicalMap(I); I ideal
1011ASSUME:  I is a homogeneous ideal in the basering
1012         defining a rational normal curve C in PP^n.
1013NOTE:   The procedure will fail or give a wrong output if I is not the
1014        ideal of a rational normal curve.
1015RETURN:  ideal defining the anticanonical map  C --> PP^(n-2). @*
1016         Note that the entries of the ideal should be considered as
1017         representatives of elements in R/I, where R is the basering.
1018THEORY:  The anti-canonical map of a rational normal curve
1019         maps C isomorpically to a rational normal curve in PP^(n-2).
1020KEYWORDS: rational normal curve, projection.
1021EXAMPLE: example rncAntiCanonicalMap; shows an example
1022"
1023{
1024  def Roriginal = basering;
1025  list rl = ringlist(Roriginal);
1026  rl[3] = list(list("dp",1:nvars(Roriginal)),list("C",0));
1027  def RoriginalDP = ring(rl);
1028  setring RoriginalDP;
1029  ideal I = imap(Roriginal,I);
1030  int cc = nvars(RoriginalDP)-2;
1031  module AKD = Ext_R(cc,I);
1032  qring qI = std(I);
1033  matrix AKD = imap(RoriginalDP,AKD);
1034  AKD = syz(transpose(AKD));
1035  ideal PR = submat(AKD,1..nrows(AKD),1);
1036  setring Roriginal;
1037  return(imap(qI,PR));
1038}
1039
1040example
1041{ "EXAMPLE:"; echo=2;
1042  ring R = 0,(x,y,z),dp;
1043  poly f = y^8-x^3*(z+x)^5;
1044  ideal adj = adjointIdeal(f);
1045  def Rn = mapToRatNormCurve(f,adj);
1046  setring(Rn);
1047  RNC;
1048  rncAntiCanonicalMap(RNC);
1049}
1050
1051
1052///////////////////////////////////////////////////////////////////////////////
1053proc rncItProjOdd(ideal I)
1054"USAGE:  rncItProjOdd(I); I ideal
1055ASSUME:  I is a homogeneous ideal in the basering with n+1 variables
1056         defining a rational normal curve C in PP^n with n odd.
1057NOTE:    The procedure will fail or give a wrong output if I is not the
1058         ideal of a rational normal curve. It will test whether n is odd.
1059RETURN:  ideal PHI defining an isomorphic projection of C to PP^1.@*
1060         Note that the entries of PHI should be considered as
1061         representatives of elements in R/I, where R is the basering.
1062THEORY:  We iterate the procedure @ref{rncAntiCanonicalMap} to obtain PHI.
1063KEYWORDS: rational normal curve, projection.
1064SEE ALSO: rncItProjEven.
1065EXAMPLE: example rncItProjOdd; shows an example
1066"
1067{
1068  int n = nvars(basering);
1069  if((n mod 2) == 1){ERROR("Pn has even dimension");}
1070  def Roriginal = basering;
1071  list rlo = ringlist(Roriginal);
1072  rlo[3]= list(list("dp",1:n),list("C",0));
1073  int k;
1074  for(k = 1; k <= n; k++)
1075    {
1076      rlo[2][k] = "z("+string(k)+")";
1077    }
1078  def RoriginalCopy = ring(rlo);
1079  for(k = 1; k <= n; k++)
1080    {
1081      rlo[2][k] = "y("+string(k)+")";
1082    }
1083  def Rold = ring(rlo);
1084  setring RoriginalCopy;
1085  ideal PHI  = maxideal(1);
1086  setring Rold;
1087  ideal J = fetch(Roriginal,I);
1088  list rl2;
1089  def Rnew;
1090  def Rbig;
1091  def Relim;
1092  intvec HJJ;
1093  while(n>2)
1094     {
1095        ideal PR = rncAntiCanonicalMap(J);
1096        list rl = ringlist(Rold);
1097        Rbig = Rold + RoriginalCopy;
1098        setring Rbig;
1099        ideal PHI = imap(RoriginalCopy,PHI);
1100        ideal dummy = imap(Rold,PR);
1101        for(k = 1; k <= n; k++)
1102          {
1103             dummy = subst(dummy,var(k),PHI[k]);
1104          }
1105        setring RoriginalCopy;
1106        PHI = imap(Rbig,dummy);
1107        /* begin workaround elimination*/
1108        setring Rold;
1109        for(k = 1; k <= n; k++)
1110          {
1111            rl[2][k] = "x("+string(k)+")";
1112          }
1113        for(k = 1; k <= n-2; k++)
1114          {
1115            rl[2][k+n] = "y("+string(k)+")";
1116          }
1117        rl[3]= list(list("dp",1:(2*n-2)),list("C",0));
1118        Relim = ring(rl);
1119        setring Relim;
1120        ideal J = fetch(Rold,J);
1121        ideal PR = fetch(Rold,PR);
1122        ideal JJ = J;
1123        poly pvar=1;
1124        for(k = 1; k <= n; k++)
1125          {
1126            pvar = pvar*var(k);
1127          }
1128        for(k=1;k<=n-2;k++)
1129          {
1130            JJ=JJ,var(k+n)-PR[k];
1131          }
1132        ideal SJJ = std(JJ);
1133        HJJ = hilb(SJJ,1);
1134        J = eliminate(JJ,pvar,HJJ);
1135        list rl = ringlist(Relim);
1136        rl2 = rl[2];
1137        rl[2] = list(rl2[n+1..2*n-2]);
1138        rl[3]= list(list("dp",1:(n-2)),list("C",0));
1139        Rnew = ring(rl);
1140        setring Rnew;
1141        ideal J = imap(Relim,J);
1142        /* end workaround elimination*/
1143        Rold = Rnew;
1144        setring Rold;
1145        n = n-2;
1146     }
1147  setring Roriginal;
1148  return(fetch(RoriginalCopy,PHI));
1149}
1150
1151example
1152{ "EXAMPLE:"; echo=2;
1153  ring R = 0,(x,y,z),dp;
1154  poly f = -x7-10x5y2-10x4y3-3x3y4+8x2y5+7xy6+11y7+3x6+10x5y +30x4y2
1155           +26x3y3-13x2y4-29xy5-33y6-3x5-20x4y-33x3y2-8x2y3+37xy4+33y5
1156           +x4+10x3y+13x2y2-15xy3-11y4;
1157  f = homog(f,z);
1158  ideal adj = adjointIdeal(f);
1159  def Rn = mapToRatNormCurve(f,adj);
1160  setring(Rn);
1161  RNC;
1162  rncItProjOdd(RNC);
1163}
1164
1165
1166///////////////////////////////////////////////////////////////////////////////
1167proc rncItProjEven(ideal I)
1168"USAGE:  rncItProjEven(I); I ideal
1169ASSUME:  I is a homogeneous ideal in the basering with n+1 variables
1170         defining a rational normal curve C in PP^n with n even.
1171NOTE:    The procedure will fail or give a wrong output if I is not the
1172         ideal of a rational normal curve. It will test whether n is odd.
1173RETURN:  ring with an ideal CONIC defining a conic C2 in PP^2.@*
1174         In addition, an ideal PHI in the basering defining an isomorphic
1175         projection of C to C2 will be exported.@*
1176         Note that the entries of PHI should be considered as
1177         representatives of elements in R/I, where R is the basering.
1178THEORY:  We iterate the procedure @ref{rncAntiCanonicalMap} to obtain PHI.
1179KEYWORDS: rational normal curve, projection.
1180SEE ALSO: rncItProjOdd.
1181EXAMPLE: example rncItProjEven; shows an example
1182"
1183{
1184  int n = nvars(basering);
1185  if((n mod 2) == 0){ERROR("Pn has odd dimension");}
1186  def Roriginal = basering;
1187  list rlo = ringlist(Roriginal);
1188  rlo[3]= list(list("dp",1:n),list("C",0));
1189  int k;
1190  for(k = 1; k <= n; k++)
1191    {
1192      rlo[2][k] = "z("+string(k)+")";
1193    }
1194  def RoriginalCopy = ring(rlo);
1195  for(k = 1; k <= n; k++)
1196    {
1197      rlo[2][k] = "y("+string(k)+")";
1198    }
1199  def Rold = ring(rlo);
1200  setring RoriginalCopy;
1201  ideal PHI  = maxideal(1);
1202  setring Rold;
1203  ideal J = fetch(Roriginal,I);
1204  list rl2;
1205  def Rnew;
1206  def Rbig;
1207  def Relim;
1208  intvec HJJ;
1209  while(n>3)
1210     {
1211        ideal PR = rncAntiCanonicalMap(J);
1212        list rl = ringlist(Rold);
1213        Rbig = Rold + RoriginalCopy;
1214        setring Rbig;
1215        ideal PHI = imap(RoriginalCopy,PHI);
1216        ideal dummy = imap(Rold,PR);
1217        for(k = 1; k <= n; k++)
1218          {
1219             dummy = subst(dummy,var(k),PHI[k]);
1220          }
1221        setring RoriginalCopy;
1222        PHI = imap(Rbig,dummy);
1223        /* begin workaround elimination*/
1224        setring Rold;
1225        for(k = 1; k <= n; k++)
1226          {
1227            rl[2][k] = "x("+string(k)+")";
1228          }
1229        for(k = 1; k <= n-2; k++)
1230          {
1231            rl[2][k+n] = "y("+string(k)+")";
1232          }
1233        rl[3]= list(list("dp",1:(2*n-2)),list("C",0));
1234        Relim = ring(rl);
1235        setring Relim;
1236        ideal J = fetch(Rold,J);
1237        ideal PR = fetch(Rold,PR);
1238        ideal JJ = J;
1239        poly pvar=1;
1240        for(k = 1; k <= n; k++)
1241          {
1242            pvar = pvar*var(k);
1243          }
1244        for(k=1;k<=n-2;k++)
1245          {
1246            JJ=JJ,var(k+n)-PR[k];
1247          }
1248        ideal SJJ = std(JJ);
1249        HJJ = hilb(SJJ,1);
1250        J = eliminate(JJ,pvar,HJJ);
1251        list rl = ringlist(Relim);
1252        rl2 = rl[2];
1253        rl[2] = list(rl2[n+1..2*n-2]);
1254        rl[3]= list(list("dp",1:(n-2)),list("C",0));
1255        Rnew = ring(rl);
1256        setring Rnew;
1257        ideal J = imap(Relim,J);
1258        /* end workaround elimination*/
1259        Rold = Rnew;
1260        setring Rold;
1261        n = n-2;
1262     }
1263  poly CONIC = J[1];
1264  export(CONIC);
1265  setring Roriginal;
1266  ideal PHI = fetch(RoriginalCopy,PHI);
1267  export(PHI);
1268  return(Rold);
1269}
1270
1271example
1272{ "EXAMPLE:"; echo=2;
1273  ring R = 0,(x,y,z),dp;
1274  poly f = y^8-x^3*(z+x)^5;
1275  ideal adj = adjointIdeal(f);
1276  def Rn = mapToRatNormCurve(f,adj);
1277  setring(Rn);
1278  RNC;
1279  def Rc = rncItProjEven(RNC);
1280  PHI;
1281  setring Rc;
1282  CONIC;
1283}
1284
1285///////////////////////////////////////////////////////////////////////////////
1286static proc geomGenusIB(poly f, list #)
1287"USAGE:  geomGenusIB(f [, L]); f poly, L optional list representing the
1288         integral basis as returned by @ref integralBasisJ.
1289ASSUME:  The basering must be a polynomial ring in three variables, say x,y,z,
1290         with coefficients in Q. @*
1291         The polynomial f must be homogeneous and absolutely irreducible.@*
1292         Its dehomogenization with respect to the third variable must be monic
1293         as a polynomial in the second variable (that is, the curve C = {f = 0}
1294         does not contain the point (0:1:0)).@*
1295         The curve C is not allowed to have singularities
1296         at infinity (z = 0). @*
1297NOTE:    The last two conditions can be met by a suitable change of coordinates in PGL(3)
1298         as applied in the procedure @ref adjointIdeal. The other conditions
1299         can be tested using @ref checkAssumptions.@*
1300RETURN:  int, the geometric genus of C.
1301THEORY:  We compute an integral basis of the integral closure of the coordinate
1302         ring of C and from that the geometric genus.@*
1303KEYWORDS: geometric genus, plane curves.
1304SEE ALSO: genus.
1305"
1306{
1307  int bb = size(#);
1308  poly dhf = subst(f,var(3),1);
1309  def Roriginal = basering;
1310  list rl = ringlist(Roriginal);
1311  rl[2] = list(var(1), var(2));
1312  rl[3] = list(list("dp",1:2),list("C",0));
1313  def Rdummy = ring(rl);
1314  setring Rdummy;
1315  poly f = imap(Roriginal,dhf);
1316  list LIntB;
1317  if(bb == 0)
1318    {
1319      LIntB = integralBasis(f,2,"isIrred");
1320    }
1321  else
1322    {
1323      LIntB = imap(Roriginal,#);
1324    }
1325  ideal IB = LIntB[1];
1326  poly d = LIntB[2];
1327  int ud = deg(d);
1328  int sL = size(IB);
1329  int k;
1330  int gg = (sL-1)*(sL-2) div 2-sL*ud;
1331  for(k = 1; k <= sL; k++)
1332     {
1333        gg = gg + deg(gcd(d,IB[k]));
1334     }
1335  setring Roriginal;
1336  return(gg);
1337}
1338
1339
1340///////////////////////////////////////////////////////////////////////////////
1341static proc geomGenusLA(poly F)
1342"USAGE:  geomGenusLA(F); F polynomial
1343ASSUME:  The basering must be a polynomial ring in three variables. @*
1344         The polynomial F must be homogeneous.@*
1345RETURN:  list L:
1346@texinfo
1347@table @asis
1348@item @code{L[1]}; int:
1349         the geometric genus p_g = p_a - delta of the projective
1350         curve C defined by F, where p_a is the arithmetic genus.
1351@item @code{L[2]}; int:
1352         is positive if C has singularities other
1353         than ordinary multiple points.@*
1354@item @code{L[3]}; list:
1355         consists of one list for each primary component
1356         of the singular locus of C which corresponds to a set of conjugated
1357         ordinary multiple points. Each list consists of an int, the
1358         multiplicity of the points, and an ideal, the primary component.
1359@end table
1360@end texinfo
1361NOTE:    delta is the sum of all local delta-invariants of the singularities,
1362         i.e. dim(R'/R), R' the normalization of the local ring R of the
1363         singularity. @*
1364SEE ALSO: genus
1365"
1366{
1367   int w = printlevel-voice+2;  // w=printlevel (default: w=0)
1368   int d = deg(F);
1369   def R = basering;
1370   ring S = create_ring(ring_list(R)[1], "(x,y,t)", "dp", "no_minpoly");
1371   ring C = create_ring(ring_list(R)[1], "(x,y)", "ds", "no_minpoly");
1372   int genus=(d-1)*(d-2) div 2;
1373   if(w>=1){"the arithmetic genus of the plane curve:";genus;pause();}
1374
1375   int delt,deltaloc,deltainf,tau,tauinf,cusps,iloc,iglob,l,nsing,
1376       tauloc,tausing,k,rat,nbranchinf,nbranch,nodes,cuspsinf,nodesinf;
1377   list inv;
1378   ring newR = create_ring(ring_list(R)[1], "(x,y)", "dp", "no_minpoly");
1379   //the singularities at the affine part
1380   map sigma=R,var(1),var(2),1;
1381   ideal I=sigma(F);
1382
1383   list OMPButNodes;
1384   int sizeOMPButNodes;
1385   int NotOnlyOMPPlusCusps;
1386
1387   ideal I1=jacob(I);
1388   matrix Hess[2][2]=jacob(I1);
1389   ideal ID=I+I1+ideal(det(Hess));//singular locus of I+I1
1390   ideal radID=std(radical(ID));//the non-nodal locus
1391   if(w>=1){"the non-nodal locus:";"";radID;pause();"";}
1392   if(deg(radID[1])==0)
1393   {
1394     ideal IDsing=1;
1395   }
1396   else
1397   {
1398     ideal IDsing=minor(jacob(ID),2)+radID;//singular locus of ID
1399   }
1400
1401   iglob=vdim(std(IDsing));
1402
1403   ideal radIDsing = 1;
1404
1405   if(iglob!=0)//computation of the radical of IDsing
1406   {
1407      radIDsing=reduce(IDsing,radID);
1408      if(size(radIDsing)==0)
1409      {
1410         radIDsing=radID;
1411         attrib(radIDsing,"isSB",1);
1412      }
1413      else
1414      {
1415         radIDsing=std(radical(IDsing));
1416      }
1417      iglob=vdim(radIDsing);
1418      if((w>=1)&&(iglob))
1419          {"the non-nodal-cuspidal locus:";radIDsing;pause();"";}
1420   }
1421   cusps=vdim(radID)-iglob;
1422
1423   ideal NodesPlusCusps  = radical(sat(I+I1, radIDsing)[1]);
1424
1425   nsing=nsing+cusps;
1426
1427   if(iglob==0)
1428   {
1429      if(w>=1){"             there are only cusps and nodes";"";}
1430      tau=vdim(std(I+jacob(I)));
1431      tauinf=tauinf+tau;
1432      nodes=tau-2*cusps;
1433      delt=nodes+cusps;
1434      nbranch=2*tau-3*cusps;
1435      nsing=nsing+nodes;
1436   }
1437   else
1438   {
1439       if(w>=1){"the non-nodal-cuspidal singularities";"";}
1440       setring C;
1441       ideal I1=imap(newR,radIDsing);
1442       iloc=vdim(std(I1));
1443       if(iglob==iloc)
1444       {
1445          if(w>=1){"only cusps and nodes outside (0,0,1)";}
1446          setring newR;
1447          tau=vdim(std(I+jacob(I)));
1448          tauinf=tauinf+tau;
1449          inv=deltaLocMod(I[1],maxideal(1));
1450          delt=inv[1];
1451          tauloc=inv[2];
1452          nodes=tau-tauloc-2*cusps;
1453          nsing=nsing+nodes;
1454          if(inv[2]!=0)
1455            {
1456              nsing=nsing+1;
1457            }
1458          nbranch=inv[3]+ 2*nodes+cusps;
1459          delt=delt+nodes+cusps;
1460          if((w>=1)&&(inv[2]==0)){"smooth at (0,0,1)";}
1461          if(inv[4]!=0)
1462            {
1463              OMPButNodes = insert(OMPButNodes,list(inv[4],maxideal(1)),
1464                                   sizeOMPButNodes);
1465              sizeOMPButNodes = size(OMPButNodes); // new
1466            }
1467          else
1468            {
1469              NotOnlyOMPPlusCusps = NotOnlyOMPPlusCusps + 1;
1470            }
1471        }
1472        else
1473        {
1474           setring newR;
1475           list pr=minAssGTZ(radIDsing);
1476           if(w>=1){pr;}
1477
1478           for(k=1;k<=size(pr);k++)
1479           {
1480              if(w>=1){nsing=nsing+vdim(std(pr[k]));}
1481              inv=deltaLocMod(I[1],pr[k]);
1482              delt=delt+inv[1];
1483              tausing=tausing+inv[2];
1484              nbranch=nbranch+inv[3];
1485              if(inv[4]!=0)
1486                {
1487                  OMPButNodes = insert(OMPButNodes,list(inv[4],pr[k]),
1488                                       sizeOMPButNodes);
1489                  sizeOMPButNodes = size(OMPButNodes);
1490                }
1491              else
1492                {
1493                  NotOnlyOMPPlusCusps = NotOnlyOMPPlusCusps + 1;
1494                }
1495           }
1496           tau=vdim(std(I+jacob(I)));
1497           tauinf=tauinf+tau;
1498           nodes=tau-tausing-2*cusps;
1499           nsing=nsing+nodes;
1500           delt=delt+nodes+cusps;
1501           nbranch=nbranch+2*nodes+cusps;
1502        }
1503   }
1504   genus=genus-delt-deltainf;
1505   if(w>=1)
1506   {
1507      "The projected plane curve has locally:";"";
1508      "singularities:";nsing;
1509      "branches:";nbranch+nbranchinf;
1510      "nodes:"; nodes+nodesinf;
1511      "cusps:";cusps+cuspsinf;
1512      "Tjurina number:";tauinf;
1513      "Milnor number:";2*(delt+deltainf)-nbranch-nbranchinf+nsing;
1514      "delta of the projected curve:";delt+deltainf;
1515      //"delta of the curve:";p_a-genus;
1516      "genus:";genus;
1517      "====================================================";
1518      "";
1519   }
1520   setring R;
1521   if(sizeOMPButNodes>0)
1522     {
1523       list OMPButNodes = fetch(newR,OMPButNodes);
1524     }
1525   return(list(genus,NotOnlyOMPPlusCusps,OMPButNodes,
1526               fetch(newR,NodesPlusCusps)));
1527}
1528
1529
1530///////////////////////////////////////////////////////////////////////////////
1531static proc deltaLocMod(poly f,ideal singL)
1532"USAGE:  deltaLoc(f,J);  f poly, J ideal
1533ASSUME: f is reduced bivariate polynomial; basering has exactly two variables;
1534        J is irreducible prime component of the singular locus of f (e.g., one
1535        entry of the output of @code{minAssGTZ(I);}, I = <f,jacob(f)>).
1536RETURN:  list L:
1537@texinfo
1538@table @asis
1539@item @code{L[1]}; int:
1540         the sum of (local) delta invariants of f at the (conjugated) singular
1541         points given by J.
1542@item @code{L[2]}; int:
1543         the sum of (local) Tjurina numbers of f at the (conjugated) singular
1544         points given by J.
1545@item @code{L[3]}; int:
1546         the sum of (local) number of branches of f at the (conjugated)
1547         singular points given by J.
1548@item @code{L[3]}; int:
1549         the multiplicity of f at the (conjugated) singular points given by J,
1550         if these are ordinary multiple points, and 0 otherwise.
1551@end table
1552@end texinfo
1553NOTE:    procedure makes use of @code{execute}; increasing printlevel displays
1554         more comments (default: printlevel=0).
1555SEE ALSO: deltaLoc, delta, tjurina
1556KEYWORDS: delta invariant; Tjurina number
1557"
1558{
1559   option(redSB);
1560   def R=basering;
1561   ring S = create_ring(ring_list(R)[1], "(x,y)", "lp", "no_minpoly");
1562   map phi=R,x,y;
1563   ideal singL=phi(singL);
1564   singL=simplify(std(singL),1);
1565   attrib(singL,"isSB",1);
1566   int d=vdim(singL);
1567   poly f=phi(f);
1568   int i;
1569   int w = printlevel-voice+2;  // w=printlevel (default: w=0)
1570   if(d==1)
1571   {
1572      map alpha=S,var(1)-singL[2][2],var(2)-singL[1][2];
1573      f=alpha(f);
1574      ring C = create_ring(ring_list(S)[1], "("+varstr(S)+")", "ds", "no_minpoly");
1575      poly f=imap(S,f);
1576      ideal singL=imap(S,singL);
1577      if((w>=1)&&(ord(f)>=2))
1578      {
1579        "local analysis of the singularities";"";
1580        basering;
1581        singL;
1582        f;
1583        pause();
1584      }
1585   }
1586   else
1587   {
1588      poly p;
1589      poly c;
1590      map psi;
1591      number co;
1592
1593      while((deg(lead(singL[1]))>1)&&(deg(lead(singL[2]))>1))
1594      {
1595         psi=S,x,y+random(-100,100)*x;
1596         singL=psi(singL);
1597         singL=std(singL);
1598          f=psi(f);
1599      }
1600
1601      if(deg(lead(singL[2]))==1)
1602      {
1603         p=singL[1];
1604         c=singL[2]-lead(singL[2]);
1605         co=leadcoef(singL[2]);
1606      }
1607      if(deg(lead(singL[1]))==1)
1608      {
1609         psi=S,y,x;
1610         f=psi(f);
1611         singL=psi(singL);
1612         p=singL[2];
1613         c=singL[1]-lead(singL[1]);
1614         co=leadcoef(singL[1]);
1615      }
1616
1617      ring B = create_ring(ring_list(S)[1], "a", "dp", "no_minpoly");
1618      map beta=S,a,a;
1619      poly p=beta(p);
1620
1621      ring C = create_ring("("+charstr(S)+",a)", "("+varstr(S)+")", "ds");
1622      number p=number(imap(B,p));
1623      minpoly=p;
1624
1625      map iota=S,a,a;
1626      number c=number(iota(c));
1627      number co=iota(co);
1628
1629      map alpha=S,x-c/co,y+a;
1630      poly f=alpha(f);
1631      f=cleardenom(f);
1632      if((w>=1)&&(ord(f)>=2))
1633      {
1634        "local analysis of the singularities";"";
1635        basering;
1636        alpha;
1637        f;
1638        pause();
1639        "";
1640      }
1641   }
1642   int intMult = deg(lead(f));
1643   poly fdummy = f;
1644   poly gdummy = lead(f);
1645   int ivr = 1;
1646   while(ivr)
1647      {
1648        fdummy = fdummy - lead(fdummy);
1649        if((fdummy ==0) || (deg(lead(fdummy))>intMult)){break;}
1650        gdummy = gdummy + lead(fdummy);
1651      }
1652   poly SQRpart = sqrfree(gdummy, 3);
1653   int IntForRet;
1654   if(deg(SQRpart)==intMult)
1655     {
1656        IntForRet = intMult;
1657     }
1658   option(noredSB);
1659   ideal fstd=std(ideal(f)+jacob(f));
1660   poly hc=highcorner(fstd);
1661   int tau=vdim(fstd);
1662   int o=ord(f);
1663   int delt,nb;
1664
1665   if(tau==0)                 //smooth case
1666   {
1667      setring R;
1668      return(list(0,0,1,0));
1669   }
1670   if((char(basering)>=181)||(char(basering)==0))
1671   {
1672      if(o==2)                //A_k-singularity
1673      {
1674        if(w>=1){"A_k-singularity";"";}
1675         setring R;
1676         delt=(tau+1) div 2;
1677         return(list(d*delt,d*tau,d*(2*delt-tau+1),IntForRet));
1678      }
1679      if((lead(f)==var(1)*var(2)^2)||(lead(f)==var(1)^2*var(2)))
1680      {
1681        if(w>=1){"D_k- singularity";"";}
1682
1683         setring R;
1684         delt=(tau+2) div 2;
1685         return(list(d*delt,d*tau,d*(2*delt-tau+1),IntForRet));
1686      }
1687
1688      int mu=vdim(std(jacob(f)));
1689      poly g=f+var(1)^mu+var(2)^mu;  //to obtain a convenient Newton-polygon
1690
1691      list NP=newtonpoly(g);
1692      if(w>=1){"Newton-Polygon:";NP;"";}
1693      int s=size(NP);
1694
1695      if(is_NND(f,mu,NP))
1696      { // the Newton-polygon is non-degenerate
1697        // compute nb, the number of branches
1698        for(i=1;i<=s-1;i++)
1699        {
1700          nb=nb+gcd(NP[i][2]-NP[i+1][2],NP[i][1]-NP[i+1][1]);
1701        }
1702        if(w>=1){"Newton-Polygon is non-degenerated";"";}
1703        return(list(d*(mu+nb-1) div 2,d*tau,d*nb,IntForRet));
1704      }
1705
1706      if(w>=1){"Newton-Polygon is degenerated";"";}
1707
1708      // the following can certainly be made more efficient when replacing
1709      // 'hnexpansion' (used only for computing number of branches) by
1710      // successive blowing-up + test if Newton polygon degenerate:
1711      if(s>2)    //  splitting of f
1712      {
1713         if(w>=1){"Newton polygon can be used for splitting";"";}
1714         intvec v=NP[1][2]-NP[2][2],NP[2][1];
1715         int de=w_deg(g,v);
1716         int st=w_deg(hc,v)+v[1]+v[2];
1717         poly f1=var(2)^NP[2][2];
1718         poly f2=jet(g,de,v)/var(2)^NP[2][2];
1719         poly h=g-f1*f2;
1720         de=w_deg(h,v);
1721         poly k;
1722         ideal wi=var(2)^NP[2][2],f2;
1723         matrix li;
1724         while(de<st)
1725         {
1726           k=jet(h,de,v);
1727           li=lift(wi,k);
1728           f1=f1+li[2,1];
1729           f2=f2+li[1,1];
1730           h=g-f1*f2;
1731           de=w_deg(h,v);
1732         }
1733         nb=deltaLocMod(f1,maxideal(1))[3]+deltaLocMod(f2,maxideal(1))[3];
1734         setring R;
1735         return(list(d*(mu+nb-1) div 2,d*tau,d*nb,IntForRet));
1736      }
1737
1738      f=jet(f,deg(hc)+2);
1739      if(w>=1){"now we have to use Hamburger-Noether (Puiseux) expansion";}
1740      ideal fac=factorize(f,1);
1741      if(size(fac)>1)
1742      {
1743         nb=0;
1744         for(i=1;i<=size(fac);i++)
1745         {
1746            nb=nb+deltaLocMod(fac[i],maxideal(1))[3];
1747         }
1748         setring R;
1749         return(list(d*(mu+nb-1) div 2,d*tau,d*nb,IntForRet));
1750      }
1751      list HNEXP=hnexpansion(f);
1752      if (typeof(HNEXP[1])=="ring") {
1753        def altring = basering;
1754        def HNEring = HNEXP[1]; setring HNEring;
1755        nb=size(hne);
1756        setring R;
1757        kill HNEring;
1758      }
1759      else
1760      {
1761        nb=size(HNEXP);
1762      }
1763      return(list(d*(mu+nb-1) div 2,d*tau,d*nb,IntForRet));
1764   }
1765   else             //the case of small characteristic
1766   {
1767      f=jet(f,deg(hc)+2);
1768      if(w>=1){"now we have to use Hamburger-Noether (Puiseux) expansion";}
1769      delt=delta(f);
1770      return(list(d*delt,d*tau,d,IntForRet));
1771   }
1772}
1773
1774///////////////////////////////////////////////////////////////////////////////
1775proc paraConic(poly q)
1776"USAGE:  paraConic(q); q poly
1777ASSUME:  The basering must be a polynomial ring in three variables with
1778         coefficients in Q. @*
1779         The polynomial q must be homogeneous of degree 2 and absolutely
1780         irreducible. @*
1781NOTE:    The procedure might fail or give a wrong output if the assumptions
1782         do not hold.
1783
1784RETURN:  ring with an ideal PARACONIC. The ring should be considered as the
1785         homogeneous coordinate ring of PP^1, the ideal defines a rational
1786         parametrization PP^1 --> C2 = {q=0}.
1787
1788THEORY:  We compute a point on C2 via @ref{rationalPointConic}. The pencil of
1789         lines through this point projects C2 birationally to PP^1. Inverting
1790         the projection gives the result.
1791KEYWORDS: conic, parametrization, rational point.
1792SEE ALSO: rationalPointConic.
1793EXAMPLE: example paraConic; shows an example
1794"
1795{
1796  def Roriginal = basering;
1797  def RP2 = projConic(q);  // ring with ideal Ipoint
1798                           // possibly defined over algebraic number field
1799  setring RP2;
1800  def rp1 = invertBirMap(Ipoint, ideal(fetch(Roriginal,q)));
1801  setring rp1;
1802  list rl = ringlist(rp1);
1803  rl[2] = list("s","t");
1804  def RP1 = ring(rl);
1805  setring RP1;
1806  ideal PARACONIC = fetch(rp1,psi);
1807  export(PARACONIC);
1808  int p = printlevel - voice + 3;
1809  dbprint(p,"// 'paraConic' created a ring together with an ideal RNC.
1810// Supposing you typed, say,  def RP1 = paraConic(q);
1811// you may access the ideal by typing
1812//      setring RP1; PARACONIC;");
1813  return(RP1);
1814}
1815example
1816{ "EXAMPLE:"; echo=2;
1817  ring R = 0,(x,y,z),dp;
1818  poly f = y^8-x^3*(z+x)^5;
1819  ideal adj = adjointIdeal(f);
1820  def Rn = invertBirMap(adj,ideal(f));
1821  setring(Rn);
1822  J;
1823  def Rc = rncItProjEven(J);
1824  PHI;
1825  setring Rc;
1826  CONIC;
1827  def RPc = paraConic(CONIC);
1828  setring RPc;
1829  PARACONIC;
1830}
1831
1832///////////////////////////////////////////////////////////////////////////////
1833static proc projConic(poly q)
1834"USAGE:  projConic(q); q poly
1835ASSUME:  The basering must be a polynomial ring in three variables with
1836         coefficients in Q. @*
1837         The polynomial q must be homogeneous of degree 2 and absolutely
1838         irreducible. @*
1839NOTE:    The procedure might fail or give a wrong output if the assumptions
1840         do not hold.
1841RETURN:  ring with an ideal Ipoint defining a pencil of lines through a point
1842         on the conic C2 = {q=0}. This point has either coefficients in Q or
1843         in a quadratic extension field of Q.
1844THEORY:  We compute the point on C2 via @ref rationalPointConic.
1845KEYWORDS: conic, parametrization, rational point.
1846SEE ALSO: rationalPointConic.
1847"
1848{
1849  def Roriginal = basering;
1850  list rl = ringlist(Roriginal);
1851  rl[3] = list(list("dp",1:3),list("C",0));
1852  def RP20 = ring(rl);
1853  setring RP20;
1854  poly q = imap(Roriginal,q);
1855  def RP21 = rationalPointConic(q);  //  ring with ideal point representing
1856                                     //  point on conic
1857                                     //  possibly defined over algebraic number
1858                                     //  field
1859  setring RP21;
1860  list rl1 = ringlist(RP21);
1861  rl1[2] = list("u","v","w");
1862  rl1[3] = list(list("dp",1:3),list("C",0));
1863  def RP2 = ring(rl1);
1864  setring RP2;
1865  ideal point = fetch(RP21,point);
1866  matrix bP = syz(point);
1867  ideal Ipoint = matrix(maxideal(1))*bP;  // defines pencil of lines through
1868                                          // point
1869  export(Ipoint);
1870  return(RP2);
1871}
1872
1873
1874///////////////////////////////////////////////////////////////////////////////
1875static proc isIrreducible(poly f)
1876"USAGE:  isIrreducible(f); f poly
1877RETURN:  1 iff the given polynomial f is irreducible; 0 otherwise.
1878THEORY:  This test is performed by computing the absolute factorization of f.
1879KEYWORDS: irreducible.
1880"
1881{
1882  def r = basering;
1883  def s = absFactorize(f);
1884  setring s;
1885  list L = absolute_factors;
1886  int result = 0;
1887  if (L[4] == 1){result = 1;}
1888  setring r;
1889  kill s;
1890  return (result);
1891}
1892
1893
1894///////////////////////////////////////////////////////////////////////////////
1895static proc isQuadratic(poly p)
1896"USAGE:  isQuadratic(p); p poly
1897RETURN:  checks whether p is a homogeneous, quadratic polynomial in the
1898         first three ring variables, x, y, z say;
1899         If so, the method extracs the coefficients a, b, ..., f such that
1900         p = a*x2 + b*xy + c * y2 + d * xz + e * yz + f * z2
1901         and returns them as a list of seven entries, [1, a, b, c, d, e, f];
1902         otherwise, a list with the single entry [0] is returned
1903"
1904{
1905  bigint a = bigint(leadcoef(subst(p, var(2), 0, var(3), 0)));
1906  bigint c = bigint(leadcoef(subst(p, var(1), 0, var(3), 0)));
1907  bigint f = bigint(leadcoef(subst(p, var(1), 0, var(2), 0)));
1908  poly h = p - a * var(1)^2 - c * var(2)^2 - f * var(3)^2;
1909  bigint b = bigint(leadcoef(subst(h, var(3), 0)));
1910  bigint d = bigint(leadcoef(subst(h, var(2), 0)));
1911  bigint e = bigint(leadcoef(subst(h, var(1), 0)));
1912  list L = 0;
1913  if (h - b * var(1) * var(2) - d * var(1) * var(3)
1914        - e * var(2) * var(3) != 0) { return (L); }
1915  L = 1, a, b, c, d, e, f;
1916  return (L);
1917}
1918
1919
1920///////////////////////////////////////////////////////////////////////////////
1921static proc largestSquare(bigint n)
1922"USAGE:  largestSquare(n); n bigint
1923ASSUME:  n <> 0
1924RETURN:  returns the largest positive number m (as bigint) such that m^2
1925         divides n.
1926THEORY:  This computation is done by prime factorization of n.
1927KEYWORDS: prime factorization.
1928"
1929{
1930  if (n == 0) { "ERROR: largestSquare(0) had been invoked"; }
1931
1932  bigint nn = n; if (nn < 0) { nn = -n; }
1933  list L = primefactors(nn);
1934  if (L[3] != 1)
1935  { "WARNING: command 'primefactors(.)' did not find all prime factors"; }
1936  int i; bigint m = bigint(1); int e; int j;
1937  for (i = 1; i <= size(L[1]); i++)
1938  {
1939    e = L[2][i] div 2;
1940    for (j = 1; j <= e; j++) { m = m * bigint(L[1][i]); }
1941  }
1942  return (m);
1943}
1944
1945
1946///////////////////////////////////////////////////////////////////////////////
1947static proc jIndex(bigint a, bigint b, bigint c)
1948"USAGE:  jIndex(a, b, c); a, b, c bigint's
1949RETURN:  returns the middle of the three numbers |ab|, |bc|, and |ca|.
1950"
1951{
1952  bigint n1 = a*b; if (n1 < 0) { n1 = -n1; }
1953  bigint n2 = b*c; if (n2 < 0) { n2 = -n2; }
1954  bigint n3 = c*a; if (n3 < 0) { n3 = -n3; }
1955  if ((n1 <= n2) && (n2 <= n3)) { return (n2); }
1956  if ((n1 >= n2) && (n2 >= n3)) { return (n2); }
1957  if ((n2 <= n1) && (n1 <= n3)) { return (n1); }
1958  if ((n2 >= n1) && (n1 >= n3)) { return (n1); }
1959  return (n3);
1960}
1961
1962
1963///////////////////////////////////////////////////////////////////////////////
1964static proc aMod(bigint a, bigint b)
1965"USAGE:  aMod(a,b); a, b bigint
1966RETURN:  r bigint
1967THEORY:  The asymmetric residue r of the division with remainder a mod b.
1968"
1969{
1970  bigint c = a mod b;
1971  if (c<0)
1972  {
1973    return(c+b);
1974  }
1975  return(c);
1976}
1977
1978///////////////////////////////////////////////////////////////////////////////
1979static proc aDiv(bigint a, bigint b)
1980"USAGE:  aDiv(a,b); a, b bigint
1981RETURN:  q bigint
1982THEORY:  Quotient with remainder q = a div b with asymmetric residue.
1983"
1984{
1985  bigint q = a div b;
1986  if ((a mod b)<0)
1987  {
1988    return(q-1);
1989  }
1990return(q);
1991}
1992
1993
1994
1995///////////////////////////////////////////////////////////////////////////////
1996static proc polyModP(poly q, bigint p)
1997"USAGE:  polyModP(q, p); q poly, p bigint
1998RETURN:  takes each coefficient of q modulo p and returns the resulting poly
1999"
2000{
2001  poly qq = q; poly res = 0;
2002  bigint c;
2003  while (qq != 0)
2004  {
2005    c = bigint(leadcoef(qq)) mod p;
2006    res = res + c * leadmonom(qq);
2007    qq = qq - lead(qq);
2008  }
2009  return (res);
2010}
2011
2012
2013///////////////////////////////////////////////////////////////////////////////
2014static proc rootModP(bigint r, bigint p)
2015"USAGE:  rootModP(r, p); r, p bigint's
2016ASSUME:  0 <= r < p, and p prime;
2017         Furthermore it is assumes that there is some x in {0, 1, ..., p-1}
2018         such that x^2 = r mod p;
2019RETURN:  an x in {0, 1, ..., p-1} such that x^2 = r mod p;
2020THEORY:  For p larger than 32003, this computation is done using Cantor-
2021         Zassenhaus' algorithm. Otherwise a brute force approach is used.
2022KEYWORDS: Cantor-Zassenhaus algorithm.
2023"
2024{
2025  if (r == 0) { return (0); }
2026  if (r == 1) { return (1); }
2027  if (p <= 32003)
2028  {
2029    /* For small p, we use a brute force approach: */
2030    int i;
2031    for (i = 2; i < p; i++)
2032    {
2033      if (((i*i) mod p) == r) { return (i); }
2034    }
2035    /* should never be reached: */
2036    return (-1);
2037  }
2038
2039  /* For p > 32003, we use Cantor-Zassenhaus' algorithm: */
2040  def br = basering;
2041  ring rTemp = 0, x, dp;
2042  bigint b; bigint exponent; poly factor;
2043  poly h = x^2 - r;
2044  ideal redI = h; redI = std(redI);
2045  poly q = x^2; bigint root = 0;
2046  while (root == 0)
2047  {
2048    b = bigint(random(1, 2^30));
2049    exponent = bigint((p - 1) div 2);
2050    /* We need to compute q^exponent mod (x^2 - a) and mod p: */
2051    factor = x + b; q = 1;
2052    while (exponent > 0)
2053    {
2054      if ((exponent mod 2) == 1)
2055      {
2056        q = q * factor;
2057        q = reduce(q, redI);
2058        q = polyModP(q, p);
2059      }
2060      exponent = bigint(exponent div 2);
2061      factor = factor * factor;
2062      factor = reduce(factor, redI);
2063      factor = polyModP(factor, p);
2064    }
2065    if (deg(q) == 1)
2066    {
2067      q = q - 1;
2068      b = inverseModP(bigint(leadcoef(q)), p);
2069      q = q - lead(q);
2070      root = aMod((bigint(q) * b),p);
2071      if (((root * root - r) mod p) != 0) { root = 0; }
2072    }
2073  }
2074  setring br; kill rTemp;
2075  return (root);
2076}
2077
2078
2079///////////////////////////////////////////////////////////////////////////////
2080static proc inverseModP(bigint r, bigint p)
2081"USAGE:  inverseModP(r, p); r, p bigint's
2082ASSUME:  0 <= r < p, and r and p coprime;
2083RETURN:  returns the inverse of r in Z/p represented by an element in
2084         {1, 2, ..., p-1}
2085THEORY:  This uses Euclid's extended gcd algorithm.
2086"
2087{
2088  list L = extgcd(r, p);
2089  if (L[1] != 1) { ERROR("GCD of", r, "and", p, "should be 1."); }
2090  L[2] = aMod(L[2],p);
2091  return (L[2]);
2092}
2093
2094
2095///////////////////////////////////////////////////////////////////////////////
2096static proc squareRoot(bigint r, bigint m, int justCheck)
2097"USAGE:  squareRoot(r, m, j); r, m bigint's, j int
2098RETURN:  checks whether r is a square modulo m, i.e., checks whether there is
2099         some x such that x^2 = r mod m;
2100         If justCheck is 1, then the method will terminate after the check
2101         and return 1 if r is a square and -1 otherwise.
2102         If justCheck is 0 and r is a square, then the method continues and
2103         computes a solution x in {0, 1, m-1} with x^2 = r mod m, which will
2104         then be returned
2105THEORY:  This algorithm checks solvability by computing the Legendre symbols
2106         modulo all primes in m. Then, individual roots will be computed and
2107         lifted to the desired square root modulo m using Chinese
2108         remaindering.
2109"
2110{
2111  if (m == 0) { "ERROR: squareRoot had been invoked with m = 0"; }
2112
2113  list L = primefactors(m);
2114  if ((L[3] != 1) && (L[3] != -1))
2115  { "WARNING: command 'primefactors(.)' did not find all prime factors"; }
2116  int i;
2117  for (i = 1; i <= size(L[2]); i++)
2118  {
2119    if (legendreSymbol(r, L[1][i]) == -1) { return (-1); }
2120  }
2121  /* now we know that there is some x in {0, 1, m-1} with
2122     x^2 = r mod m */
2123  if (justCheck == 1) { return (1); }
2124  else
2125  {
2126    // now we need to compute x; this works in two stages:
2127    // 1) write m = p1^e1 * ... * pk^ek (we already have that),
2128    // 2) for each i in {1, 2, ..., k}
2129    //    2.1) compute a yi such that yi^2 = r mod pi,
2130    //    2.2) lift yi to an xi such that xi^2 = r mod (pi^ei),
2131    // 3) lift (x1, x2, ..., xk) in Z/p1^e1 * ... * Z/pk^ek
2132    //    to x in Z/m via Chinese remainder theorem
2133
2134    list roots;
2135    // 2.1):
2136    for (i = 1; i <= size(L[1]); i++)
2137    {
2138      roots = insert(roots, rootModP(aMod(r,L[1][i]), L[1][i]), size(roots));
2139    }
2140
2141    // 2.2):
2142    bigint c; bigint l; bigint temp; bigint pPower; int e;
2143    for (i = 1; i <= size(roots); i++)
2144    {
2145      pPower = bigint(L[1][i]);
2146      for (e = 2; e <= L[2][i]; e++)
2147      {
2148        c = bigint(roots[i]); l = pPower;
2149        temp = r - c * c; l = bigint(2) * c * l; c = temp;
2150        c = aDiv(c,pPower); l = aDiv(l,pPower);
2151        c = aMod(c,L[1][i]); l = aMod(l,L[1][i]);
2152        c = aMod((c * bigint(inverseModP(l, L[1][i]))), L[1][i]);
2153        c = bigint(roots[i]) + c * pPower;
2154        pPower = pPower * L[1][i]; roots[i] = c;
2155      }
2156    }
2157
2158    // 2.3):
2159    list mm; bigint z; int j;
2160    for (i = 1; i <= size(L[1]); i++)
2161    {
2162      z = bigint(L[1][i]);
2163      for (j = 2; j <= L[2][i]; j++)
2164      {
2165        z = z * bigint(L[1][i]);
2166      }
2167      mm = insert(mm, z, size(mm));
2168    }
2169    return (aMod(chinrem(roots, mm) , m));
2170  }
2171}
2172
2173
2174///////////////////////////////////////////////////////////////////////////////
2175static proc chineseRemainder(list rr, list mm)
2176"USAGE:  chineseRemainder(rr, mm); rr, mm lists of bigint's
2177ASSUME:  lists rr and mm must have same sizes;
2178         Furthermore the entries of mm must be mutually coprime.
2179RETURN:  an x which fulfills the simultaneous remainder conditions
2180         x = rr[i] mod mm[i], 1 <= i <= size(rr)
2181KEYWORDS: Chinese remainder.
2182"
2183{
2184  bigint x = bigint(0); int i; bigint N; list l;
2185  bigint M = bigint(mm[1]);
2186  for (i = 2; i <= size(mm); i++) { M = M * bigint(mm[i]); }
2187  for (i = 1; i <= size(mm); i++)
2188  {
2189    N = aDiv(M,mm[i]);
2190    l = extgcd(mm[i], N);
2191    x = x + rr[i]*l[3]*N;
2192  }
2193  return (x);
2194}
2195
2196
2197///////////////////////////////////////////////////////////////////////////////
2198static proc rationalPointSpecial(bigint b1, bigint c1)
2199"USAGE:  rationalPointSpecial(b1, c1); b1, c1 bigint's
2200ASSUME:  b1 <> 0 and c1 <> 0;
2201RETURN:  with poly p = var(1)^2 + b1 * var(2)^2 + c1 * var(3)^2, the method
2202         returns a list L with either one entry or four entries:
2203         case 'three entries':
2204           L[1] = 0 signaling that there is no rational point on V(p),
2205           L[2] the largest number b such that b^2 divides b1
2206                (for subsequent use by the caller of this method),
2207           L[3] the largest number c such that c^2 divides c1
2208                (for subsequent use by the caller of this method);
2209         case 'four entries':
2210           L[1] = 1 signaling that there is a rational point on V(p),
2211           L[2], L[3], L[4] rational numbers such that the tuple
2212                (L[2], L[3], L[4]) is on V(p)
2213"
2214{
2215  if (b1 == 0) { "ERROR: rationalPointSpecial(0, c1) had been invoked"; }
2216  if (c1 == 0) { "ERROR: rationalPointSpecial(b1, 0) had been invoked"; }
2217
2218  bigint b_s = largestSquare(b1); bigint b_r = b1/b_s/b_s;
2219  bigint c_s = largestSquare(c1); bigint c_r = c1/c_s/c_s;
2220  bigint g = gcd(b_r, c_r);
2221  def S=basering;
2222  ideal mi = maxideal(1);
2223  map mm = basering, mi; map mTemp;
2224  mm[1] = var(1); mm[2] = var(2)/b_s/g; mm[3] = var(3)/c_s/g;
2225  bigint a = g;     bigint aa = a; if (aa <= 0) { aa = -aa; }
2226  bigint b = b_r/g; bigint bb = b; if (bb <= 0) { bb = -bb; }
2227  bigint c = c_r/g; bigint cc = c; if (cc <= 0) { cc = -cc; }
2228  bigint R1 = squareRoot(-a*b, cc, 1);
2229  if (R1 == -1) { list L = 0, b_s, c_s; return (L); }
2230  bigint R2 = squareRoot(-a*c, bb, 1);
2231  if (R2 == -1) { list L = 0, b_s, c_s; return (L); }
2232  bigint R3 = squareRoot(-b*c, aa, 1);
2233  if (R3 == -1) { list L = 0, b_s, c_s; return (L); }
2234  bigint t; bigint r1; bigint Q; bigint A; bigint B; bigint C;
2235  bigint alpha; bigint beta; bigint gamma;
2236  while (jIndex(a, b, c) > 1)
2237  {
2238    mTemp = basering, mi;
2239    if (aa > cc)
2240    {
2241      t = a; a = c; c = t;
2242      t = aa; aa = cc; cc = t;
2243      mTemp = basering, mi;
2244      mTemp[1] = var(3); mTemp[3] = var(1); mm = mTemp(mm);
2245    }
2246    if (bb > cc)
2247    {
2248      t = b; b = c; c = t;
2249      t = bb; bb = cc; cc = t;
2250      mTemp = basering, mi;
2251      mTemp[2] = var(3); mTemp[3] = var(2); mm = mTemp(mm);
2252    }
2253    if (bb < aa)
2254    {
2255      t = b; b = a; a = t;
2256      t = bb; bb = aa; aa = t;
2257      mTemp = basering, mi;
2258      mTemp[1] = var(2); mTemp[2] = var(1); mm = mTemp(mm);
2259    }
2260    /* now, we have established |a| <= |b| <= |c|; and permuted
2261       the map mm, accordingly */
2262    cc = c; if (cc <= 0) { cc = -cc; }
2263    R1 = squareRoot(-a*b, cc, 0);
2264    r1 = aMod((R1 * inverseModP(a, cc)), cc);
2265    if (r1*bigint(2) > cc) { r1 = r1 - cc; }
2266    Q = (a*r1*r1 + b)/c;
2267    if (Q == 0)
2268    {
2269      list L = 1, subst(mm[1], var(1), 1, var(2), 1, var(3), 0),
2270                  subst(mm[2], var(1), 1, var(2), 1, var(3), 0),
2271                  subst(mm[3], var(1), 1, var(2), 1, var(3), 0);
2272      return (L);
2273    }
2274    A = gcd(gcd(a*r1*r1, b), c*Q);
2275    alpha = r1/A; beta = b/A;
2276    B = a*beta;
2277    gamma = largestSquare(Q/A);
2278    C = Q/A/gamma/gamma;
2279    mTemp = basering, mi;
2280    mTemp[1] = A*alpha*var(1) - beta*var(2);
2281    mTemp[2] = var(1) + a*alpha*var(2);
2282    mTemp[3] = C*gamma*var(3);
2283    mm = mTemp(mm);
2284    a = A; b = B; c = C;
2285    aa = a; if (aa <= 0) { aa = -aa; }
2286    bb = b; if (bb <= 0) { bb = -bb; }
2287    cc = c; if (cc <= 0) { cc = -cc; }
2288  }
2289  if (a*b < 0)
2290  {
2291    list L = 1, subst(mm[1], var(1), 1, var(2), 1, var(3), 0),
2292                subst(mm[2], var(1), 1, var(2), 1, var(3), 0),
2293                subst(mm[3], var(1), 1, var(2), 1, var(3), 0);
2294    return (L);
2295  }
2296  if (a*c < 0)
2297  {
2298    list L = 1, subst(mm[1], var(1), 1, var(2), 0, var(3), 1),
2299                subst(mm[2], var(1), 1, var(2), 0, var(3), 1),
2300                subst(mm[3], var(1), 1, var(2), 0, var(3), 1);
2301    return (L);
2302  }
2303  if (b*c < 0)
2304  {
2305    list L = 1, subst(mm[1], var(1), 0, var(2), 1, var(3), 1),
2306                subst(mm[2], var(1), 0, var(2), 1, var(3), 1),
2307                subst(mm[3], var(1), 0, var(2), 1, var(3), 1);
2308    return (L);
2309  }
2310  list L = 0, b_s, c_s; return (L);
2311}
2312
2313
2314///////////////////////////////////////////////////////////////////////////////
2315static proc extendedEuclid(bigint a, bigint b)
2316"USAGE:  extendedEuclid(a, b); a, b bigint's
2317ASSUME:  a <> 0 or b <> 0;
2318RETURN:  returns a list with three entries:
2319         _[1]: gcd(a,b) > 0,
2320         _[2], _[3]: s, t, such that s*a + t*b = gcd(a,b)
2321KEYWORDS: extended Euclidean algorithm.
2322"
2323{
2324  list l = 0; bigint temp;
2325  if (a == 0)         { l = b, 0, 1; if (b < 0) { l = -b, 0, -1; } }
2326  if (b == 0)         { l = a, 1, 0; if (a < 0) { l = -a, -1, 0; } }
2327  if (aMod(a , b) == 0) { l = b, 0, 1; if (b < 0) { l = -b, 0, -1; } }
2328  if (aMod(b , a) == 0) { l = a, 1, 0; if (a < 0) { l = -a, -1, 0; } }
2329  if (size(l) > 1) { return (l); }
2330
2331  temp = aMod(a , b);
2332  l = extendedEuclid(b, temp);
2333  temp = (a - temp) / b;
2334  temp = bigint(l[2]) - temp * bigint(l[3]);
2335  l = l[1], l[3], temp;
2336  return (l);
2337}
2338
2339static proc legendreSymbol(bigint r, bigint p)
2340"assumes p prime;
2341returns the Legendre symbol (r/p), that is
2342 1 if r appears as residue modulo p of a square,
2343-1 if not,
2344 0 if r is a multiple of p
2345"
2346{
2347  bigint rr = aMod(r , p);
2348  if (rr == 0) { return (0) }
2349  if (rr == 1) { return (1) }
2350  /* now, p must be at least 3 */
2351  bigint e = (p - 1) / bigint(2);
2352  bigint result = 1;
2353  bigint power = rr;
2354  while (e > 0)
2355  {
2356    if ((e mod 2) == 1) { result = aMod((result * power), p); }
2357    e = e / bigint(2);
2358    power = aMod((power * power), p);
2359  }
2360  if (result > 1) { result = result - p; /* should be -1 */ }
2361  return (result);
2362}
2363
2364
2365///////////////////////////////////////////////////////////////////////////////
2366static proc buildExtension(bigint b, bigint c, bigint bs, bigint cs)
2367"USAGE:  buildExtension(b, c, bs, cs); b, c, bs, cs bigint's
2368ASSUME:  assumes that bs is the largest positive number such that bs^2
2369         divides b; analogously for cs regarding c;
2370         Assumes furthermore that there is no rational point on the conic
2371         X^2 + b*Y^2 + c*Z^2 = 0.
2372         Assumes that the ground field of the basering is Q.
2373RETURN:  builds an appropriate quadratic field extension Q(a) in which a
2374         point exists that lies on the given conic. This point is stored in
2375         a newly defined and exported (1x3) matrix named 'point'.
2376         The method returns the resulting polynomial ring over Q(a).
2377"
2378{
2379  bigint br = b/bs/bs;
2380  bigint cr = c/cs/cs;
2381  /* X^2 + br*bs^2*Y^2 + cr*cs^2*Z^2 = 0 */
2382  def bRing = basering;
2383  list L = ringlist(bRing);
2384
2385  if (b != 0)
2386  {
2387    L[1] = list(0, list("a"), list(list("lp", 1)), ideal(0));
2388    def RTemp = ring(L);
2389    setring RTemp; list L = ringlist(RTemp);
2390    L[1][4] = ideal(a^2 + br);
2391    def R = ring(L);
2392    setring R; kill RTemp;
2393    matrix point[1][3];
2394    point[1, 1] = a * bs; point[1, 2] = 1; point[1, 3] = 0;
2395    export point;
2396    setring bRing;
2397    return (R);
2398  }
2399  if (c != 0)
2400  {
2401    L[1] = list(0, list("a"), list(list("lp", 1)), ideal(0));
2402    def RTemp = ring(L);
2403    setring RTemp; list L = ringlist(RTemp);
2404    L[1][4] = ideal(a^2 + cr);
2405    def R = ring(L);
2406    setring R; kill RTemp;
2407    matrix point[1][3];
2408    point[1, 1] = a * cs; point[1, 2] = 0; point[1, 3] = 1;
2409    export point;
2410    setring bRing;
2411    return (R);
2412  }
2413
2414  "ERROR: unexpectedly encountered conic X^2 + 0*Y^2 + 0*Z^2 = 0";
2415  return (bRing);
2416}
2417
2418
2419///////////////////////////////////////////////////////////////////////////////
2420static proc testRationalPointConic(poly pp)
2421"USAGE:  testRationalPointConic(pp); pp poly
2422RETURN:  returns 0 in case of unexpected input (e.g. non-quadratic,
2423         reducible); 1 otherwise
2424NOTE:    This method calls rationalPointConic, measures time consumption
2425         and checks whether the computed point lies indeed on the conic pp.
2426         The results will be printed to standard output.
2427"
2428{
2429  "testing rationalPointConic(poly) for poly p:";
2430  "p =", pp;
2431  if (isQuadratic(pp)[1] == 1) { "p is quadratic."; }
2432  else                         { "p is not quadratic.";   return (0); }
2433  if (isIrreducible(pp) == 1)  { "p is irreducible."; }
2434  else                         { "p is not irreducible."; return (0); }
2435  def rOrig = basering;
2436  int t = rtimer;
2437  def rNew = rationalPointConic(pp);
2438  t = rtimer - t;
2439  "time for finding a point on the conic [sec] =", t;
2440  setring rNew;
2441  poly ff = fetch(rOrig, pp);
2442  if (minpoly == 0)
2443  { "there is a rational point on the conic p";
2444    "x =", point[1,1], "  y =", point[1,2], "  z =", point[1,3];
2445    "check (should be zero):", subst(ff, var(1), point[1,1],
2446                                         var(2), point[1,2],
2447                                         var(3), point[1,3]);
2448  }
2449  else
2450  {
2451    "there is no rational point on the conic p";
2452    "but there is a point on the conic in the field extension Q(a),";
2453    "with minpoly =", minpoly;
2454    "x =", point[1,1], "  y =", point[1,2], "  z =", point[1,3];
2455    "check (should be zero):", subst(ff, var(1), point[1,1],
2456                                         var(2), point[1,2],
2457                                         var(3), point[1,3]);
2458  }
2459  setring rOrig;
2460}
2461
2462example
2463{ "EXAMPLE:"; echo=2;
2464  ring r = 0, (x,y,z, u, v, w), dp;
2465  poly p = x^2 + 2*y^2 + 5*z^2 - 4*x*y + 3*x*z + 17*y*z;
2466  testRationalPointConic(p);
2467}
2468
2469///////////////////////////////////////////////////////////////////////////////
2470proc rationalPointConic(poly p)
2471"USAGE:  rationalPointConic(p); p poly
2472ASSUME:  assumes that p is an irreducible quadratic polynomial in the first
2473         three ring variables;
2474         ground field is expected to be Q.
2475RETURN:  The method finds a point on the given conic. There are two
2476         possibilities:
2477         1) There is a rational point on the curve.
2478         2) There is no rational point on the curve.
2479         In the second case, the method creates a modification of the current
2480         basering which is a polynomial ring over some quadratic field
2481         extension Q(a) of Q. Apart from the replacement of Q by Q(a), the
2482         new polynomial ring, R say, is the same as the original basering.
2483         (In the first case, R is identical with the basering.)
2484         In both cases, the method will then define a (1x3) matrix named
2485         'point' which lives in R and which contains the coordinates of the
2486         desired point on q.
2487         Finally, the method returns the ring R (which will in the 1st case
2488         be the original base ring).
2489EXAMPLE: example rationalPointConic; shows an example
2490"
2491{
2492  list L = isQuadratic(p);
2493  bigint a = bigint(L[2]); bigint b = bigint(L[3]); bigint c = bigint(L[4]);
2494  bigint d = bigint(L[5]); bigint e = bigint(L[6]); bigint f = bigint(L[7]);
2495  bigint x; bigint y; bigint z; bigint nn;
2496  def R = basering;
2497
2498  if (b^2 == 4*a*c)
2499  {
2500    if (c == 0)
2501    {
2502      x = -2*d*e; y = d^2-4*a*f; z = e*4*a;
2503      nn = gcd(gcd(absValue(x), absValue(y)), absValue(z));
2504      matrix point[1][3];
2505      point[1, 1] = x/nn; point[1, 2] = y/nn; point[1, 3] = z/nn;
2506      export point; return (R);
2507    }
2508    else
2509    {
2510      bigint fs = 4*c*f - e^2;
2511      bigint ds = 4*c*d - 2*b*e;
2512      x = -fs*2*c; y = b*fs-e*ds; z = ds*2*c;
2513      nn = gcd(gcd(absValue(x), absValue(y)), absValue(z));
2514      matrix point[1][3];
2515      point[1, 1] = x/nn; point[1, 2] = y/nn; point[1, 3] = z/nn;
2516      export point; return (R);
2517    }
2518  }
2519
2520  if (d^2 == 4*a*f)
2521  {
2522    if (f == 0)
2523    {
2524      x = -b*e*2; y = e*4*a; z = b^2-4*a*c;
2525      nn = gcd(gcd(absValue(x), absValue(y)), absValue(z));
2526      matrix point[1][3];
2527      point[1, 1] = x/nn; point[1, 2] = y/nn; point[1, 3] = z/nn;
2528      export point; return (R);
2529    }
2530    else
2531    {
2532      bigint c_s = 4*c*f - e^2;
2533      bigint b_s = 4*f*b - 2*d*e;
2534      x = -c_s*2*f; y = b_s*2*f; z = d*c_s-e*b_s;
2535      nn = gcd(gcd(absValue(x), absValue(y)), absValue(z));
2536      matrix point[1][3];
2537      point[1, 1] = x/nn; point[1, 2] = y/nn; point[1, 3] = z/nn;
2538      export point; return (R);
2539    }
2540  }
2541
2542  if (e^2 == 4*c*f)
2543  {
2544    if (c == 0)
2545    {
2546      x = b*4*f; y = d^2-4*a*f; z = -b*d*2;
2547      nn = gcd(gcd(absValue(x), absValue(y)), absValue(z));
2548      matrix point[1][3];
2549      point[1, 1] = x/nn; point[1, 2] = y/nn; point[1, 3] = z/nn;
2550      export point; return (R);
2551    }
2552    else
2553    {
2554      bigint as = 4*c*a - b^2;
2555      bigint ds = 4*c*d - 2*b*e;
2556      x = ds*2*c; y = e*as-b*ds; z = -as*2*c;
2557      nn = gcd(gcd(absValue(x), absValue(y)), absValue(z));
2558      matrix point[1][3];
2559      point[1, 1] = x/nn; point[1, 2] = y/nn; point[1, 3] = z/nn;
2560      export point; return (R);
2561    }
2562  }
2563
2564  ideal mi = maxideal(1);
2565  map mm = R, mi;
2566  bigint B; bigint C; bigint D;
2567
2568  if ((a == 0) && (c == 0))
2569  {
2570    B = -1; C = 4*b*f - 4*d*e;
2571    /* now, b <> 0 since otherwise p would have the factor z,
2572       and hence not be irreducible */
2573    mm[1] = (var(1)+var(2)-2*e*var(3))/(2*b);
2574    mm[2] = (var(1)-var(2)-2*d*var(3))/(2*b);
2575  }
2576  if ((a != 0) && (c == 0))
2577  {
2578    mm[1] = var(2);
2579    mm[2] = var(1);
2580    bigint t = a; a = c; c = t;
2581    t = e; e = d; d = t;
2582  }
2583  if (c != 0)
2584  {
2585    D = 4*a*c-b^2;
2586    mm[2] = (var(2)-e*var(3)-b*var(1))/(2*c);
2587    map mTemp = basering, mi;
2588    mTemp[1] = (var(1)-2*d*c*var(3)+b*e*var(3))/D;
2589    mm = mTemp(mm);
2590    B = D;
2591    C = 16*a*c^2*f-4*a*c*e^2-4*b^2*c*f+4*b*c*d*e-4*c^2*d^2;
2592  }
2593  list K;
2594  if ((B > 0) && (C >= 0)) { K = 0; }
2595  if ((B >= 0) && (C > 0)) { K = 0; }
2596  if (B == 0)
2597  {
2598    /* looking for a point on X^2 = |C| * Z^2 */
2599    bigint root = largestSquare(absValue(C));
2600    if (absValue(C)/root/root == 1) { K = 1, root, 0, 1; }
2601    else                            { K = 0; }
2602  }
2603  if (C == 0)
2604  {
2605    /* looking for a point on X^2 = |B| * Y^2 */
2606    bigint root = largestSquare(absValue(B));
2607    if (absValue(B)/root/root == 1) { K = 1, root, 1, 0; }
2608    else                            { K = 0; }
2609  }
2610  else { K = rationalPointSpecial(B, C); }
2611  if (K[1] == 0)
2612  {
2613    /* no rational point on conic;
2614       we need to move to an appropriate field extension Q(a) */
2615    poly h1 = mm[1]; poly h2 = mm[2]; poly h3 = mm[3];
2616    def extendedR = buildExtension(B, C, K[2], K[3]);
2617    setring extendedR;
2618    poly g1 = fetch(R, h1);
2619    poly g2 = fetch(R, h2);
2620    poly g3 = fetch(R, h3);
2621    matrix temp[1][3];
2622    temp[1, 1] = subst(g1, var(1), point[1, 1], var(2), point[1, 2],
2623                           var(3), point[1, 3]);
2624    temp[1, 2] = subst(g2, var(1), point[1, 1], var(2), point[1, 2],
2625                           var(3), point[1, 3]);
2626    temp[1, 3] = subst(g3, var(1), point[1, 1], var(2), point[1, 2],
2627                           var(3), point[1, 3]);
2628    point[1, 1] = temp[1, 1]; point[1, 2] = temp[1, 2];
2629    point[1, 3] = temp[1, 3];
2630    setring R;
2631    return (extendedR);
2632  }
2633  else
2634  {
2635    string dummyString = string(K); // without this useless line, we
2636                                    // sometimes get a seg fault because
2637                                    // mm is corrupted; strange!?!?!?!?
2638    number nx = number(subst(mm[1], var(1), K[2], var(2), K[3], var(3), K[4]));
2639    number ny = number(subst(mm[2], var(1), K[2], var(2), K[3], var(3), K[4]));
2640    number nz = number(subst(mm[3], var(1), K[2], var(2), K[3], var(3), K[4]));
2641    /* the point (nx, ny, nz) is already a solution;
2642       the following lines will just remove denominators and reduce
2643       numerators in order to return a nice tuple from Z^3 */
2644    bigint nxd = bigint(denominator(absValue(nx)));
2645    bigint nyd = bigint(denominator(absValue(ny)));
2646    bigint nzd = bigint(denominator(absValue(nz)));
2647    nn = nxd * nyd / gcd(nxd, nyd);
2648    nn =  nn * nzd / gcd(nn, nzd);
2649    x = bigint(nx*nn); y = bigint(ny*nn); z = bigint(nz*nn);
2650    nn = gcd(gcd(absValue(x), absValue(y)), absValue(z));
2651    matrix point[1][3];
2652    point[1, 1] = x/nn; point[1, 2] = y/nn; point[1, 3] = z/nn;
2653    export point;
2654    return (R);
2655  }
2656}
2657
2658example
2659{ "EXAMPLE:"; echo=2;
2660ring R = 0, (x,y,z), dp;
2661system("random", 4711);
2662poly p = x^2 + 2*y^2 + 5*z^2 - 4*x*y + 3*x*z + 17*y*z;
2663def S = rationalPointConic(p); // quadratic field extension,
2664                               // minpoly = a^2 - 2
2665testPointConic(p, S);
2666setring R;
2667p = x^2 - 1857669520 * y^2 + 86709575222179747132487270400 * z^2;
2668S = rationalPointConic(p); // same as current basering,
2669                           // no extension needed
2670testPointConic(p, S);
2671}
2672///////////////////////////////////////////////////////////////////////////////
2673proc testParametrization(poly f, def rTT)
2674"USAGE:  testParametrization(f, rTT); f poly, rTT ring
2675ASSUME:  The assumptions on the basering and the polynomial f are as required
2676         by @ref{paraPlaneCurve}. The ring rTT has two variables and contains
2677         an ideal PARA (such as the ring obtained by applying
2678         @ref{paraPlaneCurve} to f).
2679RETURN: int which is 1 if PARA defines a parametrization of the curve
2680        {f=0} and 0, otherwise.
2681THEORY: We compute the polynomial defining the image of PARA
2682        and compare it with f.
2683KEYWORDS: Parametrization, image.
2684EXAMPLE: example testParametrization; shows an example
2685"
2686{
2687  def Roriginal = basering;
2688  setring rTT;
2689  /* begin workaround elimination*/
2690  int k;
2691  list rl = ringlist(rTT);
2692  rl[2] = list("s","t","x","y","z");
2693  rl[3]= list(list("dp",1:5),list("C",0));
2694  def Relim = ring(rl);
2695  setring Relim;
2696  ideal PARA = fetch(rTT,PARA);
2697  ideal JJ;
2698  for(k=1;k<=3;k++)
2699     {
2700       JJ=JJ,var(k+2)-PARA[k];
2701     }
2702  ideal SJJ = std(JJ);
2703  intvec HJJ = hilb(SJJ,1);
2704  ideal J = eliminate(JJ,var(1)*var(2),HJJ);
2705  setring rTT;
2706  /*end workaround elimination*/
2707  rl[2] = list("x","y","z");
2708  rl[3] = list(list("dp",1:3),list("C",0));
2709  def RP2 = ring(rl);
2710  setring RP2;
2711  ideal f = fetch(Roriginal,f);
2712  ideal ftest = imap(Relim,J);
2713  poly g = reduce(f[1],std(ftest));
2714  if(g!=0){return(0)}
2715  g = reduce(ftest[1],std(ideal(f)));
2716  if(g!=0){return(0)}
2717  return (1);
2718}
2719
2720example
2721{ "EXAMPLE:"; echo=2;
2722  ring R = 0,(x,y,z),dp;
2723  poly f = y^8-x^3*(z+x)^5;
2724  def RP1 = paraPlaneCurve(f);
2725  testParametrization(f, RP1);
2726}
2727
2728///////////////////////////////////////////////////////////////////////////////
2729proc testPointConic(poly p, def r)
2730"USAGE:  testPointConic(p, r); p poly, r ring
2731ASSUME:  assumes that p is a homogeneous quadratic polynomial in the
2732        first three ring variables of the current basering;
2733        Assumes that there is a (1x3) matrix named 'point' in r with
2734        entries from the ground field of r.
2735RETURN:  returns 1 iff the point named 'point', residing in r, lies on
2736        the conic given by p; 0 otherwise
2737NOTE:    This method temporarily changes the basering to r. Afterwards,
2738        the basering will be the same as before.
2739EXAMPLE: example testPointConic; shows an example
2740"
2741{
2742 def rOrig = basering;
2743 "conic:", p;
2744 setring r;
2745 string s = "point: " + string(point[1,1]) + ", " + string(point[1,2]);
2746 s = s + ", " + string(point[1,3]);
2747 s;
2748 if (minpoly != 0) { "minpoly:", minpoly; }
2749 poly f = fetch(rOrig, p);
2750 poly g = subst(f, var(1), point[1,1],
2751                   var(2), point[1,2],
2752                   var(3), point[1,3]);
2753 int result = 0; if (g == 0) { result = 1; }
2754 setring rOrig;
2755 return (result);
2756}
2757
2758example
2759{ "EXAMPLE:"; echo=2;
2760 ring R = 0, (x,y,z), dp;
2761 system("random", 4711);
2762 poly p = x^2 + 2*y^2 + 5*z^2 - 4*x*y + 3*x*z + 17*y*z;
2763 def S = rationalPointConic(p);
2764 if (testPointConic(p, S) == 1)
2765 { "point lies on conic"; }
2766 else
2767 { "point does not lie on conic"; }
2768}
2769
2770/////////////////////////////////////////////////////////////////////////////
2771/////////////////////////////////////////////////////////////////////////////
2772/////////////////////////////////////////////////////////////////////////////
2773/*
2774/////////////////////////////////////////////////////////////////////////////
2775/// Further examples for testing the main procedures
2776/// Timings on wawa Sept 29
2777/////////////////////////////////////////////////////////////////////////////
2778LIB"paraplanecurves.lib";
2779// -------------------------------------------------------
2780// Example 1
2781// -------------------------------------------------------
2782ring RR = 0, (x,y,z), dp;
2783poly f = 7*z2+11*y2+13*z*y+17*x2+19*x*y; // conic
2784def RP1 = paraConic(f);
2785setring RP1; PARACONIC;
2786setring RR;
2787RP1 = paraPlaneCurve(f);
2788testParametrization(f,RP1);
2789setring RP1; PARA;
2790kill RR;kill RP1;
2791// -------------------------------------------------------
2792// Example 2
2793// -------------------------------------------------------
2794ring RR = 0, (x,y,z), dp;
2795poly f = y3-x2z;  // cusp at origin
2796adjointIdeal(f,1);
2797adjointIdeal(f,2);
2798def RP1 = paraPlaneCurve(f);  // time 0
2799testParametrization(f,RP1);
2800setring RP1; PARA;
2801kill RR;kill RP1;
2802// -------------------------------------------------------
2803// Example 3
2804// -------------------------------------------------------
2805ring RR = 0, (x,y,z), dp;
2806poly f=(xz-y^2)^2-x*y^3; // 1 sing at origin, 1 cusp, no OMPs
2807adjointIdeal(f,1);
2808adjointIdeal(f,2);
2809def RP1 = paraPlaneCurve(f); // time 0
2810testParametrization(f,RP1);
2811setring RP1; PARA;
2812kill RR;kill RP1;
2813// -------------------------------------------------------
2814// Example 4
2815// -------------------------------------------------------
2816ring RR = 0, (x,y,z), dp;
2817poly f = y5-y4x+4y2x2z-x4z;  // 1 sing at origin, no OMPs, no cusps
2818adjointIdeal(f,1);
2819adjointIdeal(f,2);
2820def RP1 = paraPlaneCurve(f);  // time 0
2821testParametrization(f,RP1);
2822setring RP1; PARA;
2823kill RR;kill RP1;
2824// -------------------------------------------------------
2825// Example 5
2826// -------------------------------------------------------
2827ring RR = 0, (x,y,z), dp;
2828poly f = 259x5-31913x4y+939551x3y2+2871542x2y3+2845801xy4;
2829f = f+914489y5+32068x4z-1884547x3yz-8472623x2y2z-11118524xy3z;
2830f = f-4589347y4z+944585x3z2+8563304x2yz2+16549772xy2z2+9033035y3z2;
2831f = f-2962425x2z3-11214315xyz3-8951744y2z3+2937420xz4+4547571yz4-953955z5;
2832// 6 nodes
2833adjointIdeal(f,1);
2834adjointIdeal(f,2);
2835def RP1 = paraPlaneCurve(f);  // time 0
2836testParametrization(f,RP1);
2837setring RP1; PARA;
2838kill RR;kill RP1;
2839// -------------------------------------------------------
2840// Example 7
2841// -------------------------------------------------------
2842ring RR = 0, (x,y,z), dp;
2843poly f = y^8-x^3*(z+x)^5;  // 1 sing at origin, 1 further sing, no OMPs,
2844                           // no cusps
2845adjointIdeal(f,1);
2846adjointIdeal(f,2);
2847def RP1 = paraPlaneCurve(f);  // time 0
2848testParametrization(f,RP1);
2849setring RP1; PARA;
2850kill RR;kill RP1;
2851// -------------------------------------------------------
2852// Example 8
2853// -------------------------------------------------------
2854ring RR = 0, (x,y,z), dp;
2855poly f = 11y7+7y6x+8y5x2-3y4x3-10y3x4-10y2x5-x7-33y6-29y5x-13y4x2+26y3x3;
2856f = f+30y2x4+10yx5+3x6+33y5+37y4x-8y3x2-33y2x3-20yx4-3x5-11y4-15y3x;
2857f = f+13y2x2+10yx3+x4; // 3 OMPs of mult 3, 1 OMP of mult 4
2858f = homog(f,z);
2859adjointIdeal(f,1);
2860adjointIdeal(f,2);
2861def RP1 = paraPlaneCurve(f);  // time 0
2862testParametrization(f,RP1);
2863setring RP1; PARA;
2864kill RR;kill RP1;
2865// -------------------------------------------------------
2866// Example 9
2867// -------------------------------------------------------
2868ring RR = 0, (x,y,z), dp;
2869poly f = y^8-x^3*(z+x)^5;  // 1 sing at origin, 1 further sing, no OMPs,
2870                           // no cusps
2871adjointIdeal(f,1);
2872adjointIdeal(f,2);
2873def RP1 = paraPlaneCurve(f);  // time 0
2874testParametrization(f,RP1);
2875setring RP1; PARA;
2876kill RR;kill RP1;
2877// -------------------------------------------------------
2878// Example 10
2879// -------------------------------------------------------
2880ring SS = 0, (u,v,z), dp;
2881poly f = u^4-14*u^2*v^2+v^4+8*u^2*v*z+8*v^3*z; // 1 OMP of mult 3 at origin
2882adjointIdeal(f,1);
2883adjointIdeal(f,2);
2884def RP1 = paraPlaneCurve(f);  // time 0
2885testParametrization(f,RP1);
2886setring RP1; PARA;
2887kill SS;kill RP1;
2888// -------------------------------------------------------
2889// Example 11
2890// -------------------------------------------------------
2891ring SS = 0, (u,v,z), dp;
2892poly f = 14440*u^5-16227*u^4*v+10812*u^3*v^2-13533*u^2*v^3+3610*u*v^4;
2893f = f+1805*v^5+14440*u^4*z-18032*u^3*v*z+16218*u^2*v^2*z-12626*u*v^3*z;
2894f = f+3610*v^4*z+3610*u^3*z^2-4508*u^2*v*z^2+5406*u*v^2*z^2-2703*v^3*z^2;
2895// 1 OMP of mult 3 at origin, 2 nodes
2896adjointIdeal(f,1);
2897adjointIdeal(f,2);
2898def RP1 = paraPlaneCurve(f);  // time 0
2899testParametrization(f,RP1);
2900setring RP1; PARA;
2901kill SS;kill RP1;
2902// -------------------------------------------------------
2903// Example 12
2904// -------------------------------------------------------
2905ring SS = 0, (u,v,z), dp;
2906poly f = u^6+3*u^4*v^2+3*u^2*v^4+v^6-4*u^4*z^2-34*u^3*v*z^2-7*u^2*v^2*z^2;
2907f = f+12*u*v^3*z^2+6*v^4*z^2+36*u^2*z^4+36*u*v*z^4+9*v^2*z^4;
2908// needs field extension *** 6 nodes, 2 cusps, 1 sing at 0
2909adjointIdeal(f,1);
2910adjointIdeal(f,2);
2911def RP1 = paraPlaneCurve(f);  // time 0
2912testParametrization(f,RP1);
2913setring RP1; PARA;
2914kill SS;kill RP1;
2915// -------------------------------------------------------
2916// Example 13
2917// -------------------------------------------------------
2918ring SS = 0, (u,v,z), dp;
2919poly f = -24135/322*u^6-532037/6440*u^5*v+139459/560*u^4*v^2;
2920f = f-1464887/12880*u^3*v^3+72187/25760*u^2*v^4+9/8*u*v^5+1/8*v^6;
2921f = f-403511/3220*u^5*z-40817/920*u^4*v*z+10059/80*u^3*v^2*z;
2922f = f-35445/1288*u^2*v^3*z+19/4*u*v^4*z+3/4*v^5*z-20743/805*u^4*z^2;
2923f = f+126379/3220*u^3*v*z^2-423417/6440*u^2*v^2*z^2+11/2*u*v^3*z^2;
2924f = f+3/2*v^4*z^2+3443/140*u^3*z^3+u^2*v*z^3+u*v^2*z^3+v^3*z^3;
2925// 2 OMPs of mult 3 (1 at origin), 4 nodes
2926adjointIdeal(f,1);
2927adjointIdeal(f,2);
2928def RP1 = paraPlaneCurve(f);  // time 14
2929testParametrization(f,RP1);
2930setring RP1; PARA;
2931kill SS;kill RP1;
2932// -------------------------------------------------------
2933// Example 14
2934// -------------------------------------------------------
2935ring SS = 0, (u,v,z), dp;
2936poly f =
29372*u^7+u^6*v+3*u^5*v^2+u^4*v^3+2*u^3*v^4+u^2*v^5+2*u*v^6+v^7
2938-7780247/995328*u^6*z-78641/9216*u^5*v*z-10892131/995328*u^4*v^2*z
2939-329821/31104*u^3*v^3*z-953807/331776*u^2*v^4*z-712429/248832*u*v^5*z
2940+1537741/331776*v^6*z+2340431/248832*u^5*z^2+5154337/248832*u^4*v*z^2
2941+658981/41472*u^3*v^2*z^2+1737757/124416*u^2*v^3*z^2
2942-1234733/248832*u*v^4*z^2-1328329/82944*v^5*z^2-818747/248832*u^4*z^3
2943-1822879/124416*u^3*v*z^3-415337/31104*u^2*v^2*z^3
2944+1002655/124416*u*v^3*z^3+849025/82944*v^4*z^3;
2945// 3 OMPs of mult 3, 1 OMP of mult 4 at origin
2946adjointIdeal(f,2);
2947def RP1 = paraPlaneCurve(f);  // time 1
2948testParametrization(f,RP1);
2949setring RP1; PARA;
2950kill SS;kill RP1;
2951// -------------------------------------------------------
2952// Example 15
2953// -------------------------------------------------------
2954ring SS = 0, (u,v,z), dp;
2955poly f = 590819418867856650536224u7-147693905508217596067968u6v;
2956f = f+229117518934972047619978u5v2-174050799674982973889542u4v3;
2957f = f-92645796479789150855110u3v4-65477418713685583062704u2v5;
2958f = f+4529961835917468460168uv6+7715404057796585983136v7;
2959f = f-413640780091141905428104u6z+571836835577486968144618u5vz;
2960f = f-551807810327826605739444u4v2z-488556410340789283359926u3v3z;
2961f = f-473466023008413178155962u2v4z+48556741573432247323608uv5z;
2962f = f+77647371229172269259528v6z+340450118906560552282893u5z2;
2963f = f-433598825064368371610344u4vz2-937281070591684636591672u3v2z2;
2964f = f-1388949843915129934647751u2v3z2+204081793110898617103998uv4z2;
2965f = f+335789953068251652554308v5z2+6485661002496681852577u4z3;
2966f = f-772700266516318390630202u3vz3-2068348417248100329533330u2v2z3;
2967f = f+440320154612359641806108uv3z3+808932515589210854581618v4z3;
2968f = f-229384307132237615286548u3z4-1564303565658228216055227u2vz4;
2969f = f+520778334468674798322974uv2z4+1172483905704993294097655v3z4;
2970f = f-480789741398016816562100u2z5+322662751598958620410786uvz5;
2971f = f+1022525576391791616258310v2z5+82293493608853837667471uz6;
2972f = f+496839109904761426785889vz6+103766136235628614937587z7; // 15 nodes
2973adjointIdeal(f,2);
2974def RP1 = paraPlaneCurve(f);  // time 72
2975testParametrization(f,RP1);
2976setring RP1; PARA;
2977kill SS;kill RP1;
2978
2979// -------------------------------------------------------
2980// Example 16
2981// -------------------------------------------------------
2982ring SS = 0, (u,v,z), dp;
2983poly f = 25*u^8+184*u^7*v+518*u^6*v^2+720*u^5*v^3+576*u^4*v^4+282*u^3*v^5;
2984f = f+84*u^2*v^6+14*u*v^7+v^8+244*u^7*z+1326*u^6*v*z+2646*u^5*v^2*z;
2985f = f+2706*u^4*v^3*z+1590*u^3*v^4*z+546*u^2*v^5*z+102*u*v^6*z+8*v^7*z;
2986f = f+854*u^6*z^2+3252*u^5*v*z^2+4770*u^4*v^2*z^2+3582*u^3*v^3*z^2;
2987f = f+1476*u^2*v^4*z^2+318*u*v^5*z^2+28*v^6*z^2+1338*u^5*z^3+3740*u^4*v*z^3;
2988f = f+4030*u^3*v^2*z^3+2124*u^2*v^3*z^3+550*u*v^4*z^3+56*v^5*z^3+1101*u^4*z^4;
2989f = f+2264*u^3*v*z^4+1716*u^2*v^2*z^4+570*u*v^3*z^4+70*v^4*z^4+508*u^3*z^5;
2990f = f+738*u^2*v*z^5+354*u*v^2*z^5+56*v^3*z^5+132*u^2*z^6+122*u*v*z^6;
2991f = f+28*v^2*z^6+18*u*z^7+8*v*z^7+z^8; // 3 nodes, 1 sing
2992adjointIdeal(f,1);
2993adjointIdeal(f,2);
2994def RP1 = paraPlaneCurve(f);  // time 20
2995testParametrization(f,RP1);
2996setring RP1; PARA;
2997kill SS;kill RP1;
2998// -------------------------------------------------------
2999// Example 17
3000// -------------------------------------------------------
3001ring SS = 0, (u,v,z), dp;
3002poly f = -2*u*v^4*z^4+u^4*v^5+12*u^4*v^3*z^2+12*u^2*v^4*z^3-u^3*v*z^5;
3003f = f+11*u^3*v^2*z^4-21*u^3*v^3*z^3-4*u^4*v*z^4+2*u^4*v^2*z^3-6*u^4*v^4*z;
3004f = f+u^5*z^4-3*u^5*v^2*z^2+u^5*v^3*z-3*u*v^5*z^3-2*u^2*v^3*z^4+u^3*v^4*z^2;
3005f = f+v^5*z^4; // 2 OMPs of mult 4, 1 OMP of mult 5, 1 sing at origin
3006f = subst(f,z,u+v+z);
3007adjointIdeal(f,2);
3008def RP1 = paraPlaneCurve(f);  // time 5
3009testParametrization(f,RP1);
3010setring RP1; PARA;
3011kill SS;kill RP1;
3012// -------------------------------------------------------
3013// Example 18
3014// -------------------------------------------------------
3015ring SS = 0, (u,v,z), dp;
3016poly f = u^5*v^5+21*u^5*v^4*z-36*u^4*v^5*z-19*u^5*v^3*z^2+12*u^4*v^4*z^2;
3017f = f+57*u^3*v^5*z^2+u^5*v^2*z^3+u^4*v^3*z^3-53*u^3*v^4*z^3-19*u^2*v^5*z^3;
3018f = f+u^5*v*z^4+43*u^3*v^3*z^4+u*v^5*z^4+u^5*z^5-15*u^3*v^2*z^5+u^2*v^3*z^5;
3019f = f+u*v^4*z^5+v^5*z^5; // 1 OMP of mult 4, 3 OMPs of mult 5 (1 at origin)
3020adjointIdeal(f,2);
3021def RP1 = paraPlaneCurve(f);  // time 8
3022testParametrization(f,RP1);
3023setring RP1; PARA;
3024kill SS;kill RP1;
3025// -------------------------------------------------------
3026// Example 19
3027// -------------------------------------------------------
3028ring SS = 0, (u,v,z), dp;
3029poly f = u^10+6*u^9*v-30*u^7*v^3-15*u^6*v^4+u^5*v^5+u^4*v^6+6*u^3*v^7;
3030f = f+u^2*v^8+7*u*v^9+v^10+5*u^9*z+24*u^8*v*z-30*u^7*v^2*z-120*u^6*v^3*z;
3031f = f-43*u^5*v^4*z+5*u^4*v^5*z+20*u^3*v^6*z+10*u^2*v^7*z+29*u*v^8*z+5*v^9*z;
3032f = f+10*u^8*z^2+36*u^7*v*z^2-105*u^6*v^2*z^2-179*u^5*v^3*z^2-38*u^4*v^4*z^2;
3033f = f+25*u^3*v^5*z^2+25*u^2*v^6*z^2+46*u*v^7*z^2+10*v^8*z^2+10*u^7*z^3;
3034f = f+24*u^6*v*z^3-135*u^5*v^2*z^3-117*u^4*v^3*z^3-u^3*v^4*z^3+25*u^2*v^5*z^3;
3035f = f+34*u*v^6*z^3+10*v^7*z^3+5*u^6*z^4+6*u^5*v*z^4-75*u^4*v^2*z^4;
3036f = f-27*u^3*v^3*z^4+10*u^2*v^4*z^4+11*u*v^5*z^4+5*v^6*z^4+u^5*z^5;
3037f = f-15*u^3*v^2*z^5+u^2*v^3*z^5+u*v^4*z^5+v^5*z^5;
3038// 1 OMP of mult 4, 3 OMPs of mult 5 (1 at origin)
3039adjointIdeal(f,2);
3040def RP1 = paraPlaneCurve(f);  // time 2 // see Ex. 18
3041testParametrization(f,RP1);
3042setring RP1; PARA;
3043kill SS;kill RP1;
3044// -------------------------------------------------------
3045// Example 20
3046// -------------------------------------------------------
3047ring R = 0, (x,y,z), dp;
3048system("random", 4711);
3049poly p = x^2 + 2*y^2 + 5*z^2 - 4*x*y + 3*x*z + 17*y*z;
3050def S = rationalPointConic(p); // quadratic field extension,
3051                              // minpoly = a^2 - 2
3052if (testPointConic(p, S) == 1)
3053{ "point lies on conic"; }
3054else
3055{ "point does not lie on conic"; }
3056kill R;kill S;
3057// -------------------------------------------------------
3058// Example 21
3059// -------------------------------------------------------
3060ring R = 0, (x,y,z), dp;
3061system("random", 4711);
3062poly p = x^2 - 1857669520 * y^2 + 86709575222179747132487270400 * z^2;
3063def S = rationalPointConic(p); // same as current basering,
3064                              // no extension needed
3065if (testPointConic(p, S) == 1)
3066{ "point lies on conic"; }
3067else
3068{ "point does not lie on conic"; }
3069kill R;kill S;
3070// -------------------------------------------------------
3071// Example 21
3072// -------------------------------------------------------
3073ring RR = 0, (x,y,z), dp;
3074poly f = -1965466244509920x5y+34871245546721380061760x4y2;
3075f = f+104613747941595046117320x3y3+113331564241941002407560x2y4;
3076f = f+52306876673313609259800xy5+8717812860780028397880y6;
3077f = f+1040297748510024x5z+4468147845634872x4yz;
3078f = f-22398508728211453743258x3y2z-33223996581074443306854x2y3z;
3079f = f-10638598235041298082366xy4z+186886189971594356382y5z;
3080f = f-1385078844909312x4z2-34893092731637052532683x3yz2;
3081f = f-98591463214095439056609x2y2z2-92339459334829609336485xy3z2;
3082f = f-24923289542522905755711y4z2+472440640471377x3z3;
3083f = f+33821511925664516716011x2yz3+49745237303968344397437xy2z3;
3084f = f+11040465960074786720475y3z3+8728735735878837099404x2z4;
3085f = f+17676785754519678518537xyz4+17935885079051421934609y2z4;
3086f = f-11314701999743172607075xz5-16164284825803158969425yz5;
3087f = f+3666695988537425618750z6;
3088// 4 nodes, 1 OMP of mult 4
3089adjointIdeal(f,2);
3090kill RR;
3091*/
Note: See TracBrowser for help on using the repository browser.