source: git/Singular/LIB/grobcov.lib @ ede2ad8

fieker-DuValspielwiese
Last change on this file since ede2ad8 was 415851, checked in by Hans Schoenemann <hannes@…>, 9 years ago
new grobcov.lib
  • Property mode set to 100644
File size: 139.8 KB
Line 
1//
2version="version grobcov.lib 4.0.2.0 Jul_2015 "; // $Id$
3           // version L;  July_2015;
4category="General purpose";
5info="
6LIBRARY:  grobcov.lib   Groebner Cover for parametric ideals.
7
8          Comprehensive Groebner Systems, Groebner Cover, Canonical Forms,
9          Parametric Polynomial Systems, Dynamic Geometry, Loci, Envelop,
10          Constructible sets.
11          See
12
13          A. Montes A, M. Wibmer,
14          \"Groebner Bases for Polynomial Systems with parameters\",
15          Journal of Symbolic Computation 45 (2010) 1391-1425.
16          (http://www-ma2.upc.edu/~montes/).
17
18AUTHORS:  Antonio Montes , Hans Schoenemann.
19
20OVERVIEW:
21            In 2010, the library was designed to contain Montes-Wibmer's
22            algorithms for compute the canonical Groebner Cover of a
23            parametric ideal as described in the paper:
24
25            Montes A., Wibmer M.,
26            \"Groebner Bases for Polynomial Systems with parameters\".
27            Journal of Symbolic Computation 45 (2010) 1391-1425.
28
29            The central routine is grobcov. Given a parametric
30            ideal, grobcov outputs its Canonical Groebner Cover, consisting
31            of a set of pairs of (basis, segment). The basis (after
32            normalization) is the reduced Groebner basis for each point
33            of the segment. The segments are disjoint, locally closed
34            and correspond to constant lpp (leading power product)
35            of the basis, and are represented in canonical prime
36            representation. The segments are disjoint and cover the
37            whole parameter space. The output is canonical, it only
38            depends on the given parametric ideal and the monomial order.
39            This is much more than a simple Comprehensive Groebner System.
40            The algorithm grobcov allows options to solve partially the
41            problem when the whole automatic algorithm does not finish
42            in reasonable time.
43
44            grobcov uses a first algorithm cgsdr that outputs a disjoint
45            reduced Comprehensive Groebner System with constant lpp.
46            For this purpose, in this library, the implemented algorithm is
47            Kapur-Sun-Wang algorithm, because it is the most efficient
48            algorithm known for this purpose.
49
50            D. Kapur, Y. Sun, and D.K. Wang.
51            \"A New Algorithm for Computing Comprehensive Groebner Systems\".
52            Proceedings of ISSAC'2010, ACM Press, (2010), 29-36.
53
54            The library has evolved to include new applications of the
55            Groebner Cover, and new theoretical developments have been done.
56
57            The actual version also includes a routine (ConsLevels)
58            for computing the canonical form of a constructible set, given as a
59            union of locally closed sets. It is used in the new version for the
60            computation of loci and envelops. It determines the canonical locally closed
61            level sets of a constructuble. They will be described in a forthcoming paper:
62
63             J.M. Brunat, A. Montes,
64            \"Computing the canonical representation of constructible sets\".
65            Submited to Mathematics in Computer Science. July 2015.
66
67            A new set of routines (locus, locusdg, locusto) has been included to
68            compute loci of points. The routines are used in the Dynamic
69            Geometry software Geogebra. They are described in:
70
71            Abanades, Botana, Montes, Recio:
72            \''An Algebraic Taxonomy for Locus Computation in Dynamic Geometry\''.
73            Computer-Aided Design 56 (2014) 22-33.
74
75            Recently also routines for computing the envelop of a family
76            of curves (enverlop, envelopdg), to be used in Dynamic Geometry,
77            has been included and will be described in a forthcoming paper:
78
79             Abanades, Botana, Montes, Recio:
80             \''Envelops in Dynamic Geometry using the Groebner cover\''.
81
82
83            This version was finished on 31/07/2015
84
85NOTATIONS: All given and determined polynomials and ideals are in the
86@*         basering Q[a][x]; (a=parameters, x=variables)
87@*         After defining the ring, the main routines
88@*         grobcov, cgsdr,
89@*         generate the global rings
90@*         @R   (Q[a][x]),
91@*         @P   (Q[a]),
92@*         @RP  (Q[x,a])
93@*         that are used inside and killed before the output.
94
95PROCEDURES:
96grobcov(F);  Is the basic routine giving the canonical
97             Groebner Cover of the parametric ideal F.
98             This routine accepts many options, that
99             allow to obtain results even when the canonical
100             computation does not finish in reasonable time.
101
102cgsdr(F); Is the procedure for obtaining a first disjoint,
103             reduced Comprehensive Groebner System that
104             is used in grobcov, that can also be used
105             independently if only the CGS is required.
106             It is a more efficient routine than buildtree
107             (the own routine of 2010 that is no more used).
108             Now, KSW algorithm is used.
109
110pdivi(f,F); Performs a pseudodivision of a parametric polynomial
111             by a parametric ideal.
112
113pnormalf(f,E,N);   Reduces a parametric polynomial f over V(E) \ V(N)
114             ( E is the null ideal and N the non-null ideal )
115             over the parameters.
116
117Crep(N,M);  Computes the canonical C-representation of V(N) \ V(M).
118
119Prep(N,M);  Computes the canonical P-representation of V(N) \ V(M).
120
121PtoCrep(L)  Starting from the canonical Prep of a locally closed set
122             computes its Crep.
123
124extend(GC);  When the grobcov of an ideal has been computed
125             with the default option ('ext',0) and the explicit
126             option ('rep',2) (which is not the default), then
127             one can call extend (GC) (and options) to obtain the
128             full representation of the bases. With the default
129             option ('ext',0) only the generic representation of
130             the bases are computed, and one can obtain the full
131             representation using extend.
132
133ConsLevels(L); Given a list L of locally closed sets, it returns the canonical levels
134             of the constructible set of the union of them, as well as the levels
135             of the complement. It is described in the paper
136
137             J.M. Brunat, A. Montes,
138            \"Computing the canonical representation of constructible sets\".
139            Submited to Mathematics in Computer Science. July 2015.
140
141locus(G);    Special routine for determining the geometrical locus of points
142             verifying given conditions. Given a parametric ideal J with
143             parameters (x,y) and variables (x_1,..,xn), representing the
144             system determining the locus of points (x,y) who verify certain
145             properties, one can apply locus to the output of  grobcov(J),
146             locus determines the different classes of locus components.
147              described in the paper:
148
149             \"An Algebraic Taxonomy for Locus Computation in Dynamic Geometry\",
150             M. Abanades, F. Botana, A. Montes, T. Recio,
151             Computer-Aided Design 56 (2014) 22-33.
152
153             The components can be 'Normal', 'Special', 'Accumulation', 'Degenerate'.
154             The output are the components is given in P-canonical form
155             It also detects automatically a possible point that is to be
156             avoided by the mover, whose coordinates must be the last two
157             coordinates in the definition of the ring. If such a point is detected,
158             then it eliminates the segments of the grobcov depending on the
159             point that is to be avoided.
160
161locusdg(G);  Is a special routine that determines the  'Relevant' components
162             of the locus in dynamic geometry. It is to be called to the output of locus
163             and selects from it the useful components.
164
165envelop(F,C); Special routine for determining the envelop of a family of curves
166             F in Q[x,y][x_1,..xn] depending on a ideal of constraints C in Q[x_1,..,xn].
167             It detemines the different components as well as its type:
168             'Normal', 'Special', 'Accumulation', 'Degenerate'. And
169             it also classifies the Special components, determining the
170             zero dimensional antiimage of the component and verifying if
171             the component is a special curve of the family or not.
172             It calls internally first grobcov and then locus with special options
173             to obtain the complete result.
174             The taxonomy that it provides, as well as the algorithms involved
175             will be described in a forthcoming paper:
176
177             Abanades, Botana, Montes, Recio:
178             \''Envelops in Dynamic Geometry using the Gr\"obner cover\''.
179
180envelopdg(ev); Is a special routine to determine the 'Relevant' components
181             of the envelop of a family of curves to be used in Dynamic Geometry.
182             It must be called to the output of envelop(F,C).
183
184locusto(L); Transforms the output of locus, locusdg, envelop and envelopdg
185             into a string that can be reed from different computational systems.
186
187
188SEE ALSO: compregb_lib
189";
190
191LIB "primdec.lib";
192LIB "qhmoduli.lib";
193
194// ************ Begin of the grobcov library *********************
195
196// Library grobcov.lib
197// (Groebner Cover):
198// Release 0: (public)
199// Initial data: 21-1-2008
200// Uses buildtree for cgsdr
201// Final data: 3-7-2008
202// Release 2: (private)
203// Initial data: 6-9-2009
204// Last version using buildtree for cgsdr
205// Final data: 25-10-2011
206// Release B: (private)
207// Initial data: 1-7-2012
208// Uses both buildtree and KSW for cgsdr
209// Final data: 4-9-2012
210// Release G: (public)
211// Initial data: 4-9-2012
212// Uses KSW algorithm for cgsdr
213// Final data: 21-11-2013
214// Release L: (public)
215// New routine ConsLevels: 10-7-2015
216// Updated locus: 10-7-2015 (uses Conslevels)
217// New routines for computing the envelop of a family of curves: 22-1-2015
218// Final data: 22-7-2015
219
220//*************Auxiliary routines**************
221
222// elimintfromideal: elimine the constant numbers from an ideal
223//        (designed for W, nonnull conditions)
224// Input: ideal J
225// Output:ideal K with the elements of J that are non constants, in the
226//        ring K[x1,..,xm]
227static proc elimintfromideal(ideal J)
228{
229  int i;
230  int j=0;
231  ideal K;
232  if (size(J)==0){return(ideal(0));}
233  for (i=1;i<=ncols(J);i++){if (size(variables(J[i])) !=0){j++; K[j]=J[i];}}
234  return(K);
235}
236
237// delfromideal: deletes the i-th polynomial from the ideal F
238//    Works in any kind of ideal
239static proc delfromideal(ideal F, int i)
240{
241  int j;
242  ideal G;
243  if (size(F)<i){ERROR("delfromideal was called with incorrect arguments");}
244  if (size(F)<=1){return(ideal(0));}
245  if (i==0){return(F)};
246  for (j=1;j<=ncols(F);j++)
247  {
248    if (j!=i){G[ncols(G)+1]=F[j];}
249  }
250  return(G);
251}
252
253// delidfromid: deletes the polynomials in J that are in I
254// Input: ideals I, J
255// Output: the ideal J without the polynomials in I
256//   Works in any kind of ideal
257static proc delidfromid(ideal I, ideal J)
258{
259  int i; list r;
260  ideal JJ=J;
261  for (i=1;i<=size(I);i++)
262  {
263    r=memberpos(I[i],JJ);
264    if (r[1])
265    {
266      JJ=delfromideal(JJ,r[2]);
267    }
268  }
269  return(JJ);
270}
271
272// eliminates the ith element from a list or an intvec
273static proc elimfromlist(l, int i)
274{
275  if(typeof(l)=="list"){list L;}
276  if (typeof(l)=="intvec"){intvec L;}
277  if (typeof(l)=="ideal"){ideal L;}
278  int j;
279  if((size(l)==0) or (size(l)==1 and i!=1)){return(l);}
280  if (size(l)==1 and i==1){return(L);}
281  // L=l[1];
282  if(i>1)
283  {
284    for(j=1;j<=i-1;j++)
285    {
286      L[size(L)+1]=l[j];
287    }
288  }
289  for(j=i+1;j<=size(l);j++)
290  {
291    L[size(L)+1]=l[j];
292  }
293  return(L);
294}
295
296// eliminates repeated elements form an ideal or matrix or module or intmat or bigintmat
297static proc elimrepeated(F)
298{
299  int i;
300  int nt;
301  if (typeof(F)=="ideal"){nt=ncols(F);}
302  else{nt=size(F);}
303
304  def FF=F;
305  FF=F[1];
306  for (i=2;i<=nt;i++)
307  {
308    if (not(memberpos(F[i],FF)[1]))
309    {
310      FF[size(FF)+1]=F[i];
311    }
312  }
313  return(FF);
314}
315
316
317// equalideals
318// Input: ideals F and G;
319// Output: 1 if they are identical (the same polynomials in the same order)
320//         0 else
321static proc equalideals(ideal F, ideal G)
322{
323  int i=1; int t=1;
324  if (size(F)!=size(G)){return(0);}
325  while ((i<=size(F)) and (t))
326  {
327    if (F[i]!=G[i]){t=0;}
328    i++;
329  }
330  return(t);
331}
332
333// returns 1 if the two lists of ideals are equal and 0 if not
334static proc equallistideals(list L, list M)
335{
336  int t; int i;
337  if (size(L)!=size(M)){return(0);}
338  else
339  {
340    t=1;
341    if (size(L)>0)
342    {
343      i=1;
344      while ((t) and (i<=size(L)))
345      {
346        if (equalideals(L[i],M[i])==0){t=0;}
347        i++;
348      }
349    }
350    return(t);
351  }
352}
353
354// idcontains
355// Input: ideal p, ideal q
356// Output: 1 if p contains q,  0 otherwise
357// If the routine is to be called from the top, a previous call to
358// setglobalrings() is needed.
359static proc idcontains(ideal p, ideal q)
360{
361  int t; int i;
362  t=1; i=1;
363  def P=p; def Q=q;
364  attrib(P,"isSB",1);
365  poly r;
366  while ((t) and (i<=size(Q)))
367  {
368    r=reduce(Q[i],P);
369    if (r!=0){t=0;}
370    i++;
371  }
372  return(t);
373}
374
375
376// selectminideals
377//   given a list of ideals returns the list of integers corresponding
378//   to the minimal ideals in the list
379// Input: L (list of ideals)
380// Output: the list of integers corresponding to the minimal ideals in L
381//   Works in Q[u_1,..,u_m]
382static proc selectminideals(list L)
383{
384  list P; int i; int j; int t;
385  if(size(L)==0){return(L)};
386  if(size(L)==1){P[1]=1; return(P);}
387  for (i=1;i<=size(L);i++)
388  {
389    t=1;
390    j=1;
391    while ((t) and (j<=size(L)))
392    {
393      if (i!=j)
394      {
395        if(idcontains(L[i],L[j])==1)
396        {
397          t=0;
398        }
399      }
400      j++;
401    }
402    if (t){P[size(P)+1]=i;}
403  }
404  return(P);
405}
406
407
408// Auxiliary routine
409// elimconstfac: eliminate the factors in the polynom f that are in Q[a]
410// Input:
411//   poly f:
412//   list L: of components of the segment
413// Output:
414//   poly f2  where the factors of f in Q[a] that are non-null on any component
415//   have been dropped from f
416static proc elimconstfac(poly f)
417{
418  int cond; int i; int j; int t;
419  if (f==0){return(f);}
420  def RR=basering;
421  setring(@R);
422  def ff=imap(RR,f);
423  def l=factorize(ff,0);
424  poly f1=1;
425  for(i=2;i<=size(l[1]);i++)
426  {
427      f1=f1*(l[1][i])^(l[2][i]);
428  }
429  setring(RR);
430  def f2=imap(@R,f1);
431  return(f2);
432};
433
434static proc memberpos(f,J)
435//"USAGE:  memberpos(f,J);
436//         (f,J) expected (polynomial,ideal)
437//               or       (int,list(int))
438//               or       (int,intvec)
439//               or       (intvec,list(intvec))
440//               or       (list(int),list(list(int)))
441//               or       (ideal,list(ideal))
442//               or       (list(intvec),  list(list(intvec))).
443//         Works in any kind of ideals
444//RETURN:  The list (t,pos) t int; pos int;
445//         t is 1 if f belongs to J and 0 if not.
446//         pos gives the position in J (or 0 if f does not belong).
447//EXAMPLE: memberpos; shows an example"
448{
449  int pos=0;
450  int i=1;
451  int j;
452  int t=0;
453  int nt;
454  if (typeof(J)=="ideal"){nt=ncols(J);}
455  else{nt=size(J);}
456  if ((typeof(f)=="poly") or (typeof(f)=="int"))
457  { // (poly,ideal)  or
458    // (poly,list(poly))
459    // (int,list(int)) or
460    // (int,intvec)
461    i=1;
462    while(i<=nt)
463    {
464      if (f==J[i]){return(list(1,i));}
465      i++;
466    }
467    return(list(0,0));
468  }
469  else
470  {
471    if ((typeof(f)=="intvec") or ((typeof(f)=="list") and (typeof(f[1])=="int")))
472    { // (intvec,list(intvec)) or
473      // (list(int),list(list(int)))
474      i=1;
475      t=0;
476      pos=0;
477      while((i<=nt) and (t==0))
478      {
479        t=1;
480        j=1;
481        if (size(f)!=size(J[i])){t=0;}
482        else
483        {
484          while ((j<=size(f)) and t)
485          {
486            if (f[j]!=J[i][j]){t=0;}
487            j++;
488          }
489        }
490        if (t){pos=i;}
491        i++;
492      }
493      if (t){return(list(1,pos));}
494      else{return(list(0,0));}
495    }
496    else
497    {
498      if (typeof(f)=="ideal")
499      { // (ideal,list(ideal))
500        i=1;
501        t=0;
502        pos=0;
503        while((i<=nt) and (t==0))
504        {
505          t=1;
506          j=1;
507          if (ncols(f)!=ncols(J[i])){t=0;}
508          else
509          {
510            while ((j<=ncols(f)) and t)
511            {
512              if (f[j]!=J[i][j]){t=0;}
513              j++;
514            }
515          }
516          if (t){pos=i;}
517          i++;
518        }
519        if (t){return(list(1,pos));}
520        else{return(list(0,0));}
521      }
522      else
523      {
524        if ((typeof(f)=="list") and (typeof(f[1])=="intvec"))
525        { // (list(intvec),list(list(intvec)))
526          i=1;
527          t=0;
528          pos=0;
529          while((i<=nt) and (t==0))
530          {
531            t=1;
532            j=1;
533            if (size(f)!=size(J[i])){t=0;}
534            else
535            {
536              while ((j<=size(f)) and t)
537              {
538                if (f[j]!=J[i][j]){t=0;}
539                j++;
540              }
541            }
542            if (t){pos=i;}
543            i++;
544          }
545          if (t){return(list(1,pos));}
546          else{return(list(0,0));}
547        }
548      }
549    }
550  }
551}
552//example
553//{ "EXAMPLE:"; echo = 2;
554//  list L=(7,4,5,1,1,4,9);
555//  memberpos(1,L);
556//}
557
558// Auxiliary routine
559// pos
560// Input:  intvec p of zeros and ones
561// Output: intvec W of the positions where p has ones.
562static proc pos(intvec p)
563{
564  int i;
565  intvec W; int j=1;
566  for (i=1; i<=size(p); i++)
567  {
568    if (p[i]==1){W[j]=i; j++;}
569  }
570  return(W);
571}
572
573// Input:
574//  A,B: lists of ideals
575// Output:
576//   1 if both lists of ideals are equal, or 0 if not
577static proc equallistsofideals(list A, list B)
578{
579 int i;
580 int tes=0;
581 if (size(A)!=size(B)){return(tes);}
582 tes=1; i=1;
583 while(tes==1 and i<=size(A))
584 {
585   if (equalideals(A[i],B[i])==0){tes=0; return(tes);}
586   i++;
587 }
588 return(tes);
589}
590
591// Input:
592//  A,B:  lists of P-rep, i.e. of the form [p_i,[p_{i1},..,p_{ij_i}]]
593// Output:
594//   1 if both lists of P-reps are equal, or 0 if not
595static proc equallistsA(list A, list B)
596{
597  int tes=0;
598  if(equalideals(A[1],B[1])==0){return(tes);}
599  tes=equallistsofideals(A[2],B[2]);
600  return(tes);
601}
602
603// Input:
604//  A,B:  lists lists of of P-rep, i.e. of the form [[p_1,[p_{11},..,p_{1j_1}]] .. [p_i,[p_{i1},..,p_{ij_i}]]
605// Output:
606//   1 if both lists of lists of P-rep are equal, or 0 if not
607static proc equallistsAall(list A,list B)
608{
609 int i; int tes;
610 if(size(A)!=size(B)){return(tes);}
611 tes=1; i=1;
612 while(tes and i<=size(A))
613 {
614   tes=equallistsA(A[i],B[i]);
615   i++;
616 }
617 return(tes);
618}
619
620// idint: ideal intersection
621//        in the ring @P.
622//        it works in an extended ring
623// input: two ideals in the ring @P
624// output the intersection of both (is not a GB)
625static proc idint(ideal I, ideal J)
626{
627  def RR=basering;
628  ring T=0,t,lp;
629  def K=T+RR;
630  setring(K);
631  def Ia=imap(RR,I);
632  def Ja=imap(RR,J);
633  ideal IJ;
634  int i;
635  for(i=1;i<=size(Ia);i++){IJ[i]=t*Ia[i];}
636  for(i=1;i<=size(Ja);i++){IJ[size(Ia)+i]=(1-t)*Ja[i];}
637  ideal eIJ=eliminate(IJ,t);
638  setring(RR);
639  return(imap(K,eIJ));
640}
641
642//purpose ideal intersection called in @R and computed in @P
643static proc idintR(ideal N, ideal M)
644{
645  def RR=basering;
646  setring(@P);
647  def Np=imap(RR,N);
648  def Mp=imap(RR,M);
649  def Jp=idint(Np,Mp);
650  setring(RR);
651  return(imap(@P,Jp));
652}
653
654// Auxiliary routine
655// comb: the list of combinations of elements (1,..n) of order p
656static proc comb(int n, int p)
657{
658  list L; list L0;
659  intvec c; intvec d;
660  int i; int j; int last;
661  if ((n<0) or (n<p))
662  {
663    return(L);
664  }
665  if (p==1)
666  {
667    for (i=1;i<=n;i++)
668    {
669      c=i;
670      L[size(L)+1]=c;
671    }
672    return(L);
673  }
674  else
675  {
676    L0=comb(n,p-1);
677    for (i=1;i<=size(L0);i++)
678    {
679      c=L0[i]; d=c;
680      last=c[size(c)];
681      for (j=last+1;j<=n;j++)
682      {
683        d[size(c)+1]=j;
684        L[size(L)+1]=d;
685      }
686    }
687    return(L);
688  }
689}
690
691// Auxiliary routine
692// combrep
693// Input: V=(n_1,..,n_i)
694// Output: L=(v_1,..,v_p) where p=prod_j=1^i (n_j)
695//    is the list of all intvec v_j=(v_j1,..,v_ji) where 1<=v_jk<=n_i
696static proc combrep(intvec V)
697{
698  list L; list LL;
699  int i; int j; int k;  intvec W;
700  if (size(V)==1)
701  {
702    for (i=1;i<=V[1];i++)
703    {
704      L[i]=intvec(i);
705    }
706    return(L);
707  }
708  for (i=1;i<size(V);i++)
709  {
710    W[i]=V[i];
711  }
712  LL=combrep(W);
713  for (i=1;i<=size(LL);i++)
714  {
715    W=LL[i];
716    for (j=1;j<=V[size(V)];j++)
717    {
718      W[size(V)]=j;
719      L[size(L)+1]=W;
720    }
721  }
722  return(L);
723}
724
725static proc subset(J,K)
726//"USAGE:   subset(J,K);
727//          (J,K)  expected (ideal,ideal)
728//                  or     (list, list)
729//RETURN:   1 if all the elements of J are in K, 0 if not.
730//EXAMPLE:  subset; shows an example;"
731{
732  int i=1;
733  int nt;
734  if (typeof(J)=="ideal"){nt=ncols(J);}
735  else{nt=size(J);}
736  if (size(J)==0){return(1);}
737  while(i<=nt)
738  {
739    if (memberpos(J[i],K)[1]){i++;}
740    else {return(0);}
741  }
742  return(1);
743}
744//example
745//{ "EXAMPLE:"; echo = 2;
746//  list J=list(7,3,2);
747//  list K=list(1,2,3,5,7,8);
748//  subset(J,K);
749//}
750
751static proc setglobalrings()
752// "USAGE:   setglobalrings();
753//           No arguments
754// RETURN: After its call the rings Grobcov::@R=Q[a][x], Grobcov::@P=Q[a],
755//           Grobcov::@RP=Q[x,a] are defined as global variables.
756//           (a=parameters, x=variables)
757// NOTE: It is called internally by many basic routines of the
758//           library grobcov, cgsdr, extend, pdivi, pnormalf, locus, locusdg,
759//           envelop, envelopdg, and killed before the output.
760//           The user does not need to call it, except when it is interested
761//           in using some internal routine of the library that
762//           uses these rings.
763//           The basering R, must be of the form Q[a][x], (a=parameters,
764//           x=variables), and should be defined previously.
765// KEYWORDS: ring, rings
766// EXAMPLE:  setglobalrings; shows an example"
767{
768  if (defined(@P))
769  {
770    kill @P; kill @R; kill @RP;
771  }
772  def RR=basering;
773  def @R=basering;  // must be of the form Q[a][x], (a=parameters, x=variables)
774  def Rx=ringlist(RR);
775  def @P=ring(Rx[1]);
776  list Lx;
777  Lx[1]=0;
778  Lx[2]=Rx[2]+Rx[1][2];
779  Lx[3]=Rx[1][3];
780  Lx[4]=Rx[1][4];
781  Rx[1]=0;
782  def D=ring(Rx);
783  def @RP=D+@P;
784  export(@R);      // global ring Q[a][x]
785  export(@P);      // global ring Q[a]
786  export(@RP);     // global ring K[x,a] with product order
787  setring(RR);
788};
789// example
790// {
791//   "EXAMPLE:"; echo = 2;
792//   ring R=(0,a,b),(x,y,z),dp;
793//   setglobalrings();
794//   " ";"R=";R;
795//   " ";"Grobcov::@R=";Grobcov::@R;
796//   " ";"Grobcov::@P=";Grobcov::@P;
797//   " ";"Grobcov::@RP=";Grobcov::@RP;
798//  " "; "ringlist(Grobcov::@R)=";  ringlist(Grobcov::@R);
799//  " "; "ringlist(Grobcov::@P)=";  ringlist(Grobcov::@P);
800//  " "; "ringlist(Grobcov::@RP)=";  ringlist(Grobcov::@RP);
801// }
802
803// cld : clears denominators of an ideal and normalizes to content 1
804//        can be used in @R or @P or @RP
805// input:
806//        ideal J (J can be also poly), but the output is an ideal;
807// output:
808//        ideal Jc (the new form of ideal J without denominators and
809//        normalized to content 1)
810static proc cld(ideal J)
811{
812  if (size(J)==0){return(ideal(0));}
813  int te=0;
814  def RR=basering;
815  if(not(defined(@RP)))
816  {
817    te=1;
818    setglobalrings();
819  }
820  setring(@RP);
821  def Ja=imap(RR,J);
822  ideal Jb;
823  if (size(Ja)==0){setring(RR); return(ideal(0));}
824  int i;
825  def j=0;
826  for (i=1;i<=ncols(Ja);i++){if (size(Ja[i])!=0){j++; Jb[j]=cleardenom(Ja[i]);}}
827  setring(RR);
828  def Jc=imap(@RP,Jb);
829  if(te){kill @R; kill @RP; kill @P;}
830  return(Jc);
831};
832
833// simpqcoeffs : simplifies a quotient of two polynomials
834// input: two coeficients (or terms), that are considered as a quotient
835// output: the two coeficients reduced without common factors
836static proc simpqcoeffs(poly n,poly m)
837{
838  def nc=content(n);
839  def mc=content(m);
840  def gc=gcd(nc,mc);
841  ideal s=n/gc,m/gc;
842  return (s);
843}
844
845// pdivi : pseudodivision of a parametric polynomial f by a parametric ideal F in Q[a][x].
846// input:
847//   poly  f
848//   ideal F
849// output:
850//   list (poly r, ideal q, poly mu)
851proc pdivi(poly f,ideal F)
852"USAGE: pdivi(f,F);
853          poly f: the polynomialin Q[a][x] to be divided
854          ideal F: the divisor ideal in Q[a][x].
855RETURN: A list (poly r, ideal q, poly m). r is the remainder of the
856          pseudodivision, q is the set of quotients, and m is the
857          coefficient factor by which f is to be multiplied.
858NOTE: pseudodivision of a poly f by an ideal F in Q[a][x]. Returns a
859          list (r,q,m) such that m*f=r+sum(q.G), and no lpp of a divisor
860          divides a pp of r.
861KEYWORDS: division, reduce
862EXAMPLE:  pdivi; shows an example"
863{
864  F=simplify(F,2);
865  int i;
866  int j;
867  poly v=1;
868  for(i=1;i<=nvars(basering);i++){v=v*var(i);}
869  poly r=0;
870  poly mu=1;
871  def p=f;
872  ideal q;
873  for (i=1; i<=ncols(F); i++){q[i]=0;};
874  ideal lpf;
875  ideal lcf;
876  for (i=1;i<=ncols(F);i++){lpf[i]=leadmonom(F[i]);}
877  for (i=1;i<=ncols(F);i++){lcf[i]=leadcoef(F[i]);}
878  poly lpp;
879  poly lcp;
880  poly qlm;
881  poly nu;
882  poly rho;
883  int divoc=0;
884  ideal qlc;
885  while (p!=0)
886  {
887    i=1;
888    divoc=0;
889    lpp=leadmonom(p);
890    lcp=leadcoef(p);
891    while (divoc==0 and i<=size(F))
892    {
893      qlm=lpp/lpf[i];
894      if (qlm!=0)
895      {
896        qlc=simpqcoeffs(lcp,lcf[i]);
897        nu=qlc[2];
898        mu=mu*nu;
899        rho=qlc[1]*qlm;
900        p=nu*p-rho*F[i];
901        r=nu*r;
902        for (j=1;j<=size(F);j++){q[j]=nu*q[j];}
903        q[i]=q[i]+rho;
904        divoc=1;
905      }
906      else {i++;}
907    }
908    if (divoc==0)
909    {
910      r=r+lcp*lpp;
911      p=p-lcp*lpp;
912    }
913  }
914  list res=r,q,mu;
915  return(res);
916}
917example
918{
919  "EXAMPLE:"; echo = 2;
920  ring R=(0,a,b,c),(x,y),dp;
921  poly f=(ab-ac)*xy+(ab)*x+(5c);
922  // Divisor=";
923  f;
924  ideal F=ax+b,cy+a;
925  // Dividends=";
926  F;
927  def r=pdivi(f,F);
928  // (Remainder, quotients, factor)=";
929  r;
930  // Verifying the division:
931  r[3]*f-(r[2][1]*F[1]+r[2][2]*F[2]+r[1]);
932}
933
934// pspol : S-poly of two polynomials in @R
935// @R
936// input:
937//   poly f (given in the ring @R)
938//   poly g (given in the ring @R)
939// output:
940//   list (S, red):  S is the S-poly(f,g) and red is a Boolean variable
941//                if red then S reduces by Buchberger 1st criterion
942//                (not used)
943static proc pspol(poly f,poly g)
944{
945  def lcf=leadcoef(f);
946  def lcg=leadcoef(g);
947  def lpf=leadmonom(f);
948  def lpg=leadmonom(g);
949  def v=gcd(lpf,lpg);
950  def s=simpqcoeffs(lcf,lcg);
951  def vf=lpf/v;
952  def vg=lpg/v;
953  poly S=s[2]*vg*f-s[1]*vf*g;
954  return(S);
955}
956
957// facvar: Returns all the free-square factors of the elements
958//         of ideal J (non repeated). Integer factors are ignored,
959//         even 0 is ignored. It can be called from ideal @R, but
960//         the given ideal J must only contain poynomials in the
961//         parameters.
962//         Operates in the ring @P, but can be called from ring @R,
963//         and the ideal @P must be defined calling first setglobalrings();
964// input:  ideal J
965// output: ideal Jc: Returns all the free-square factors of the elements
966//         of ideal J (non repeated). Integer factors are ignored,
967//         even 0 is ignored. It can be called from ideal @R.
968static proc facvar(ideal J)
969//"USAGE:   facvar(J);
970//          J: an ideal in the parameters
971//RETURN:   all the free-square factors of the elements
972//          of ideal J (non repeated). Integer factors are ignored,
973//          even 0 is ignored. It can be called from ideal @R, but
974//          the given ideal J must only contain poynomials in the
975//          parameters.
976//NOTE:     Operates in the ring @P, and the ideal J must contain only
977//          polynomials in the parameters, but can be called from ring @R.
978//KEYWORDS: factor
979//EXAMPLE:  facvar; shows an example"
980{
981  int i;
982  def RR=basering;
983  setring(@P);
984  def Ja=imap(RR,J);
985  if(size(Ja)==0){setring(RR); return(ideal(0));}
986  Ja=elimintfromideal(Ja); // also in ideal @P
987  ideal Jb;
988  if (size(Ja)==0){Jb=ideal(0);}
989  else
990  {
991    for (i=1;i<=ncols(Ja);i++){if(size(Ja[i])!=0){Jb=Jb,factorize(Ja[i],1);}}
992    Jb=simplify(Jb,2+4+8);
993    Jb=cld(Jb);
994    Jb=elimintfromideal(Jb); // also in ideal @P
995  }
996  setring(RR);
997  def Jc=imap(@P,Jb);
998  return(Jc);
999}
1000//example
1001//{ "EXAMPLE:"; echo = 2;
1002//  ring R=(0,a,b,c),(x,y,z),dp;
1003//  setglobalrings();
1004//  ideal J=a2-b2,a2-2ab+b2,abc-bc;
1005//  facvar(J);
1006//}
1007
1008// Ered: eliminates the factors in the polynom f that are non-null.
1009//       In ring @R
1010// input:
1011//   poly f:
1012//   ideal E  of null-conditions
1013//   ideal N  of non-null conditions
1014//        (E,N) represents V(E) \ V(N),
1015//        Ered eliminates the non-null factors of f in V(E) \ V(N)
1016// output:
1017//   poly f2  where the non-null conditions have been dropped from f
1018static proc Ered(poly f,ideal E, ideal N)
1019{
1020  def RR=basering;
1021  setring(@R);
1022  poly ff=imap(RR,f);
1023  ideal EE=imap(RR,E);
1024  ideal NN=imap(RR,N);
1025  if((ff==0) or (equalideals(NN,ideal(1)))){setring(RR); return(f);}
1026  def v=variables(ff);
1027  int i;
1028  poly X=1;
1029  for(i=1;i<=size(v);i++){X=X*v[i];}
1030  matrix M=coef(ff,X);
1031  setring(@P);
1032  def RPE=imap(@R,EE);
1033  def RPN=imap(@R,NN);
1034  matrix Mp=imap(@R,M);
1035  poly g=Mp[2,1];
1036  if (size(Mp)!=2)
1037  {
1038    for(i=2;i<=size(Mp) div 2;i++)
1039    {
1040      g=gcd(g,Mp[2,i]);
1041    }
1042  }
1043  if (g==1){setring(RR); return(f);}
1044  else
1045  {
1046    def wg=factorize(g,2);
1047    if (wg[1][1]==1){setring(RR); return(f);}
1048    else
1049    {
1050      poly simp=1;
1051      int te;
1052      for(i=1;i<=size(wg[1]);i++)
1053      {
1054        te=inconsistent(RPE+wg[1][i],RPN);
1055        if(te)
1056        {
1057          simp=simp*(wg[1][i])^(wg[2][i]);
1058        }
1059      }
1060    }
1061    if (simp==1){setring(RR); return(f);}
1062    else
1063    {
1064      setring(RR);
1065      def simp0=imap(@P,simp);
1066      def f2=f/simp0;
1067      return(f2);
1068    }
1069  }
1070}
1071
1072// pnormalf: reduces a polynomial f wrt a V(E) \ V(N)
1073//           dividing by E and eliminating factors in N.
1074//           called in the ring @R,
1075//           operates in the ring @RP.
1076// input:
1077//         poly  f
1078//         ideal E  (depends only on the parameters)
1079//         ideal N  (depends only on the parameters)
1080//                  (E,N) represents V(E) \ V(N)
1081//         optional:
1082// output: poly f2 reduced wrt to V(E) \ V(N)
1083proc pnormalf(poly f, ideal E, ideal N)
1084"USAGE: pnormalf(f,E,N);
1085          f: the polynomial in Q[a][x]  (a=parameters, x=variables) to be
1086          reduced modulo V(E) \ V(N) of a segment in Q[a].
1087          E: the null conditions ideal in Q[a]
1088          N: the non-null conditions in Q[a]
1089RETURN: a reduced polynomial g of f, whose coefficients are reduced
1090          modulo E and having no factor in N.
1091NOTE: Should be called from ring Q[a][x].
1092          Ideals E and N must be given by polynomials in Q[a].
1093KEYWORDS: division, pdivi, reduce
1094EXAMPLE: pnormalf; shows an example"
1095{
1096    def RR=basering;
1097    int te=0;
1098    if (defined(@P)){te=1;}
1099    else{setglobalrings();}
1100    setring(@RP);
1101    def fa=imap(RR,f);
1102    def Ea=imap(RR,E);
1103    def Na=imap(RR,N);
1104    option(redSB);
1105    Ea=std(Ea);
1106    def r=cld(reduce(fa,Ea));
1107    poly f1=r[1];
1108    f1=Ered(r[1],Ea,Na);
1109    setring(RR);
1110    def f2=imap(@RP,f1);
1111    if(te==0){kill @R; kill @RP; kill @P;}
1112    return(f2)
1113};
1114example
1115{
1116  "EXAMPLE:"; echo = 2;
1117  ring R=(0,a,b,c),(x,y),dp;
1118  short=0;
1119  poly f=(b^2-1)*x^3*y+(c^2-1)*x*y^2+(c^2*b-b)*x+(a-bc)*y;
1120  ideal E=(c-1);
1121  ideal N=a-b;
1122
1123  pnormalf(f,E,N);
1124}
1125
1126// lesspol: compare two polynomials by its leading power products
1127// input:  two polynomials f,g in the ring @R
1128// output: 0 if f<g,  1 if f>=g
1129static proc lesspol(poly f, poly g)
1130{
1131  if (leadmonom(f)<leadmonom(g)){return(1);}
1132  else
1133  {
1134    if (leadmonom(g)<leadmonom(f)){return(0);}
1135    else
1136    {
1137      if (leadcoef(f)<leadcoef(g)){return(1);}
1138      else {return(0);}
1139    }
1140  }
1141};
1142
1143// sortideal: sorts the polynomials in an ideal by lm in ascending order
1144static proc sortideal(ideal Fi)
1145{
1146  def RR=basering;
1147  setring(@RP);
1148  def F=imap(RR,Fi);
1149  def H=F;
1150  ideal G;
1151  int i;
1152  int j;
1153  poly p;
1154  while (size(H)!=0)
1155  {
1156    j=1;
1157    p=H[1];
1158    for (i=1;i<=ncols(H);i++)
1159    {
1160      if(lesspol(H[i],p)){j=i;p=H[j];}
1161    }
1162    G[ncols(G)+1]=p;
1163    H=delfromideal(H,j);
1164    H=simplify(H,2);
1165  }
1166  setring(RR);
1167  def GG=imap(@RP,G);
1168  GG=simplify(GG,2);
1169  return(GG);
1170}
1171
1172// mingb: given a basis (gb reducing) it
1173// order the polynomials in ascending order and
1174// eliminates the polynomials whose lpp are divisible by some
1175// smaller one
1176static proc mingb(ideal F)
1177{
1178  int t; int i; int j;
1179  def H=sortideal(F);
1180  ideal G;
1181  if (ncols(H)<=1){return(H);}
1182  G=H[1];
1183  for (i=2; i<=ncols(H); i++)
1184  {
1185    t=1;
1186    j=1;
1187    while (t and (j<i))
1188    {
1189      if((leadmonom(H[i])/leadmonom(H[j]))!=0) {t=0;}
1190      j++;
1191    }
1192    if (t) {G[size(G)+1]=H[i];}
1193  }
1194  return(G);
1195}
1196
1197// redgbn: given a minimal basis (gb reducing) it
1198// reduces each polynomial wrt to V(E) \ V(N)
1199static proc redgbn(ideal F, ideal E, ideal N)
1200{
1201  int te=0;
1202  if (defined(@P)==1){te=1;}
1203  ideal G=F;
1204  ideal H;
1205  int i;
1206  if (size(G)==0){return(ideal(0));}
1207  for (i=1;i<=size(G);i++)
1208  {
1209    H=delfromideal(G,i);
1210    G[i]=pnormalf(pdivi(G[i],H)[1],E,N);
1211    G[i]=primepartZ(G[i]);
1212  }
1213  if(te==1){setglobalrings();}
1214  return(G);
1215}
1216
1217//**************Begin homogenizing************************
1218
1219// ishomog:
1220// Purpose: test if a polynomial is homogeneous in the variables or not
1221// input:  poly f
1222// output  1 if f is homogeneous, 0 if not
1223static proc ishomog(f)
1224{
1225  int i; poly r; int d; int dr;
1226  if (f==0){return(1);}
1227  d=deg(f); dr=d; r=f;
1228  while ((d==dr) and (r!=0))
1229  {
1230    r=r-lead(r);
1231    dr=deg(r);
1232  }
1233  if (r==0){return(1);}
1234  else{return(0);}
1235}
1236
1237// postredgb: given a minimal basis (gb reducing) it
1238// reduces each polynomial wrt to the others
1239static proc postredgb(ideal F)
1240{
1241  int te=0;
1242  if(defined(@P)==1){te=1;}
1243  ideal G;
1244  ideal H;
1245  int i;
1246  if (size(F)==0){return(ideal(0));}
1247  for (i=1;i<=size(F);i++)
1248  {
1249    H=delfromideal(F,i);
1250    G[i]=pdivi(F[i],H)[1];
1251  }
1252  if(te==1){setglobalrings();}
1253  return(G);
1254}
1255
1256
1257//purpose reduced Groebner basis called in @R and computed in @P
1258static proc gbR(ideal N)
1259{
1260  def RR=basering;
1261  setring(@P);
1262  def Np=imap(RR,N);
1263  option(redSB);
1264  Np=std(Np);
1265  setring(RR);
1266  return(imap(@P,Np));
1267}
1268
1269//**************End homogenizing************************
1270
1271//**************Begin of Groebner Cover*****************
1272
1273// incquotient
1274// incremental quotient
1275// Input: ideal N: a Groebner basis of an ideal
1276//        poly f:
1277// Output: Na = N:<f>
1278static proc incquotient(ideal N, poly f)
1279{
1280  poly g; int i;
1281  ideal Nb; ideal Na=N;
1282  if (size(Na)==1)
1283  {
1284    g=gcd(Na[1],f);
1285    if (g!=1)
1286    {
1287      Na[1]=Na[1]/g;
1288    }
1289    attrib(Na,"IsSB",1);
1290    return(Na);
1291  }
1292  def P=basering;
1293  poly @t;
1294  ring H=0,@t,lp;
1295  def HP=H+P;
1296  setring(HP);
1297  def fh=imap(P,f);
1298  def Nh=imap(P,N);
1299  ideal Nht;
1300  for (i=1;i<=size(Nh);i++)
1301  {
1302    Nht[i]=Nh[i]*@t;
1303  }
1304  attrib(Nht,"isSB",1);
1305  def fht=(1-@t)*fh;
1306  option(redSB);
1307  Nht=std(Nht,fht);
1308  ideal Nc; ideal v;
1309  for (i=1;i<=size(Nht);i++)
1310  {
1311    v=variables(Nht[i]);
1312    if(memberpos(@t,v)[1]==0)
1313    {
1314      Nc[size(Nc)+1]=Nht[i]/fh;
1315    }
1316  }
1317  setring(P);
1318  ideal HH;
1319  def Nd=imap(HP,Nc); Nb=Nd;
1320  option(redSB);
1321  Nb=std(Nd);
1322  return(Nb);
1323}
1324
1325// Auxiliary routine to define an order for ideals
1326// Returns 1 if the ideal a is shoud precede ideal b by sorting them in idbefid order
1327//             2 if the the contrary happen
1328//             0 if the order is not relevant
1329static proc idbefid(ideal a, ideal b)
1330{
1331  poly fa; poly fb; poly la; poly lb;
1332  int te=1; int i; int j;
1333  int na=size(a);
1334  int nb=size(b);
1335  int nm;
1336  if (na<=nb){nm=na;} else{nm=nb;}
1337  for (i=1;i<=nm; i++)
1338  {
1339    fa=a[i]; fb=b[i];
1340    while((fa!=0) or (fb!=0))
1341    {
1342      la=lead(fa);
1343      lb=lead(fb);
1344      fa=fa-la;
1345      fb=fb-lb;
1346      la=leadmonom(la);
1347      lb=leadmonom(lb);
1348      if(leadmonom(la+lb)!=la){return(1);}
1349      else{if(leadmonom(la+lb)!=lb){return(2);}}
1350    }
1351  }
1352  if(na<nb){return(1);}
1353  else
1354  {
1355    if(na>nb){return(2);}
1356    else{return(0);}
1357  }
1358}
1359
1360// sort a list of ideals using idbefid
1361static proc sortlistideals(list L)
1362{
1363  int i; int j; int n;
1364  ideal a; ideal b;
1365  list LL=L;
1366  list NL;
1367  int k; int te;
1368  i=1;
1369  while(size(LL)>0)
1370  {
1371    k=1;
1372    for(j=2;j<=size(LL);j++)
1373    {
1374      te=idbefid(LL[k],LL[j]);
1375      if (te==2){k=j;}
1376    }
1377    NL[size(NL)+1]=LL[k];
1378    n=size(LL);
1379    if (n>1){LL=elimfromlist(LL,k);} else{LL=list();}
1380  }
1381  return(NL);
1382}
1383
1384// Crep
1385// Computes the C-representation of V(N) \ V(M).
1386// input:
1387//    ideal N (null ideal) (not necessarily radical nor maximal)
1388//    ideal M (hole ideal) (not necessarily containing N)
1389// output:
1390//    the list (a,b) of the canonical ideals
1391//    the Crep of V(N) \ V(M)
1392// Assumed to be called in the ring @R
1393// Works on the ring @P
1394proc Crep(ideal N, ideal M)
1395 "USAGE:  Crep(N,M);
1396 Input: ideal N (null ideal) (not necessarily radical nor maximal)
1397           ideal M (hole ideal) (not necessarily containing N)
1398 RETURN:  The canonical C-representation of the locally closed set.
1399           [ P,Q ], a pair of radical ideals with P included in Q,
1400           representing the set V(P) \ V(Q) = V(N) \ V(M)
1401 NOTE:   Operates in a ring R=Q[a] (a=parameters)
1402 KEYWORDS: locally closed set, canoncial form
1403 EXAMPLE:  Crep; shows an example"
1404{
1405  list l;
1406  ideal Np=std(N);
1407  if (equalideals(Np,ideal(1)))
1408  {
1409    l=ideal(1),ideal(1);
1410    return(l);
1411  }
1412  int i;
1413  list L;
1414  ideal Q=Np+M;
1415  ideal P=ideal(1);
1416  L=minGTZ(Np);
1417  for(i=1;i<=size(L);i++)
1418  {
1419    if(idcontains(L[i],Q)==0)
1420    {
1421      P=intersect(P,L[i]);
1422    }
1423  }
1424  P=std(P);
1425  Q=std(radical(Q+P));
1426  list T=P,Q;
1427  return(T);
1428}
1429example
1430{
1431  "EXAMPLE:"; echo = 2;
1432  if(defined(Grobcov::@P)){kill Grobcov::@R; kill Grobcov::@P; kill Grobcov::@RP;}
1433  ring R=0,(x,y,z),lp;
1434  short=0;
1435  ideal E=x*(x^2+y^2+z^2-25);
1436  ideal N=x*(x-3),y-4;
1437  def Cr=Crep(E,N);
1438  Cr;
1439  def L=Prep(E,N);
1440  L;
1441  def Cr1=PtoCrep(L);
1442  Cr1;
1443}
1444
1445// Prep
1446// Computes the P-representation of V(N) \ V(M).
1447// input:
1448//    ideal N (null ideal) (not necessarily radical nor maximal)
1449//    ideal M (hole ideal) (not necessarily containing N)
1450// output:
1451//    the ((p_1,(p_11,p_1k_1)),..,(p_r,(p_r1,p_rk_r)));
1452//    the Prep of V(N) \ V(M)
1453// Assumed to be called in the ring @R
1454// Works on the ring @P
1455proc Prep(ideal N, ideal M)
1456 "USAGE:  Prep(N,M);
1457 Input: ideal N (null ideal) (not necessarily radical nor maximal)
1458           ideal M (hole ideal) (not necessarily containing N)
1459 RETURN: The canonical P-representation of the locally closed set V(N) \ V(M)
1460           Output: [ Comp_1, .. , Comp_s ] where
1461              Comp_i=[p_i,[p_i1,..,p_is_i]]
1462 NOTE:   Operates in a ring R=Q[a]  (a=parameters)
1463 KEYWORDS: Locally closed set, Canoncial form
1464 EXAMPLE:  Prep; shows an example"
1465{
1466  int te;
1467  if (N[1]==1)
1468  {
1469    return(list(list(ideal(1),list(ideal(1)))));
1470  }
1471  int i; int j; list L0;
1472  list Ni=minGTZ(N);
1473  list prep;
1474  for(j=1;j<=size(Ni);j++)
1475  {
1476    option(redSB);
1477    Ni[j]=std(Ni[j]);
1478  }
1479  list Mij;
1480  for (i=1;i<=size(Ni);i++)
1481  {
1482    Mij=minGTZ(Ni[i]+M);
1483    for(j=1;j<=size(Mij);j++)
1484    {
1485      option(redSB);
1486      Mij[j]=std(Mij[j]);
1487    }
1488    if ((size(Mij)==1) and (equalideals(Ni[i],Mij[1])==1)){;}
1489    else
1490    {
1491        prep[size(prep)+1]=list(Ni[i],Mij);
1492    }
1493  }
1494  //"T_abans="; prep;
1495  if (size(prep)==0){prep=list(list(ideal(1),list(ideal(1))));}
1496  //"T_Prep="; prep;
1497  //def Lout=CompleteA(prep,prep);
1498  //"T_Lout="; Lout;
1499  return(prep);
1500}
1501example
1502{
1503  "EXAMPLE:"; echo = 2;
1504  if(defined(Grobcov::@P)){kill Grobcov::@R; kill Grobcov::@P; kill Grobcov::@RP;}
1505  short=0;
1506  ring R=0,(x,y,z),lp;
1507  ideal E=x*(x^2+y^2+z^2-25);
1508  ideal N=x*(x-3),y-4;
1509  Prep(E,N);
1510}
1511
1512// PtoCrep
1513// Computes the C-representation from the P-representation.
1514// input:
1515//    list ((p_1,(p_11,p_1k_1)),..,(p_r,(p_r1,p_rk_r)));
1516//         the P-representation of V(N) \ V(M)
1517// output:
1518//    list (ideal ida, ideal idb)
1519//    the C-representaion of V(N) \ V(M) = V(ida) \ V(idb)
1520// Assumed to be called in the ring @R
1521// Works on the ring @P
1522proc PtoCrep(list L)
1523"USAGE: PtoCrep(L)
1524 Input L: list  [ Comp_1, .. , Comp_s ] where
1525          Comp_i=[p_i,[p_i1,..,p_is_i] ], is
1526          the P-representation of a locally closed set V(N) \ V(M)
1527 RETURN:  The canonical C-representation of the locally closed set
1528          [ P,Q ], a pair of radical ideals with P included in Q,
1529          representing the set V(P) \ V(Q)
1530 NOTE: Operates in a ring R=Q[a]  (a=parameters)
1531 KEYWORDS: locally closed set, canoncial form
1532 EXAMPLE:  PtoCrep; shows an example"
1533{
1534  int te;
1535  def RR=basering;
1536  if(defined(@P)){te=1; setring(@P); list Lp=imap(RR,L);}
1537  else {  te=0; def Lp=L;}
1538  def La=PtoCrep0(Lp);
1539  if(te==1) {setring(RR); def LL=imap(@P,La);}
1540  if(te==0){def LL=La;}
1541  return(LL);
1542}
1543example
1544{
1545  "EXAMPLE:"; echo = 2;
1546  if(defined(Grobcov::@P)){kill Grobcov::@R; kill Grobcov::@P; kill Grobcov::@RP;}
1547  short=0;
1548  ring R=0,(x,y,z),lp;
1549
1550  // (P,Q) represents a locally closed set
1551  ideal P=x^3+x*y^2+x*z^2-25*x;
1552  ideal Q=y-4,x*z,x^2-3*x;
1553
1554  // Now compute the P-representation=
1555  def L=Prep(P,Q);
1556  L;
1557  // Now compute the C-representation=
1558  def J=PtoCrep(L);
1559  J;
1560  // Now come back recomputing the P-represetation of the C-representation=
1561  Prep(J[1],J[2]);
1562}
1563
1564// PtoCrep0
1565// Computes the C-representation from the P-representation.
1566// input:
1567//    list ((p_1,(p_11,p_1k_1)),..,(p_r,(p_r1,p_rk_r)));
1568//         the P-representation of V(N) \ V(M)
1569// output:
1570//    list (ideal ida, ideal idb)
1571//    the C-representation of V(N) \ V(M) = V(ida) \ V(idb)
1572// Works in a ring Q[u_1,..,u_m] and is called on it.
1573static proc PtoCrep0(list L)
1574{
1575  int te=0;
1576  def Lp=L;
1577  int i; int j;
1578  ideal ida=ideal(1); ideal idb=ideal(1); list Lb; ideal N;
1579  for (i=1;i<=size(Lp);i++)
1580  {
1581    option(returnSB);
1582    N=Lp[i][1];
1583    ida=intersect(ida,N);
1584    Lb=Lp[i][2];
1585    for(j=1;j<=size(Lb);j++)
1586    {
1587      idb=intersect(idb,Lb[j]);
1588    }
1589  }
1590  //idb=radical(idb);
1591  def La=list(ida,idb);
1592  return(La);
1593}
1594
1595// input: F a parametric ideal in Q[a][x]
1596// output: a rComprehensive Groebner System disjoint and reduced.
1597//      It uses Kapur-Sun-Wang algorithm, and with the options
1598//      can compute the homogenization before  (('can',0) or ( 'can',1))
1599//      and dehomogenize the result.
1600proc cgsdr(ideal F, list #)
1601"USAGE: cgsdr(F);
1602          F: ideal in Q[a][x] (a=parameters, x=variables) to be discussed.
1603          To compute a disjoint, reduced Comprehensive Groebner System (CGS).
1604          cgsdr is the starting point of the fundamental routine grobcov.
1605          Inside grobcov it is used with options 'can' set to 0,1 and
1606          not with options ('can',2).
1607          It is to be used if only a disjoint reduced CGS is required.
1608
1609          Options: To modify the default options, pairs of arguments
1610          -option name, value- of valid options must be added to the call.
1611
1612          Options:
1613            \"can\",0-1-2: The default value is \"can\",2. In this case no
1614                homogenization is done. With option (\"can\",0) the given
1615                basis is homogenized, and with option (\"can\",1) the
1616                whole given ideal is homogenized before computing the
1617                cgs and dehomogenized after.
1618                with option (\"can\",0) the homogenized basis is used
1619                with option (\"can\",1) the homogenized ideal is used
1620                with option (\"can\",2) the given basis is used
1621            \"null\",ideal E: The default is (\"null\",ideal(0)).
1622            \"nonnull\",ideal N: The default (\"nonnull\",ideal(1)).
1623                When options \"null\" and/or \"nonnull\" are given, then
1624                the parameter space is restricted to V(E) \ V(N).
1625            \"comment\",0-1: The default is (\"comment\",0). Setting (\"comment\",1)
1626                will provide information about the development of the
1627                computation.
1628            \"out\",0-1: 1 (default) the output segments are given as
1629                as difference of varieties.
1630                0: the output segments are given in P-representation
1631                and the segments grouped by lpp
1632                With options (\"can\",0) and (\"can\",1) the option (\"out\",1)
1633                is set to (\"out\",0) because it is not compatible.
1634          One can give none or whatever of these options.
1635          With the default options (\"can\",2,\"out\",1), only the
1636          Kapur-Sun-Wang algorithm is computed. This is very efficient
1637          but is only the starting point for the computation of grobcov.
1638          When grobcov is computed, the call to cgsdr inside uses
1639          specific options that are more expensive ("can",0-1,"out",0).
1640RETURN: Returns a list T describing a reduced and disjoint
1641          Comprehensive Groebner System (CGS),
1642          With option (\"out\",0)
1643          the segments are grouped by
1644          leading power products (lpp) of the reduced Groebner
1645          basis and given in P-representation.
1646          The returned list is of the form:
1647           (
1648             (lpp, (num,basis,segment),...,(num,basis,segment),lpp),
1649             ..,,
1650             (lpp, (num,basis,segment),...,(num,basis,segment),lpp)
1651           )
1652          The bases are the reduced Groebner bases (after normalization)
1653          for each point of the corresponding segment.
1654
1655          The third element of each lpp segment is the lpp of the
1656          used ideal in the CGS as a string:
1657            with option (\"can\",0) the homogenized basis is used
1658            with option (\"can\",1) the homogenized ideal is used
1659            with option (\"can\",2) the given basis is used
1660
1661          With option (\"out\",1) (default)
1662          only KSW is applied and segments are given as
1663          difference of varieties and are not grouped
1664          The returned list is of the form:
1665           (
1666             (E,N,B),..(E,N,B)
1667           )
1668          E is the null variety
1669          N is the nonnull variety
1670          segment = V(E) \ V(N)
1671          B is the reduced Groebner basis
1672
1673NOTE:  The basering R, must be of the form Q[a][x], (a=parameters,
1674          x=variables), and should be defined previously, and the ideal
1675          defined on R.
1676KEYWORDS: CGS, disjoint, reduced, Comprehensive Groebner System
1677EXAMPLE:  cgsdr; shows an example"
1678{
1679  int te;
1680  def RR=basering;
1681  if(defined(@P)){te=1;}
1682  else{te=0; setglobalrings();}
1683  // INITIALIZING OPTIONS
1684  int i; int j;
1685  def E=ideal(0);
1686  def N=ideal(1);
1687  int comment=0;
1688  int can=2;
1689  int out=1;
1690  poly f;
1691  ideal B;
1692  int start=timer;
1693  list L=#;
1694  for(i=1;i<=size(L) div 2;i++)
1695  {
1696    if(L[2*i-1]=="null"){E=L[2*i];}
1697    else
1698    {
1699      if(L[2*i-1]=="nonnull"){N=L[2*i];}
1700      else
1701      {
1702        if(L[2*i-1]=="comment"){comment=L[2*i];}
1703        else
1704        {
1705          if(L[2*i-1]=="can"){can=L[2*i];}
1706          else
1707          {
1708            if(L[2*i-1]=="out"){out=L[2*i];}
1709          }
1710        }
1711      }
1712    }
1713  }
1714  //if(can==2){out=1;}
1715  B=F;
1716  if ((printlevel) and (comment==0)){comment=printlevel;}
1717  if((can<2) and (out>0)){"Option out,1 is not compatible with can,0,1"; out=0;}
1718  // DEFINING OPTIONS
1719  list LL;
1720  LL[1]="can";     LL[2]=can;
1721  LL[3]="comment"; LL[4]=comment;
1722  LL[5]="out";     LL[6]=out;
1723  LL[7]="null";    LL[8]=E;
1724  LL[9]="nonnull"; LL[10]=N;
1725  if(comment>=1)
1726  {
1727    string("Begin cgsdr with options: ",LL);
1728  }
1729  int ish;
1730  for (i=1;i<=size(B);i++){ish=ishomog(B[i]); if(ish==0){break;};}
1731  if (ish)
1732  {
1733    if(comment>0){string("The given system is homogneous");}
1734    def GS=KSW(B,LL);
1735    //can=0;
1736  }
1737  else
1738  {
1739  // ACTING DEPENDING ON OPTIONS
1740  if(can==2)
1741  {
1742    // WITHOUT HOMOHGENIZING
1743    if(comment>0){string("Option of cgsdr: do not homogenize");}
1744    def GS=KSW(B,LL);
1745    setglobalrings();
1746  }
1747  else
1748  {
1749    if(can==1)
1750    {
1751      // COMPUTING THE HOMOGOENIZED IDEAL
1752      if(comment>=1){string("Homogenizing the whole ideal: option can=1");}
1753      list RRL=ringlist(RR);
1754      RRL[3][1][1]="dp";
1755      def Pa=ring(RRL[1]);
1756      list Lx;
1757      Lx[1]=0;
1758      Lx[2]=RRL[2]+RRL[1][2];
1759      Lx[3]=RRL[1][3];
1760      Lx[4]=RRL[1][4];
1761      RRL[1]=0;
1762      def D=ring(RRL);
1763      def RP=D+Pa;
1764      setring(RP);
1765      def B1=imap(RR,B);
1766      option(redSB);
1767      B1=std(B1);
1768      setring(RR);
1769      def B2=imap(RP,B1);
1770    }
1771    else
1772    { // (can=0)
1773       if(comment>0){string("Homogenizing the basis: option can=0");}
1774      def B2=B;
1775    }
1776    // COMPUTING HOMOGENIZED CGS
1777    poly @t;
1778    ring H=0,@t,dp;
1779    def RH=RR+H;
1780    setring(RH);
1781    setglobalrings();
1782    def BH=imap(RR,B2);
1783    def LH=imap(RR,LL);
1784    for (i=1;i<=size(BH);i++)
1785    {
1786      BH[i]=homog(BH[i],@t);
1787    }
1788    if (comment>=2){string("Homogenized system = "); BH;}
1789    def GSH=KSW(BH,LH);
1790    setglobalrings();
1791    // DEHOMOGENIZING THE RESULT
1792    if(out==0)
1793    {
1794      for (i=1;i<=size(GSH);i++)
1795      {
1796        GSH[i][1]=subst(GSH[i][1],@t,1);
1797        for(j=1;j<=size(GSH[i][2]);j++)
1798        {
1799          GSH[i][2][j][2]=subst(GSH[i][2][j][2],@t,1);
1800        }
1801      }
1802    }
1803    else
1804    {
1805      for (i=1;i<=size(GSH);i++)
1806      {
1807        GSH[i][3]=subst(GSH[i][3],@t,1);
1808        GSH[i][7]=subst(GSH[i][7],@t,1);
1809      }
1810    }
1811    setring(RR);
1812    def GS=imap(RH,GSH);
1813    }
1814
1815
1816    setglobalrings();
1817    if(out==0)
1818    {
1819      for (i=1;i<=size(GS);i++)
1820      {
1821        GS[i][1]=postredgb(mingb(GS[i][1]));
1822        for(j=1;j<=size(GS[i][2]);j++)
1823        {
1824          GS[i][2][j][2]=postredgb(mingb(GS[i][2][j][2]));
1825        }
1826      }
1827    }
1828    else
1829    {
1830      for (i=1;i<=size(GS);i++)
1831      {
1832        if(GS[i][2]==1)
1833        {
1834          GS[i][3]=postredgb(mingb(GS[i][3]));
1835          if (typeof(GS[i][7])=="ideal")
1836          { GS[i][7]=postredgb(mingb(GS[i][7]));}
1837        }
1838      }
1839    }
1840  }
1841  if(te==0){kill @P; kill @R; kill @RP;}
1842  return(GS);
1843}
1844example
1845{
1846  "EXAMPLE:"; echo = 2;
1847  // Casas conjecture for degree 4:
1848  ring R=(0,a0,a1,a2,a3,a4),(x1,x2,x3),dp;
1849  short=0;
1850  ideal F=x1^4+(4*a3)*x1^3+(6*a2)*x1^2+(4*a1)*x1+(a0),
1851          x1^3+(3*a3)*x1^2+(3*a2)*x1+(a1),
1852          x2^4+(4*a3)*x2^3+(6*a2)*x2^2+(4*a1)*x2+(a0),
1853          x2^2+(2*a3)*x2+(a2),
1854          x3^4+(4*a3)*x3^3+(6*a2)*x3^2+(4*a1)*x3+(a0),
1855          x3+(a3);
1856  cgsdr(F);
1857}
1858
1859// input:  internal routine called by cgsdr at the end to group the
1860//            lpp segments and improve the output
1861// output: grouped segments by lpp obtained in cgsdr
1862static proc grsegments(list T)
1863{
1864  int i;
1865  list L;
1866  list lpp;
1867  list lp;
1868  list ls;
1869  int n=size(T);
1870  lpp[1]=T[n][1];
1871  L[1]=list(lpp[1],list(list(T[n][2],T[n][3],T[n][4])));
1872  if (n>1)
1873  {
1874    for (i=1;i<=size(T)-1;i++)
1875    {
1876      lp=memberpos(T[n-i][1],lpp);
1877      if(lp[1]==1)
1878      {
1879        ls=L[lp[2]][2];
1880        ls[size(ls)+1]=list(T[n-i][2],T[n-i][3],T[n-i][4]);
1881        L[lp[2]][2]=ls;
1882      }
1883      else
1884      {
1885        lpp[size(lpp)+1]=T[n-i][1];
1886        L[size(L)+1]=list(T[n-i][1],list(list(T[n-i][2],T[n-i][3],T[n-i][4])));
1887      }
1888    }
1889  }
1890  return(L);
1891}
1892
1893// LCUnion
1894// Given a list of the P-representations of locally closed segments
1895// for which we know that the union is also locally closed
1896// it returns the P-representation of its union
1897// input:  L list of segments in P-representation
1898//      ((p_j^i,(p_j1^i,...,p_jk_j^i | j=1..t_i)) | i=1..s )
1899//      where i represents a segment
1900// output: P-representation of the union
1901//       ((P_j,(P_j1,...,P_jk_j | j=1..t)))
1902static proc LCUnion(list LL)
1903{
1904  def RR=basering;
1905  setring(@P);
1906  def L=imap(RR,LL);
1907  int i; int j; int k; list H; list C; list T;
1908  list L0; list P0; list P; list Q0; list Q;
1909  for (i=1;i<=size(L);i++)
1910  {
1911    for (j=1;j<=size(L[i]);j++)
1912    {
1913      P0[size(P0)+1]=L[i][j][1];
1914      L0[size(L0)+1]=intvec(i,j);
1915    }
1916  }
1917  Q0=selectminideals(P0);
1918  for (i=1;i<=size(Q0);i++)
1919  {
1920    Q[i]=L0[Q0[i]];
1921    P[i]=L[Q[i][1]][Q[i][2]];
1922  }
1923  // P is the list of the maximal components of the union
1924  //   with the corresponding initial holes.
1925  // Q is the list of intvec positions in L of the first element of the P's
1926  //   Its elements give (num of segment, num of max component (=min ideal))
1927  for (k=1;k<=size(Q);k++)
1928  {
1929    H=P[k][2]; // holes of P[k][1]
1930    for (i=1;i<=size(L);i++)
1931    {
1932      if (i!=Q[k][1])
1933      {
1934        for (j=1;j<=size(L[i]);j++)
1935        {
1936          C[size(C)+1]=L[i][j];
1937        }
1938      }
1939    }
1940    T[size(T)+1]=list(Q[k],P[k][1],addpart(H,C));
1941  }
1942  setring(RR);
1943  def TT=imap(@P,T);
1944  return(TT);
1945}
1946
1947// Auxiliary routine
1948// called by LCUnion to modify the holes of a primepart of the union
1949// by the addition of the segments that do not correspond to that part
1950// Works on @P ring.
1951// Input:
1952//   H=(p_i1,..,p_is) the holes of a component to be transformed by the addition of
1953//        the segments C that do not correspond to that component
1954//   C=((q_1,(q_11,..,q_1l_1),pos1),..,(q_k,(q_k1,..,q_kl_k),posk))
1955// posi=(i,j) position of the component
1956//        the list of segments to be added to the holes
1957static proc addpart(list H, list C)
1958{
1959  list Q; int i; int j; int k; int l; int t; int t1;
1960  Q=H; intvec notQ; list QQ; list addq;
1961  // @Q2=list of (i,j) positions of the components that have been aded to some hole of the maximal ideals
1962  //          plus those of the components added to the holes.
1963  ideal q;
1964  i=1;
1965  while (i<=size(Q))
1966  {
1967    if (memberpos(i,notQ)[1]==0)
1968    {
1969      q=Q[i];
1970      t=1; j=1;
1971      while ((t) and (j<=size(C)))
1972      {
1973        if (equalideals(q,C[j][1]))
1974        {
1975          // \\ @Q2[size(@Q2)+1]=C[j][3];
1976          t=0;
1977          for (k=1;k<=size(C[j][2]);k++)
1978          {
1979            t1=1;
1980            l=1;
1981            while((t1) and (l<=size(Q)))
1982            {
1983              if ((l!=i) and (memberpos(l,notQ)[1]==0))
1984              {
1985                if (idcontains(C[j][2][k],Q[l]))
1986                {
1987                  t1=0;
1988                }
1989              }
1990              l++;
1991            }
1992            if (t1)
1993            {
1994              addq[size(addq)+1]=C[j][2][k];
1995              // \\ @Q2[size(@Q2)+1]=C[j][3];
1996            }
1997          }
1998          if((size(notQ)==1) and (notQ[1]==0)){notQ[1]=i;}
1999          else {notQ[size(notQ)+1]=i;}
2000        }
2001        j++;
2002      }
2003      if (size(addq)>0)
2004      {
2005        for (k=1;k<=size(addq);k++)
2006        {
2007          Q[size(Q)+1]=addq[k];
2008        }
2009        kill addq;
2010        list addq;
2011      }
2012    }
2013    i++;
2014  }
2015  for (i=1;i<=size(Q);i++)
2016  {
2017    if(memberpos(i,notQ)[1]==0)
2018    {
2019      QQ[size(QQ)+1]=Q[i];
2020    }
2021  }
2022  if (size(QQ)==0){QQ[1]=ideal(1);}
2023  return(addpartfine(QQ,C));
2024}
2025
2026// Auxiliary routine called by addpart to finish the modification of the holes of a primepart
2027// of the union by the addition of the segments that do not correspond to
2028// that part.
2029// Works on @P ring.
2030static proc addpartfine(list H, list C0)
2031{
2032  //"T_H="; H;
2033  int i; int j; int k; int te; intvec notQ; int l; list sel; int used;
2034  intvec jtesC;
2035  if ((size(H)==1) and (equalideals(H[1],ideal(1)))){return(H);}
2036  if (size(C0)==0){return(H);}
2037  list newQ; list nQ; list Q; list nQ1; list Q0;
2038  def Q1=H;
2039  //Q1=sortlistideals(Q1,idbefid);
2040  def C=C0;
2041  while(equallistideals(Q0,Q1)==0)
2042  {
2043    Q0=Q1;
2044    i=0;
2045    Q=Q1;
2046    kill notQ; intvec notQ;
2047    while(i<size(Q))
2048    {
2049      i++;
2050      for(j=1;j<=size(C);j++)
2051      {
2052        te=idcontains(Q[i],C[j][1]);
2053        if(te)
2054        {
2055          for(k=1;k<=size(C[j][2]);k++)
2056          {
2057            if(idcontains(Q[i],C[j][2][k]))
2058            {
2059              te=0; break;
2060            }
2061          }
2062          if (te)
2063          {
2064            used++;
2065            if ((size(notQ)==1) and (notQ[1]==0)){notQ[1]=i;}
2066            else{notQ[size(notQ)+1]=i;}
2067            kill newQ; list newQ;
2068            for(k=1;k<=size(C[j][2]);k++)
2069            {
2070              nQ=minGTZ(Q[i]+C[j][2][k]);
2071              for(l=1;l<=size(nQ);l++)
2072              {
2073                option(redSB);
2074                nQ[l]=std(nQ[l]);
2075                newQ[size(newQ)+1]=nQ[l];
2076              }
2077            }
2078            sel=selectminideals(newQ);
2079            kill nQ1; list nQ1;
2080            for(l=1;l<=size(sel);l++)
2081            {
2082              nQ1[l]=newQ[sel[l]];
2083            }
2084            newQ=nQ1;
2085            for(l=1;l<=size(newQ);l++)
2086            {
2087              Q[size(Q)+1]=newQ[l];
2088            }
2089            break;
2090          }
2091        }
2092      }
2093    }
2094    kill Q1; list Q1;
2095    for(i=1;i<=size(Q);i++)
2096    {
2097      if(memberpos(i,notQ)[1]==0)
2098      {
2099        Q1[size(Q1)+1]=Q[i];
2100      }
2101    }
2102    //"T_Q1_0="; Q1;
2103    sel=selectminideals(Q1);
2104    kill nQ1; list nQ1;
2105    for(l=1;l<=size(sel);l++)
2106    {
2107      nQ1[l]=Q1[sel[l]];
2108    }
2109    Q1=nQ1;
2110  }
2111  if(size(Q1)==0){Q1=ideal(1),ideal(1);}
2112  //"T_Q1_1="; Q1;
2113  //if(used>0){string("addpartfine was ", used, " times used");}
2114  return(Q1);
2115}
2116
2117
2118// Auxiliary routine for grobcov: ideal F is assumed to be homogeneous
2119// gcover
2120// input: ideal F: a generating set of a homogeneous ideal in Q[a][x]
2121//    list #: optional
2122// output: the list
2123//   S=((lpp, generic basis, Prep, Crep),..,(lpp, generic basis, Prep, Crep))
2124//      where a Prep is ( (p1,(p11,..,p1k_1)),..,(pj,(pj1,..,p1k_j)) )
2125//            a Crep is ( ida, idb )
2126static proc gcover(ideal F,list #)
2127{
2128  int i; int j; int k; ideal lpp; list GPi2; list pairspP; ideal B; int ti;
2129  int i1; int tes; int j1; int selind; int i2; int m;
2130  list prep; list crep; list LCU; poly p; poly lcp; ideal FF;
2131  list lpi;
2132  string lpph;
2133  list L=#;
2134  int canop=1;
2135  int extop=1;
2136  int repop=0;
2137  ideal E=ideal(0);;
2138  ideal N=ideal(1);;
2139  int comment;
2140  for(i=1;i<=size(L) div 2;i++)
2141  {
2142    if(L[2*i-1]=="can"){canop=L[2*i];}
2143    else
2144    {
2145      if(L[2*i-1]=="ext"){extop=L[2*i];}
2146      else
2147      {
2148        if(L[2*i-1]=="rep"){repop=L[2*i];}
2149        else
2150        {
2151          if(L[2*i-1]=="null"){E=L[2*i];}
2152          else
2153          {
2154            if(L[2*i-1]=="nonnull"){N=L[2*i];}
2155            else
2156            {
2157              if (L[2*i-1]=="comment"){comment=L[2*i];}
2158            }
2159          }
2160        }
2161      }
2162    }
2163  }
2164  list GS; list GP;
2165  def RR=basering;
2166  GS=cgsdr(F,L); // "null",NW[1],"nonnull",NW[2],"cgs",CGS,"comment",comment);
2167  setglobalrings();
2168  int start=timer;
2169  GP=GS;
2170  ideal lppr;
2171  list LL;
2172  list S;
2173  poly sp;
2174  ideal BB;
2175  for (i=1;i<=size(GP);i++)
2176  {
2177    kill LL;
2178    list LL;
2179    lpp=GP[i][1];
2180    GPi2=GP[i][2];
2181    lpph=GP[i][3];
2182    kill pairspP; list pairspP;
2183    for(j=1;j<=size(GPi2);j++)
2184    {
2185      pairspP[size(pairspP)+1]=GPi2[j][3];
2186    }
2187    LCU=LCUnion(pairspP);
2188    kill prep; list prep;
2189    kill crep; list crep;
2190    for(k=1;k<=size(LCU);k++)
2191    {
2192      prep[k]=list(LCU[k][2],LCU[k][3]);
2193      B=GPi2[LCU[k][1][1]][2]; // ATENTION last 1 has been changed to [2]
2194      LCU[k][1]=B;
2195    }
2196    //"Deciding if combine is needed";
2197    kill BB;
2198    ideal BB;
2199    tes=1; m=1;
2200    while((tes) and (m<=size(LCU[1][1])))
2201    {
2202      j=1;
2203      while((tes) and (j<=size(LCU)))
2204      {
2205        k=1;
2206        while((tes) and (k<=size(LCU)))
2207        {
2208          if(j!=k)
2209          {
2210            sp=pnormalf(pspol(LCU[j][1][m],LCU[k][1][m]),LCU[k][2],N);
2211            if(sp!=0){tes=0;}
2212          }
2213          k++;
2214        }        //setglobalrings();
2215        if(tes)
2216        {
2217          BB[m]=LCU[j][1][m];
2218        }
2219        j++;
2220      }
2221      if(tes==0){break;}
2222      m++;
2223    }
2224    crep=PtoCrep(prep);
2225    if(tes==0)
2226    {
2227      // combine is needed
2228      kill B; ideal B;
2229      for (j=1;j<=size(LCU);j++)
2230      {
2231        LL[j]=LCU[j][2];
2232      }
2233      if (size(LCU)>1)
2234      {
2235        FF=precombint(LL);
2236      }
2237      for (k=1;k<=size(lpp);k++)
2238      {
2239        kill L; list L;
2240        for (j=1;j<=size(LCU);j++)
2241        {
2242          L[j]=list(LCU[j][2],LCU[j][1][k]);
2243        }
2244        if (size(LCU)>1)
2245        {
2246          B[k]=combine(L,FF);
2247        }
2248        else{B[k]=L[1][2];}
2249      }
2250    }
2251    else{B=BB;}
2252    for(j=1;j<=size(B);j++)
2253    {
2254      B[j]=pnormalf(B[j],crep[1],crep[2]);
2255    }
2256    S[i]=list(lpp,B,prep,crep,lpph);
2257    if(comment>=1)
2258    {
2259      lpi[size(lpi)+1]=string("[",i,"]");
2260      lpi[size(lpi)+1]=S[i][1];
2261    }
2262  }
2263  if(comment>=1)
2264  {
2265    string("Time in LCUnion + combine = ",timer-start);
2266    if(comment>=2){string("lpp=",lpi)};
2267  }
2268  if(defined(@P)==1){kill @P; kill @RP; kill @R;}
2269  return(S);
2270}
2271
2272// grobcov
2273// input:
2274//    ideal F: a parametric ideal in Q[a][x], (a=parameters, x=variables).
2275//    list #: (options) list("null",N,"nonnull",W,"can",0-1,ext",0-1, "rep",0-1-2)
2276//            where
2277//            N is the null conditions ideal (if desired)
2278//            W is the ideal of non-null conditions (if desired)
2279//            The value of \"can\"i s 1 by default and can be set to 0 if we do not
2280//            need to obtain the canonical GC, but only a GC.
2281//            The value of \"ext\" is 0 by default and so the generic representation
2282//             of the bases is given. It can be set to 1, and then the full
2283//             representation of the bases is given.
2284//            The value of \"rep\" is 0 by default, and then the segments
2285//            are given in canonical P-representation. It can be set to 1
2286//            and then they are given in canonical C-representation.
2287//            If it is set to 2, then both representations are given.
2288// output:
2289//    list S: ((lpp,basis,(idp_1,(idp_11,..,idp_1s_1))), ..
2290//             (lpp,basis,(idp_r,(idp_r1,..,idp_rs_r))) ) where
2291//            each element of S corresponds to a lpp-segment
2292//            given by the lpp, the basis, and the P-representation of the segment
2293proc grobcov(ideal F,list #)
2294"USAGE:   grobcov(F); This is the fundamental routine of the
2295          library. It computes the Groebner cover of a parametric ideal. See
2296                Montes A., Wibmer M.,
2297               \"Groebner Bases for Polynomial Systems with parameters\".
2298               JSC 45 (2010) 1391-1425.)
2299          The Groebner Cover of a parametric ideal consist of a set of
2300          pairs(S_i,B_i), where the S_i are disjoint locally closed
2301          segments of the parameter space, and the B_i are the reduced
2302          Groebner bases of the ideal on every point of S_i.
2303
2304          The ideal F must be defined on a parametric ring Q[a][x].
2305          (a=parameters, x=variables)
2306          Options: To modify the default options, pair of arguments
2307          -option name, value- of valid options must be added to the call.
2308
2309          Options:
2310            \"null\",ideal E: The default is (\"null\",ideal(0)).
2311            \"nonnull\",ideal N: The default is (\"nonnull\",ideal(1)).
2312                When options \"null\" and/or \"nonnull\" are given, then
2313                the parameter space is restricted to V(E) \ V(N).
2314            \"can\",0-1: The default is (\"can\",1). With the default option
2315                the homogenized ideal is computed before obtaining the
2316                Groebner Cover, so that the result is the canonical
2317                Groebner Cover. Setting (\"can\",0) only homogenizes the
2318                basis so the result is not exactly canonical, but the
2319                computation is shorter.
2320            \"ext\",0-1: The default is (\"ext\",0). With the default
2321                (\"ext\",0), only the generic representation of the bases is
2322                computed (single polynomials, but not specializing to non-zero
2323                for every point of the segment. With option (\"ext\",1) the
2324                full representation of the bases is computed (possible
2325                sheaves) and sometimes a simpler result is obtained,
2326                but the computation is more time consuming.
2327            \"rep\",0-1-2: The default is (\"rep\",0) and then the segments
2328                are given in canonical P-representation. Option (\"rep\",1)
2329                represents the segments in canonical C-representation,
2330                and option (\"rep\",2) gives both representations.
2331            \"comment\",0-3: The default is (\"comment\",0). Setting
2332                \"comment\" higher will provide information about the
2333                development of the computation.
2334          One can give none or whatever of these options.
2335RETURN:   The list
2336          (
2337           (lpp_1,basis_1,segment_1,lpph_1),
2338           ...
2339           (lpp_s,basis_s,segment_s,lpph_s)
2340          )
2341
2342          The lpp are constant over a segment and correspond to the
2343          set of lpp of the reduced Groebner basis for each point
2344          of the segment.
2345          The lpph corresponds to the lpp of the homogenized ideal
2346          and is different for each segment. It is given as a string,
2347          and shown only for information. With the default option
2348           \"can\",1, the segments have different lpph.
2349
2350          Basis: to each element of lpp corresponds an I-regular function
2351          given in full representation (by option (\"ext\",1)) or in
2352          generic representation (default option (\"ext\",0)). The
2353          I-regular function is the corresponding element of the reduced
2354          Groebner basis for each point of the segment with the given lpp.
2355          For each point in the segment, the polynomial or the set of
2356          polynomials representing it, if they do not specialize to 0,
2357          then after normalization, specializes to the corresponding
2358          element of the reduced Groebner basis. In the full representation
2359          at least one of the polynomials representing the I-regular
2360          function specializes to non-zero.
2361
2362          With the default option (\"rep\",0) the representation of the
2363          segment is the P-representation.
2364          With option (\"rep\",1) the representation of the segment is
2365          the C-representation.
2366          With option (\"rep\",2) both representations of the segment are
2367          given.
2368
2369          The P-representation of a segment is of the form
2370          ((p_1,(p_11,..,p_1k1)),..,(p_r,(p_r1,..,p_rkr))
2371          representing the segment Union_i ( V(p_i) \ ( Union_j V(p_ij) ) ),
2372          where the p's are prime ideals.
2373
2374          The C-representation of a segment is of the form
2375          (E,N) representing V(E) \ V(N), and the ideals E and N are
2376          radical and N contains E.
2377
2378NOTE: The basering R, must be of the form Q[a][x], (a=parameters,
2379          x=variables), and should be defined previously. The ideal must
2380          be defined on R.
2381KEYWORDS: Groebner cover, parametric ideal, canonical, discussion of
2382          parametric ideal.
2383EXAMPLE:  grobcov; shows an example"
2384{
2385  list S; int i; int ish=1; list GBR; list BR; int j; int k;
2386  ideal idp; ideal idq; int s; ideal ext; list SS;
2387  ideal E; ideal N; int canop;  int extop; int repop;
2388  int comment=0; int m;
2389  def RR=basering;
2390  setglobalrings();
2391  list L0=#;
2392  int out=0;
2393  L0[size(L0)+1]="res"; L0[size(L0)+1]=ideal(1);
2394  // default options
2395  int start=timer;
2396  E=ideal(0);
2397  N=ideal(1);
2398  canop=1; // canop=0 for homogenizing the basis but not the ideal (not canonical)
2399           // canop=1 for working with the homogenized ideal
2400  repop=0; // repop=0 for representing the segments in Prep
2401           // repop=1 for representing the segments in Crep
2402           // repop=2 for representing the segments in Prep and Crep
2403  extop=0; // extop=0 if only generic representation of the bases are to be computed
2404           // extop=1 if the full representation of the bases are to be computed
2405  for(i=1;i<=size(L0) div 2;i++)
2406  {
2407    if(L0[2*i-1]=="can"){canop=L0[2*i];}
2408    else
2409    {
2410      if(L0[2*i-1]=="ext"){extop=L0[2*i];}
2411      else
2412      {
2413        if(L0[2*i-1]=="rep"){repop=L0[2*i];}
2414        else
2415        {
2416          if(L0[2*i-1]=="null"){E=L0[2*i];}
2417          else
2418          {
2419            if(L0[2*i-1]=="nonnull"){N=L0[2*i];}
2420            else
2421            {
2422              if (L0[2*i-1]=="comment"){comment=L0[2*i];}
2423            }
2424          }
2425        }
2426      }
2427    }
2428  }
2429  if(not((canop==0) or (canop==1)))
2430  {
2431    string("Option can = ",canop," is not supported. It is changed to can = 1");
2432    canop=1;
2433  }
2434  for(i=1;i<=size(L0) div 2;i++)
2435  {
2436    if(L0[2*i-1]=="can"){L0[2*i]=canop;}
2437  }
2438  if ((printlevel) and (comment==0)){comment=printlevel;}
2439  list LL;
2440  LL[1]="can";     LL[2]=canop;
2441  LL[3]="comment"; LL[4]=comment;
2442  LL[5]="out";     LL[6]=0;
2443  LL[7]="null";    LL[8]=E;
2444  LL[9]="nonnull"; LL[10]=N;
2445  LL[11]="ext";    LL[12]=extop;
2446  LL[13]="rep";    LL[14]=repop;
2447  if (comment>=1)
2448  {
2449    string("Begin grobcov with options: ",LL);
2450  }
2451  kill S;
2452  def S=gcover(F,LL);
2453  // NOW extend
2454  if(extop)
2455  {
2456    S=extend(S,LL);
2457  }
2458  else
2459  {
2460    // NOW representation of the segments by option repop
2461    list Si; list nS;
2462    if(repop==0)
2463    {
2464      for(i=1;i<=size(S);i++)
2465      {
2466        Si=list(S[i][1],S[i][2],S[i][3],S[i][5]);
2467        nS[size(nS)+1]=Si;
2468      }
2469      kill S;
2470      def S=nS;
2471    }
2472    else
2473    {
2474      if(repop==1)
2475      {
2476        for(i=1;i<=size(S);i++)
2477        {
2478          Si=list(S[i][1],S[i][2],S[i][4],S[i][5]);
2479          nS[size(nS)+1]=Si;
2480        }
2481        kill S;
2482        def S=nS;
2483      }
2484      else
2485      {
2486        for(i=1;i<=size(S);i++)
2487        {
2488          Si=list(S[i][1],S[i][2],S[i][3],S[i][4],S[i][5]);
2489          nS[size(nS)+1]=Si;
2490        }
2491        kill S;
2492        def S=nS;
2493      }
2494    }
2495  }
2496  if (comment>=1)
2497  {
2498    string("Time in grobcov = ", timer-start);
2499    string("Number of segments of grobcov = ", size(S));
2500  }
2501  if(defined(@P)==1){kill @R; kill @P; kill @RP;}
2502  return(S);
2503}
2504example
2505{
2506  "EXAMPLE:"; echo = 2;
2507  // Casas conjecture for degree 4:
2508  ring R=(0,a0,a1,a2,a3,a4),(x1,x2,x3),dp;
2509  short=0;
2510  ideal F=x1^4+(4*a3)*x1^3+(6*a2)*x1^2+(4*a1)*x1+(a0),
2511            x1^3+(3*a3)*x1^2+(3*a2)*x1+(a1),
2512            x2^4+(4*a3)*x2^3+(6*a2)*x2^2+(4*a1)*x2+(a0),
2513            x2^2+(2*a3)*x2+(a2),
2514            x3^4+(4*a3)*x3^3+(6*a2)*x3^2+(4*a1)*x3+(a0),
2515            x3+(a3);
2516  grobcov(F);
2517}
2518
2519// Input. GC the grobcov of an ideal in generic representation of the
2520//        bases computed with option option ("rep",2).
2521// Output The grobcov in full representation.
2522// Option ("comment",1) shows the time.
2523// Can be called from the top
2524proc extend(list GC, list #);
2525"USAGE: extend(GC); The default option of grobcov provides
2526          the bases in generic representation (the I-regular functions
2527          of the bases ara given by a single polynomial. It can specialize
2528          to zero for some points of the segments, but in general, it
2529          is sufficient for many pouposes. Nevertheless the I-regular
2530          functions allow a full representation given bey a set of
2531          polynomials specializing to the value of the function (after normalization)
2532          or to zero, but at least one of the polynomials specializes to non-zero.
2533          The full representation can be obtained by computing the
2534          grobcov with option \"ext\",1. The default option is \"ext\",0.
2535          With option \"ext\",1 the computation can be much more
2536          time consuming, even if the result can be simpler.
2537          Alternatively, one can compute the full representation of the
2538          bases after computing grobcov with the defaoult option \"ext\",0
2539          and the option \"rep\",2, that outputs both the Prep and the Crep
2540          of the segments and then call \"extend\" to the output.
2541
2542RETURN: When calling extend(grobcov(S,\"rep\",2)) the result is of the form
2543              (
2544                 (lpp_1,basis_1,segment_1,lpph_1),
2545                  ...
2546                 (lpp_s,basis_s,segment_s,lpph_s)
2547              )
2548          where each function of the basis can be given by an ideal
2549          of representants.
2550
2551NOTE: The basering R, must be of the form Q[a][x], (a=parameters,
2552          x=variables), and should be defined previously. The ideal must
2553          be defined on R.
2554KEYWORDS: Groebner cover, parametric ideal, canonical, discussion of
2555          parametric ideal, full representation.
2556EXAMPLE:  extend; shows an example"
2557{
2558  list L=#;
2559  list S=GC;
2560  ideal idp;
2561  ideal idq;
2562  int i; int j; int m; int s;
2563  m=0; i=1;
2564  while((i<=size(S)) and (m==0))
2565  {
2566    if(typeof(S[i][2])=="list"){m=1;}
2567    i++;
2568  }
2569  if(m==1){"Warning! grobcov has already extended bases"; return(S);}
2570  if(size(GC[1])!=5){"Warning! extend make sense only when grobcov has been called with options  'rep',2,'ext',0"; " "; return();}
2571  int repop=0;
2572  int start3=timer;
2573  int comment;
2574  for(i=1;i<=size(L) div 2;i++)
2575  {
2576    if(L[2*i-1]=="comment"){comment=L[2*i];}
2577    else
2578    {
2579      if(L[2*i-1]=="rep"){repop=L[2*i];}
2580    }
2581  }
2582  poly leadc;
2583  poly ext;
2584  int te=0;
2585  list SS;
2586  def R=basering;
2587  if (defined(@R)){te=1;}
2588  else{setglobalrings();}
2589  // Now extend
2590  for (i=1;i<=size(S);i++)
2591  {
2592    m=size(S[i][2]);
2593     for (j=1;j<=m;j++)
2594    {
2595      idp=S[i][4][1];
2596      idq=S[i][4][2];
2597      if (size(idp)>0)
2598      {
2599        leadc=leadcoef(S[i][2][j]);
2600        kill ext;
2601        def ext=extend0(S[i][2][j],idp,idq);
2602        if (typeof(ext)=="poly")
2603        {
2604          S[i][2][j]=pnormalf(ext,idp,idq);
2605        }
2606        else
2607        {
2608          if(size(ext)==1)
2609          {
2610            S[i][2][j]=ext[1];
2611          }
2612          else
2613          {
2614            kill SS; list SS;
2615            for(s=1;s<=size(ext);s++)
2616            {
2617              ext[s]=pnormalf(ext[s],idp,idq);
2618            }
2619            for(s=1;s<=size(S[i][2]);s++)
2620            {
2621              if(s!=j){SS[s]=S[i][2][s];}
2622              else{SS[s]=ext;}
2623            }
2624            S[i][2]=SS;
2625          }
2626        }
2627      }
2628    }
2629  }
2630  // NOW representation of the segments by option repop
2631  list Si; list nS;
2632  if (repop==0)
2633  {
2634    for(i=1;i<=size(S);i++)
2635    {
2636      Si=list(S[i][1],S[i][2],S[i][3],S[i][5]);
2637      nS[size(nS)+1]=Si;
2638    }
2639    S=nS;
2640  }
2641  else
2642  {
2643    if (repop==1)
2644    {
2645      for(i=1;i<=size(S);i++)
2646      {
2647        Si=list(S[i][1],S[i][2],S[i][4],S[i][5]);
2648        nS[size(nS)+1]=Si;
2649      }
2650      S=nS;
2651    }
2652    else
2653    {
2654      for(i=1;i<=size(S);i++)
2655      {
2656        Si=list(S[i][1],S[i][2],S[i][3],S[i][4],S[i][5]);
2657        nS[size(nS)+1]=Si;
2658      }
2659
2660    }
2661  }
2662  if(comment>=1){string("Time in extend = ",timer-start3);}
2663  if(te==0){kill @R; kill @RP; kill @P;}
2664  return(S);
2665}
2666example
2667{
2668  "EXAMPLE:"; echo = 2;
2669  ring R=(0,a0,b0,c0,a1,b1,c1),(x), dp;
2670  short=0;
2671  ideal S=a0*x^2+b0*x+c0,
2672            a1*x^2+b1*x+c1;
2673  def GCS=grobcov(S,"rep",2);
2674  GCS;
2675  def FGC=extend(GCS,"rep",0);
2676  // Full representation=
2677  FGC;
2678}
2679
2680// Auxiliary routine
2681// nonzerodivisor
2682// input:
2683//    poly g in Q[a],
2684//    list P=(p_1,..p_r) representing a minimal prime decomposition
2685// output
2686//    poly f such that f notin p_i for all i and
2687//           g-f in p_i for all i such that g notin p_i
2688static proc nonzerodivisor(poly gr, list Pr)
2689{
2690  def RR=basering;
2691  setring(@P);
2692  def g=imap(RR,gr);
2693  def P=imap(RR,Pr);
2694  int i; int k;  list J; ideal F;
2695  def f=g;
2696  ideal Pi;
2697  for (i=1;i<=size(P);i++)
2698  {
2699    option(redSB);
2700    Pi=std(P[i]);
2701    //attrib(Pi,"isSB",1);
2702    if (reduce(g,Pi,1)==0){J[size(J)+1]=i;}
2703  }
2704  for (i=1;i<=size(J);i++)
2705  {
2706    F=ideal(1);
2707    for (k=1;k<=size(P);k++)
2708    {
2709      if (k!=J[i])
2710      {
2711        F=idint(F,P[k]);
2712      }
2713    }
2714    f=f+F[1];
2715  }
2716  setring(RR);
2717  def fr=imap(@P,f);
2718  return(fr);
2719}
2720
2721// Auxiliary routine
2722// deltai
2723// input:
2724//   int i:
2725//   list LPr: (p1,..,pr) of prime components of an ideal in Q[a]
2726// output:
2727//   list (fr,fnr) of two polynomials that are equal on V(pi)
2728//       and fr=0 on V(P) \ V(pi), and fnr is nonzero on V(pj) for all j.
2729static proc deltai(int i, list LPr)
2730{
2731  def RR=basering;
2732  setring(@P);
2733  def LP=imap(RR,LPr);
2734  int j; poly p;
2735  def F=ideal(1);
2736  poly f;
2737  poly fn;
2738  ideal LPi;
2739  for (j=1;j<=size(LP);j++)
2740  {
2741    if (j!=i)
2742    {
2743      F=idint(F,LP[j]);
2744    }
2745  }
2746  p=0; j=1;
2747  while ((p==0) and (j<=size(F)))
2748  {
2749    LPi=LP[i];
2750    attrib(LPi,"isSB",1);
2751    p=reduce(F[j],LPi);
2752    j++;
2753  }
2754  f=F[j-1];
2755  fn=nonzerodivisor(f,LP);
2756  setring(RR);
2757  def fr=imap(@P,f);
2758  def fnr=imap(@P,fn);
2759  return(list(fr,fnr));
2760}
2761
2762// Auxiliary routine
2763// combine
2764// input: a list of pairs ((p1,P1),..,(pr,Pr)) where
2765//    ideal pi is a prime component
2766//    poly Pi is the polynomial in Q[a][x] on V(pi)\ V(Mi)
2767//    (p1,..,pr) are the prime decomposition of the lpp-segment
2768//    list crep =(ideal ida,ideal idb): the Crep of the segment.
2769//    list Pci of the intersecctions of all pj except the ith one
2770// output:
2771//    poly P on an open and dense set of V(p_1 int ... p_r)
2772static proc combine(list L, ideal F)
2773{
2774  // ATTENTION REVISE AND USE Pci and F
2775  int i; poly f;
2776  f=0;
2777  for(i=1;i<=size(L);i++)
2778  {
2779    f=f+F[i]*L[i][2];
2780  }
2781//   f=elimconstfac(f);
2782  f=primepartZ(f);
2783  return(f);
2784}
2785
2786
2787//Auxiliary routine
2788// nullin
2789// input:
2790//   poly f:  a polynomial in Q[a]
2791//   ideal P: an ideal in Q[a]
2792//   called from ring @R
2793// output:
2794//   t:  with value 1 if f reduces modulo P, 0 if not.
2795static proc nullin(poly f,ideal P)
2796{
2797  int t;
2798  def RR=basering;
2799  setring(@P);
2800  def f0=imap(RR,f);
2801  def P0=imap(RR,P);
2802  attrib(P0,"isSB",1);
2803  if (reduce(f0,P0,1)==0){t=1;}
2804  else{t=0;}
2805  setring(RR);
2806  return(t);
2807}
2808
2809// Auxiliary routine
2810// monoms
2811// Input: A polynomial f
2812// Output: The list of leading terms
2813static proc monoms(poly f)
2814{
2815  list L;
2816  poly lm; poly lc; poly lp; poly Q; poly mQ;
2817  def p=f;
2818  int i=1;
2819  while (p!=0)
2820  {
2821    lm=lead(p);
2822    p=p-lm;
2823    lc=leadcoef(lm);
2824    lp=leadmonom(lm);
2825    L[size(L)+1]=list(lc,lp);
2826    i++;
2827  }
2828  return(L);
2829}
2830
2831// Auxiliary routine called by extend
2832// extend0
2833// input:
2834//   poly f: a generic polynomial in the basis
2835//   ideal idp: such that ideal(S)=idp
2836//   ideal idq: such that S=V(idp) \ V(idq)
2837////   NW the list of ((N1,W1),..,(Ns,Ws)) of red-rep of the grouped
2838////      segments in the lpp-segment  NO MORE USED
2839// output:
2840static proc extend0(poly f, ideal idp, ideal idq)
2841{
2842  matrix CC; poly Q; list NewMonoms;
2843  int i;  int j;  poly fout; ideal idout;
2844  list L=monoms(f);
2845  int nummonoms=size(L)-1;
2846  Q=L[1][1];
2847  if (nummonoms==0){return(f);}
2848  for (i=2;i<=size(L);i++)
2849  {
2850    CC=matrix(extendcoef(L[i][1],Q,idp,idq));
2851    NewMonoms[i-1]=list(CC,L[i][2]);
2852  }
2853  if (nummonoms==1)
2854  {
2855    for(j=1;j<=ncols(NewMonoms[1][1]);j++)
2856    {
2857      fout=NewMonoms[1][1][2,j]*L[1][2]+NewMonoms[1][1][1,j]*NewMonoms[1][2];
2858      //fout=pnormalf(fout,idp,W);
2859      if(ncols(NewMonoms[1][1])>1){idout[j]=fout;}
2860    }
2861    if(ncols(NewMonoms[1][1])==1){return(fout);} else{return(idout);}
2862  }
2863  else
2864  {
2865    list cfi;
2866    list coefs;
2867    for (i=1;i<=nummonoms;i++)
2868    {
2869      kill cfi; list cfi;
2870      for(j=1;j<=ncols(NewMonoms[i][1]);j++)
2871      {
2872        cfi[size(cfi)+1]=NewMonoms[i][1][2,j];
2873      }
2874      coefs[i]=cfi;
2875    }
2876    def indexpolys=findindexpolys(coefs);
2877    for(i=1;i<=size(indexpolys);i++)
2878    {
2879      fout=L[1][2];
2880      for(j=1;j<=nummonoms;j++)
2881      {
2882        fout=fout+(NewMonoms[j][1][1,indexpolys[i][j]])/(NewMonoms[j][1][2,indexpolys[i][j]])*NewMonoms[j][2];
2883      }
2884      fout=cleardenom(fout);
2885      if(size(indexpolys)>1){idout[i]=fout;}
2886    }
2887    if (size(indexpolys)==1){return(fout);} else{return(idout);}
2888  }
2889}
2890
2891// Auxiliary routine
2892// findindexpolys
2893// input:
2894//   list coefs=( (q11,..,q1r_1),..,(qs1,..,qsr_1) )
2895//               of denominators of the monoms
2896// output:
2897//   list ind=(v_1,..,v_t) of intvec
2898//        each intvec v=(i_1,..,is) corresponds to a polynomial in the sheaf
2899//        that will be built from it in extend procedure.
2900static proc findindexpolys(list coefs)
2901{
2902  int i; int j; intvec numdens;
2903  for(i=1;i<=size(coefs);i++)
2904  {
2905    numdens[i]=size(coefs[i]);
2906  }
2907  def RR=basering;
2908  setring(@P);
2909  def coefsp=imap(RR,coefs);
2910  ideal cof; list combpolys; intvec v; int te; list mp;
2911  for(i=1;i<=size(coefsp);i++)
2912  {
2913    cof=ideal(0);
2914    for(j=1;j<=size(coefsp[i]);j++)
2915    {
2916      cof[j]=factorize(coefsp[i][j],3);
2917    }
2918    coefsp[i]=cof;
2919  }
2920  for(j=1;j<=size(coefsp[1]);j++)
2921  {
2922    v[1]=j;
2923    te=1;
2924    for (i=2;i<=size(coefsp);i++)
2925    {
2926      mp=memberpos(coefsp[1][j],coefsp[i]);
2927      if(mp[1])
2928      {
2929        v[i]=mp[2];
2930      }
2931      else{v[i]=0;}
2932    }
2933    combpolys[j]=v;
2934  }
2935  combpolys=reform(combpolys,numdens);
2936  setring(RR);
2937  return(combpolys);
2938}
2939
2940// Auxiliary routine
2941// extendcoef: given Q,P in Q[a] where P/Q specializes on an open and dense subset
2942//      of the whole V(p1 int...int pr), it returns a basis of the module
2943//      of all syzygies equivalent to P/Q,
2944static proc extendcoef(poly P, poly Q, ideal idp, ideal idq)
2945{
2946  def RR=basering;
2947  setring(@P);
2948  def PL=ringlist(@P);
2949  PL[3][1][1]="dp";
2950  def P1=ring(PL);
2951  setring(P1);
2952  ideal idp0=imap(RR,idp);
2953  option(redSB);
2954  qring q=std(idp0);
2955  poly P0=imap(RR,P);
2956  poly Q0=imap(RR,Q);
2957  ideal PQ=Q0,-P0;
2958  module C=syz(PQ);
2959  setring(@P);
2960  def idp1=imap(RR,idp);
2961  def idq1=imap(RR,idq);
2962  def C1=matrix(imap(q,C));
2963  def redC=selectregularfun(C1,idp1,idq1);
2964  setring(RR);
2965  def CC=imap(@P,redC);
2966  return(CC);
2967}
2968
2969// Auxiliary routine
2970// selectregularfun
2971// input:
2972//   list L of the polynomials matrix CC
2973//      (we assume that one of them is non-null on V(N) \ V(M))
2974//   ideal N, ideal M: ideals representing the locally closed set V(N) \ V(M)
2975// assume to work in @P
2976static proc selectregularfun(matrix CC, ideal NN, ideal MM)
2977{
2978  int numcombused;
2979  def RR=basering;
2980  setring(@P);
2981  def C=imap(RR,CC);
2982  def N=imap(RR,NN);
2983  def M=imap(RR,MM);
2984  if (ncols(C)==1){return(C);}
2985
2986  int i; int j; int k; list c; intvec ci; intvec c0; intvec c1;
2987  list T; list T0; list T1; list LL; ideal N1;ideal M1; int te=0;
2988  for(i=1;i<=ncols(C);i++)
2989  {
2990    if((C[1,i]!=0) and (C[2,i]!=0))
2991    {
2992      if(c0==intvec(0)){c0[1]=i;}
2993      else{c0[size(c0)+1]=i;}
2994    }
2995  }
2996  def C1=submat(C,1..2,c0);
2997  for (i=1;i<=ncols(C1);i++)
2998  {
2999    c=comb(ncols(C1),i);
3000    for(j=1;j<=size(c);j++)
3001    {
3002      ci=c[j];
3003      numcombused++;
3004      if(i==1){N1=N+C1[2,j]; M1=M;}
3005      if(i>1)
3006      {
3007        kill c0; intvec c0 ; kill c1; intvec c1;
3008        c1=ci[size(ci)];
3009        for(k=1;k<size(ci);k++){c0[k]=ci[k];}
3010        T0=searchinlist(c0,LL);
3011        T1=searchinlist(c1,LL);
3012        N1=T0[1]+T1[1];
3013        M1=intersect(T0[2],T1[2]);
3014      }
3015      T=list(ci,PtoCrep(Prep(N1,M1)));
3016      LL[size(LL)+1]=T;
3017      if(equalideals(T[2][1],ideal(1))){te=1; break;}
3018    }
3019    if(te){break;}
3020  }
3021  ci=T[1];
3022  def Cs=submat(C1,1..2,ci);
3023  setring(RR);
3024  return(imap(@P,Cs));
3025}
3026
3027// Auxiliary routine
3028// searchinlist
3029// input:
3030//   intvec c:
3031//   list L=( (c1,T1),..(ck,Tk) )
3032//      where the c's are assumed to be intvects
3033// output:
3034//   object T with index c
3035static proc searchinlist(intvec c,list L)
3036{
3037  int i; list T;
3038  for(i=1;i<=size(L);i++)
3039  {
3040    if (L[i][1]==c)
3041    {
3042      T=L[i][2];
3043      break;
3044    }
3045  }
3046  return(T);
3047}
3048
3049
3050// Auxiliary routine
3051// selectminsheaves
3052// Input: L=((v_11,..,v_1k_1),..,(v_s1,..,v_sk_s))
3053//    where:
3054//    The s lists correspond to the s coefficients of the polynomial f
3055//    (v_i1,..,v_ik_i) correspond to the k_i intvec v_ij of the
3056//    spezializations of the jth rekpresentant (Q,P) of the ith coefficient
3057//    v_ij is an intvec of size equal to the number of little segments
3058//    forming the lpp-segment of 0,1, where 1 represents that it specializes
3059//    to non-zedro an the whole little segment and 0 if not.
3060// Output: S=(w_1,..,w_j)
3061//    where the w_l=(n_l1,..,n_ls) are intvec of length size(L), where
3062//    n_lt fixes which element of (v_t1,..,v_tk_t) is to be
3063//    choosen to form the tth (Q,P) for the lth element of the sheaf
3064//    representing the I-regular function.
3065// The selection is done to obtian the minimal number of elements
3066//    of the sheaf that specializes to non-null everywhere.
3067static proc selectminsheaves(list L)
3068{
3069  list C=allsheaves(L);
3070  return(smsheaves(C[1],C[2]));
3071}
3072
3073// Auxiliary routine
3074// smsheaves
3075// Input:
3076//   list C of all the combrep
3077//   list L of the intvec that correesponds to each element of C
3078// Output:
3079//   list LL of the subsets of C that cover all the subsegments
3080//   (the union of the corresponding L(C) has all 1).
3081static proc smsheaves(list C, list L)
3082{
3083  int i; int i0; intvec W;
3084  int nor; int norn;
3085  intvec p;
3086  int sp=size(L[1]); int j0=1;
3087  for (i=1;i<=sp;i++){p[i]=1;}
3088  while (p!=0)
3089  {
3090    i0=0; nor=0;
3091    for (i=1; i<=size(L); i++)
3092    {
3093      norn=numones(L[i],pos(p));
3094      if (nor<norn){nor=norn; i0=i;}
3095    }
3096    W[j0]=i0;
3097    j0++;
3098    p=actualize(p,L[i0]);
3099  }
3100  list LL;
3101  for (i=1;i<=size(W);i++)
3102  {
3103    LL[size(LL)+1]=C[W[i]];
3104  }
3105  return(LL);
3106}
3107
3108// Auxiliary routine
3109// allsheaves
3110// Input: L=((v_11,..,v_1k_1),..,(v_s1,..,v_sk_s))
3111//    where:
3112//    The s lists correspond to the s coefficients of the polynomial f
3113//    (v_i1,..,v_ik_i) correspond to the k_i intvec v_ij of the
3114//    spezializations of the jth rekpresentant (Q,P) of the ith coefficient
3115//    v_ij is an intvec of size equal to the number of little segments
3116//    forming the lpp-segment of 0,1, where 1 represents that it specializes
3117//    to non-zero on the whole little segment and 1 if not.
3118// Output:
3119//    (list LL, list LLS)  where
3120//    LL is the list of all combrep
3121//    LLS is the list of intvec of the corresponding elements of LL
3122static proc allsheaves(list L)
3123{
3124  intvec V; list LL; intvec W; int r; intvec U;
3125  int i; int j; int k;
3126  int s=size(L[1][1]); // s = number of little segments of the lpp-segment
3127  list LLS;
3128  for (i=1;i<=size(L);i++)
3129  {
3130    V[i]=size(L[i]);
3131  }
3132  LL=combrep(V);
3133  for (i=1;i<=size(LL);i++)
3134  {
3135    W=LL[i];   // size(W)= number of coefficients of the polynomial
3136    kill U; intvec U;
3137    for (j=1;j<=s;j++)
3138    {
3139      k=1; r=1; U[j]=1;
3140      while((r==1) and (k<=size(W)))
3141      {
3142        if(L[k][W[k]][j]==0){r=0; U[j]=0;}
3143        k++;
3144      }
3145    }
3146    LLS[i]=U;
3147  }
3148  return(list(LL,LLS));
3149}
3150
3151// Auxiliary routine
3152// numones
3153// Input:
3154//   intvec v of (0,1) in each position
3155//   intvec pos: the positions to test
3156// Output:
3157//   int nor: the nuber of 1 of v in the positions given by pos.
3158static proc numones(intvec v, intvec pos)
3159{
3160  int i; int n;
3161  for (i=1;i<=size(pos);i++)
3162  {
3163    if (v[pos[i]]==1){n++;}
3164  }
3165  return(n);
3166}
3167
3168// Auxiliary routine
3169// actualize: actualizes zeroes of p
3170// Input:
3171//   intvec p: of zeroes and ones
3172//   intvec c: of zeroes and ones (of the same length)
3173// Output;
3174//   intvec pp: of zeroes and ones, where a 0 stays in pp[i] if either
3175//   already p[i]==0 or c[i]==1.
3176static proc actualize(intvec p, intvec c)
3177{
3178  int i; intvec pp=p;
3179  for (i=1;i<=size(p);i++)
3180  {
3181    if ((pp[i]==1) and (c[i]==1)){pp[i]=0;}
3182  }
3183  return(pp);
3184}
3185
3186
3187// Auxiliary routine
3188static proc reducemodN(poly f,ideal E)
3189{
3190  def RR=basering;
3191  setring(@RPt);
3192  def fa=imap(RR,f);
3193  def Ea=imap(RR,E);
3194  attrib(Ea,"isSB",1);
3195  // option(redSB);
3196  // Ea=std(Ea);
3197  fa=reduce(fa,Ea);
3198  setring(RR);
3199  def f1=imap(@RPt,fa);
3200  return(f1);
3201}
3202
3203// Auxiliary routine
3204// intersp: computes the intersection of the ideals in S in @P
3205static proc intersp(list S)
3206{
3207  def RR=basering;
3208  setring(@P);
3209  def SP=imap(RR,S);
3210  option(returnSB);
3211  def NP=intersect(SP[1..size(SP)]);
3212  setring(RR);
3213  return(imap(@P,NP));
3214}
3215
3216// Auxiliary routine
3217// radicalmember
3218static proc radicalmember(poly f,ideal ida)
3219{
3220  int te;
3221  def RR=basering;
3222  setring(@P);
3223  def fp=imap(RR,f);
3224  def idap=imap(RR,ida);
3225  poly @t;
3226  ring H=0,@t,dp;
3227  def PH=@P+H;
3228  setring(PH);
3229  def fH=imap(@P,fp);
3230  def idaH=imap(@P,idap);
3231  idaH[size(idaH)+1]=1-@t*fH;
3232  option(redSB);
3233  def G=std(idaH);
3234  if (G==1){te=1;} else {te=0;}
3235  setring(RR);
3236  return(te);
3237}
3238
3239// // Auxiliary routine
3240// // NonNull: returns 1 if the poly f is nonnull on V(E) \ V(N), 0 otherwise.
3241// // Input:
3242// //   f: polynomial
3243// //   E: null ideal
3244// //   N: nonnull ideal
3245// // Output:
3246// //   1 if f is nonnul in V(P) \ V(Q),
3247// //   0 if it has zeroes inside.
3248// //  Works in @P
3249// proc NonNull(poly f, ideal E, ideal N)
3250// {
3251//   int te=1; int i;
3252//   def RR=basering;
3253//   setring(@P);
3254//   def fp=imap(RR,f);
3255//   def Ep=imap(RR,E);
3256//   def Np=imap(RR,N);
3257//   ideal H;
3258//   ideal Ef=Ep+fp;
3259//   for (i=1;i<=size(Np);i++)
3260//   {
3261//     te=radicalmember(Np[i],Ef);
3262//     if (te==0){break;}
3263//   }
3264//   setring(RR);
3265//   return(te);
3266// }
3267
3268// Auxiliary routine
3269// selectextendcoef
3270// input:
3271//    matrix CC: CC=(p_a1 .. p_ar_a)
3272//                  (q_a1 .. q_ar_a)
3273//            the matrix of elements of a coefficient in oo[a].
3274//    (ideal ida, ideal idb): the canonical representation of the segment S.
3275// output:
3276//    list caout
3277//            the minimum set of elements of CC needed such that at least one
3278//            of the q's is non-null on S, as well as the C-rep of of the
3279//            points where the q's are null on S.
3280//            The elements of caout are of the form (p,q,prep);
3281static proc selectextendcoef(matrix CC, ideal ida, ideal idb)
3282{
3283  def RR=basering;
3284  setring(@P);
3285  def ca=imap(RR,CC);
3286  def E0=imap(RR,ida);
3287  ideal E;
3288  def N=imap(RR,idb);
3289  int r=ncols(ca);
3290  int i; int te=1; list com; int j; int k; intvec c; list prep;
3291  list cs; list caout;
3292  i=1;
3293  while ((i<=r) and (te))
3294  {
3295    com=comb(r,i);
3296    j=1;
3297    while((j<=size(com)) and (te))
3298    {
3299      E=E0;
3300      c=com[j];
3301      for (k=1;k<=i;k++)
3302      {
3303        E=E+ca[2,c[k]];
3304      }
3305      prep=Prep(E,N);
3306      if (i==1)
3307      {
3308        cs[j]=list(ca[1,j],ca[2,j],prep);
3309      }
3310      if ((size(prep)==1) and (equalideals(prep[1][1],ideal(1))))
3311      {
3312        te=0;
3313        for(k=1;k<=size(c);k++)
3314        {
3315          caout[k]=cs[c[k]];
3316        }
3317      }
3318      j++;
3319    }
3320    i++;
3321  }
3322  if (te){"error: extendcoef does not extend to the whole S";}
3323  setring(RR);
3324  return(imap(@P,caout));
3325}
3326
3327// Auxiliary routine
3328// plusP
3329// Input:
3330//   ideal E1: in some basering (depends only on the parameters)
3331//   ideal E2: in some basering (depends only on the parameters)
3332// Output:
3333//   ideal Ep=E1+E2; computed in @P
3334static proc plusP(ideal E1,ideal E2)
3335{
3336  def RR=basering;
3337  setring(@P);
3338  def E1p=imap(RR,E1);
3339  def E2p=imap(RR,E2);
3340  def Ep=E1p+E2p;
3341  setring(RR);
3342  return(imap(@P,Ep));
3343}
3344
3345// Auxiliary routine
3346// reform
3347// input:
3348//   list combpolys: (v1,..,vs)
3349//      where vi are intvec.
3350//   output outcomb: (w1,..,wt)
3351//      whre wi are intvec.
3352//      All the vi without zeroes are in outcomb, and those with zeroes are
3353//         combined to form new intvec with the rest
3354static proc reform(list combpolys, intvec numdens)
3355{
3356  list combp0; list combp1; int i; int j; int k; int l; list rest; intvec notfree;
3357  list free; intvec free1; int te; intvec v;  intvec w;
3358  int nummonoms=size(combpolys[1]);
3359  for(i=1;i<=size(combpolys);i++)
3360  {
3361    if(memberpos(0,combpolys[i])[1])
3362    {
3363      combp0[size(combp0)+1]=combpolys[i];
3364    }
3365    else {combp1[size(combp1)+1]=combpolys[i];}
3366  }
3367  for(i=1;i<=nummonoms;i++)
3368  {
3369    kill notfree; intvec notfree;
3370    for(j=1;j<=size(combpolys);j++)
3371    {
3372      if(combpolys[j][i]<>0)
3373      {
3374        if(notfree[1]==0){notfree[1]=combpolys[j][i];}
3375        else{notfree[size(notfree)+1]=combpolys[j][i];}
3376      }
3377    }
3378    kill free1; intvec free1;
3379    for(j=1;j<=numdens[i];j++)
3380    {
3381      if(memberpos(j,notfree)[1]==0)
3382      {
3383        if(free1[1]==0){free1[1]=j;}
3384        else{free1[size(free1)+1]=j;}
3385      }
3386      free[i]=free1;
3387    }
3388  }
3389  list amplcombp; list aux;
3390  for(i=1;i<=size(combp0);i++)
3391  {
3392    v=combp0[i];
3393    kill amplcombp; list amplcombp;
3394    amplcombp[1]=intvec(v[1]);
3395    for(j=2;j<=size(v);j++)
3396    {
3397      if(v[j]!=0)
3398      {
3399        for(k=1;k<=size(amplcombp);k++)
3400        {
3401          w=amplcombp[k];
3402          w[size(w)+1]=v[j];
3403          amplcombp[k]=w;
3404        }
3405      }
3406      else
3407      {
3408        kill aux; list aux;
3409        for(k=1;k<=size(amplcombp);k++)
3410        {
3411          for(l=1;l<=size(free[j]);l++)
3412          {
3413            w=amplcombp[k];
3414            w[size(w)+1]=free[j][l];
3415            aux[size(aux)+1]=w;
3416          }
3417        }
3418        amplcombp=aux;
3419      }
3420    }
3421    for(j=1;j<=size(amplcombp);j++)
3422    {
3423      combp1[size(combp1)+1]=amplcombp[j];
3424    }
3425  }
3426  return(combp1);
3427}
3428
3429
3430// Auxiliary routine
3431// precombint
3432// input:  L: list of ideals (works in @P)
3433// output: F0: ideal of polys. F0[i] is a poly in the intersection of
3434//             all ideals in L except in the ith one, where it is not.
3435//             L=(p1,..,ps);  F0=(f1,..,fs);
3436//             F0[i] \in intersect_{j#i} p_i
3437static proc precombint(list L)
3438{
3439  int i; int j; int tes;
3440  def RR=basering;
3441  setring(@P);
3442  list L0; list L1; list L2; list L3; ideal F;
3443  L0=imap(RR,L);
3444  L1[1]=L0[1]; L2[1]=L0[size(L0)];
3445  for (i=2;i<=size(L0)-1;i++)
3446  {
3447    L1[i]=intersect(L1[i-1],L0[i]);
3448    L2[i]=intersect(L2[i-1],L0[size(L0)-i+1]);
3449  }
3450  L3[1]=L2[size(L2)];
3451  for (i=2;i<=size(L0)-1;i++)
3452  {
3453    L3[i]=intersect(L1[i-1],L2[size(L0)-i]);
3454  }
3455  L3[size(L0)]=L1[size(L1)];
3456  for (i=1;i<=size(L3);i++)
3457  {
3458    option(redSB); L3[i]=std(L3[i]);
3459  }
3460  for (i=1;i<=size(L3);i++)
3461  {
3462    tes=1; j=0;
3463    while((tes) and (j<size(L3[i])))
3464    {
3465      j++;
3466      option(redSB);
3467      L0[i]=std(L0[i]);
3468      if(reduce(L3[i][j],L0[i])!=0){tes=0; F[i]=L3[i][j];}
3469    }
3470    if (tes){"ERROR a polynomial in all p_j except p_i was not found";}
3471  }
3472  setring(RR);
3473  def F0=imap(@P,F);
3474  return(F0);
3475}
3476
3477
3478// Auxiliary routine
3479// minAssGTZ eliminating denominators
3480static proc minGTZ(ideal N);
3481{
3482  int i; int j;
3483  def L=minAssGTZ(N);
3484  for(i=1;i<=size(L);i++)
3485  {
3486    for(j=1;j<=size(L[i]);j++)
3487    {
3488      L[i][j]=cleardenom(L[i][j]);
3489    }
3490  }
3491  return(L);
3492}
3493
3494//********************* Begin KapurSunWang *************************
3495
3496// Auxiliary routine
3497// inconsistent
3498// Input:
3499//   ideal E: of null conditions
3500//   ideal N: of non-null conditions representing V(E) \ V(N)
3501// Output:
3502//   1 if V(E) \ V(N) = empty
3503//   0 if not
3504static proc inconsistent(ideal E, ideal N)
3505{
3506  int j;
3507  int te=1;
3508  def R=basering;
3509  setring(@P);
3510  def EP=imap(R,E);
3511  def NP=imap(R,N);
3512  poly @t;
3513  ring H=0,@t,dp;
3514  def RH=@P+H;
3515  setring(RH);
3516  def EH=imap(@P,EP);
3517  def NH=imap(@P,NP);
3518  ideal G;
3519  j=1;
3520  while((te==1) and j<=size(NH))
3521  {
3522    G=EH+(1-@t*NH[j]);
3523    option(redSB);
3524    G=std(G);
3525    if (G[1]!=1){te=0;}
3526    j++;
3527  }
3528  setring(R);
3529  return(te);
3530}
3531
3532// Auxiliary routine
3533// MDBasis: Minimal Dickson Basis
3534static proc MDBasis(ideal G)
3535{
3536  int i; int j; int te=1;
3537  G=sortideal(G);
3538  ideal MD=G[1];
3539  poly lm;
3540  for (i=2;i<=size(G);i++)
3541  {
3542    te=1;
3543    lm=leadmonom(G[i]);
3544    j=1;
3545    while ((te==1) and (j<=size(MD)))
3546    {
3547      if (lm/leadmonom(MD[j])!=0){te=0;}
3548      j++;
3549    }
3550    if (te==1)
3551    {
3552      MD[size(MD)+1]=(G[i]);
3553    }
3554  }
3555  return(MD);
3556}
3557
3558// Auxiliary routine
3559// primepartZ
3560static proc primepartZ(poly f);
3561{
3562  def cp=content(f);
3563  def fp=f/cp;
3564  return(fp);
3565}
3566
3567// LCMLC
3568static proc LCMLC(ideal H)
3569{
3570  int i;
3571  def R=basering;
3572  setring(@RP);
3573  def HH=imap(R,H);
3574  poly h=1;
3575  for (i=1;i<=size(HH);i++)
3576  {
3577    h=lcm(h,HH[i]);
3578  }
3579  setring(R);
3580  def hh=imap(@RP,h);
3581  return(hh);
3582}
3583
3584// KSW: Kapur-Sun-Wang algorithm for computing a CGS
3585// Input:
3586//   F:   parametric ideal to be discussed
3587//   Options:
3588//     \"out\",0 Transforms the description of the segments into
3589//     canonical P-representation form.
3590//     \"out\",1 Original KSW routine describing the segments as
3591//     difference of varieties
3592//   The ideal must be defined on C[parameters][variables]
3593// Output:
3594//   With option \"out\",0 :
3595//     ((lpp,
3596//       (1,B,((p_1,(p_11,..,p_1k_1)),..,(p_s,(p_s1,..,p_sk_s)))),
3597//       string(lpp)
3598//      )
3599//      ,..,
3600//      (lpp,
3601//       (k,B,((p_1,(p_11,..,p_1k_1)),..,(p_s,(p_s1,..,p_sk_s)))),
3602//       string(lpp))
3603//      )
3604//     )
3605//   With option \"out\",1 ((default, original KSW) (shorter to be computed,
3606//                    but without canonical description of the segments.
3607//     ((B,E,N),..,(B,E,N))
3608static proc KSW(ideal F, list #)
3609{
3610  setglobalrings();
3611  int start=timer;
3612  ideal E=ideal(0);
3613  ideal N=ideal(1);
3614  int comment=0;
3615  int out=1;
3616  int i;
3617  def L=#;
3618  if (size(L)>0)
3619  {
3620    for (i=1;i<=size(L) div 2;i++)
3621    {
3622      if (L[2*i-1]=="null"){E=L[2*i];}
3623      else
3624      {
3625        if (L[2*i-1]=="nonnull"){N=L[2*i];}
3626        else
3627        {
3628          if (L[2*i-1]=="comment"){comment=L[2*i];}
3629          else
3630          {
3631            if (L[2*i-1]=="out"){out=L[2*i];}
3632          }
3633        }
3634      }
3635    }
3636  }
3637  if (comment>0){string("Begin KSW with null = ",E," nonnull = ",N);}
3638  def CG=KSW0(F,E,N,comment);
3639  if (comment>0)
3640  {
3641    string("Number of segments in KSW (total) = ",size(CG));
3642    string("Time in KSW = ",timer-start);
3643  }
3644  if(out==0)
3645  {
3646    CG=KSWtocgsdr(CG);
3647    CG=groupKSWsegments(CG);
3648    if (comment>0)
3649    {
3650      string("Number of lpp segments = ",size(CG));
3651      string("Time in KSW + group + Prep = ",timer-start);
3652    }
3653  }
3654  if(defined(@P)){kill @P; kill @R; kill @RP;}
3655  return(CG);
3656}
3657
3658// Auxiliary routine
3659// sqf
3660// This is for releases of Singular before 3-5-1
3661// proc sqf(poly f)
3662// {
3663//  def RR=basering;
3664//  setring(@P);
3665//  def ff=imap(RR,f);
3666//  def G=sqrfree(ff);
3667//  poly fff=1;
3668//  int i;
3669//  for (i=1;i<=size(G);i++)
3670//  {
3671//    fff=fff*G[i];
3672//  }
3673//  setring(RR);
3674//   def ffff=imap(@P,fff);
3675//   return(ffff);
3676// }
3677
3678// Auxiliary routine
3679// sqf
3680static proc sqf(poly f)
3681{
3682  def RR=basering;
3683  setring(@P);
3684  def ff=imap(RR,f);
3685  poly fff=sqrfree(ff,3);
3686  setring(RR);
3687  def ffff=imap(@P,fff);
3688  return(ffff);
3689}
3690
3691
3692// Auxiliary routine
3693// KSW0: Kapur-Sun-Wang algorithm for computing a CGS, called by KSW
3694// Input:
3695//   F:   parametric ideal to be discussed
3696//   Options:
3697//   The ideal must be defined on C[parameters][variables]
3698// Output:
3699static proc KSW0(ideal F, ideal E, ideal N, int comment)
3700{
3701  def R=basering;
3702  int i; int j; list emp;
3703  list CGS;
3704  ideal N0;
3705  for (i=1;i<=size(N);i++)
3706  {
3707    N0[i]=sqf(N[i]);
3708  }
3709  ideal E0;
3710  for (i=1;i<=size(E);i++)
3711  {
3712    E0[i]=sqf(leadcoef(E[i]));
3713  }
3714  setring(@P);
3715  ideal E1=imap(R,E0);
3716  E1=std(E1);
3717  ideal N1=imap(R,N0);
3718  N1=std(N1);
3719  setring(R);
3720  E0=imap(@P,E1);
3721  N0=imap(@P,N1);
3722  if (inconsistent(E0,N0)==1)
3723  {
3724    return(emp);
3725  }
3726  setring(@RP);
3727  def FRP=imap(R,F);
3728  def ERP=imap(R,E);
3729  FRP=FRP+ERP;
3730  option(redSB);
3731  def GRP=std(FRP);
3732  setring(R);
3733  def G=imap(@RP,GRP);
3734  if (memberpos(1,G)[1]==1)
3735  {
3736    if(comment>1){"Basis 1 is found"; E; N;}
3737    list KK; KK[1]=list(E0,N0,ideal(1));
3738    return(KK);
3739   }
3740  ideal Gr; ideal Gm; ideal GM;
3741  for (i=1;i<=size(G);i++)
3742  {
3743    if (variables(G[i])[1]==0){Gr[size(Gr)+1]=G[i];}
3744    else{Gm[size(Gm)+1]=G[i];}
3745  }
3746  ideal Gr0;
3747  for (i=1;i<=size(Gr);i++)
3748  {
3749    Gr0[i]=sqf(Gr[i]);
3750  }
3751
3752
3753  Gr=elimrepeated(Gr0);
3754  ideal GrN;
3755  for (i=1;i<=size(Gr);i++)
3756   {
3757    for (j=1;j<=size(N0);j++)
3758    {
3759      GrN[size(GrN)+1]=sqf(Gr[i]*N0[j]);
3760    }
3761  }
3762  if (inconsistent(E,GrN)){;}
3763  else
3764  {
3765    if(comment>1){"Basis 1 is found in a branch with arguments"; E; GrN;}
3766    CGS[size(CGS)+1]=list(E,GrN,ideal(1));
3767  }
3768  if (inconsistent(Gr,N0)){return(CGS);}
3769  GM=Gm;
3770  Gm=MDBasis(Gm);
3771  ideal H;
3772  for (i=1;i<=size(Gm);i++)
3773  {
3774    H[i]=sqf(leadcoef(Gm[i]));
3775  }
3776  H=facvar(H);
3777  poly h=sqf(LCMLC(H));
3778  if(comment>1){"H = "; H; "h = "; h;}
3779  ideal Nh=N0;
3780  if(size(N0)==0){Nh=h;}
3781  else
3782  {
3783    for (i=1;i<=size(N0);i++)
3784    {
3785      Nh[i]=sqf(N0[i]*h);
3786    }
3787  }
3788  if (inconsistent(Gr,Nh)){;}
3789  else
3790  {
3791    CGS[size(CGS)+1]=list(Gr,Nh,Gm);
3792  }
3793  poly hc=1;
3794  list KS;
3795  ideal GrHi;
3796  for (i=1;i<=size(H);i++)
3797  {
3798    kill GrHi;
3799    ideal GrHi;
3800    Nh=N0;
3801    if (i>1){hc=sqf(hc*H[i-1]);}
3802    for (j=1;j<=size(N0);j++){Nh[j]=sqf(N0[j]*hc);}
3803    if (equalideals(Gr,ideal(0))==1){GrHi=H[i];}
3804    else {GrHi=Gr,H[i];}
3805//     else {for (j=1;j<=size(Gr);j++){GrHi[size(GrHi)+1]=Gr[j]*H[i];}}
3806    if(comment>1){"Call to KSW with arguments "; GM; GrHi;  Nh;}
3807    KS=KSW0(GM,GrHi,Nh,comment);
3808    for (j=1;j<=size(KS);j++)
3809    {
3810      CGS[size(CGS)+1]=KS[j];
3811    }
3812    if(comment>1){"CGS after KSW = "; CGS;}
3813  }
3814  return(CGS);
3815}
3816
3817// Auxiliary routine
3818// KSWtocgsdr
3819static proc KSWtocgsdr(list L)
3820{
3821  int i; list CG; ideal B; ideal lpp; int j; list NKrep;
3822  for(i=1;i<=size(L);i++)
3823  {
3824    B=redgbn(L[i][3],L[i][1],L[i][2]);
3825    lpp=ideal(0);
3826    for(j=1;j<=size(B);j++)
3827    {
3828      lpp[j]=leadmonom(B[j]);
3829    }
3830    NKrep=KtoPrep(L[i][1],L[i][2]);
3831    CG[i]=list(lpp,B,NKrep);
3832  }
3833  return(CG);
3834}
3835
3836// Auxiliary routine
3837// KtoPrep
3838// Computes the P-representaion of a K-representation (N,W) of a set
3839// input:
3840//    ideal E (null conditions)
3841//    ideal N (non-null conditions ideal)
3842// output:
3843//    the ((p_1,(p_11,..,p_1k_1)),..,(p_r,(p_r1,..,p_rk_r)));
3844//    the Prep of V(N) \ V(W)
3845static proc KtoPrep(ideal N, ideal W)
3846{
3847  int i; int j;
3848  if (N[1]==1)
3849  {
3850    L0[1]=list(ideal(1),list(ideal(1)));
3851    return(L0);
3852  }
3853  def RR=basering;
3854  setring(@P);
3855  ideal B; int te; poly f;
3856  ideal Np=imap(RR,N);
3857  ideal Wp=imap(RR,W);
3858  list L;
3859  list L0; list T0;
3860  L0=minGTZ(Np);
3861  for(j=1;j<=size(L0);j++)
3862  {
3863    option(redSB);
3864    L0[j]=std(L0[j]);
3865  }
3866  for(i=1;i<=size(L0);i++)
3867  {
3868    if(inconsistent(L0[i],Wp)==0)
3869    {
3870      B=L0[i]+Wp;
3871      T0=minGTZ(B);
3872      option(redSB);
3873      for(j=1;j<=size(T0);j++)
3874      {
3875        T0[j]=std(T0[j]);
3876      }
3877      L[size(L)+1]=list(L0[i],T0);
3878    }
3879  }
3880  setring(RR);
3881  def LL=imap(@P,L);
3882  return(LL);
3883}
3884
3885// Auxiliary routine
3886// groupKSWsegments
3887// input:  the list of vertices of KSW
3888// output: the same terminal vertices grouped by lpp
3889static proc groupKSWsegments(list T)
3890{
3891  int i; int j;
3892  list L;
3893  list lpp; list lppor;
3894  list kk;
3895  lpp[1]=T[1][1]; j=1;
3896  lppor[1]=intvec(1);
3897  for(i=2;i<=size(T);i++)
3898  {
3899    kk=memberpos(T[i][1],lpp);
3900    if(kk[1]==0){j++; lpp[j]=T[i][1]; lppor[j]=intvec(i);}
3901    else{lppor[kk[2]][size(lppor[kk[2]])+1]=i;}
3902  }
3903  list ll;
3904  for (j=1;j<=size(lpp);j++)
3905  {
3906    kill ll; list ll;
3907    for(i=1;i<=size(lppor[j]);i++)
3908    {
3909      ll[size(ll)+1]=list(i,T[lppor[j][i]][2],T[lppor[j][i]][3]);
3910    }
3911    L[j]=list(lpp[j],ll,string(lpp[j]));
3912  }
3913  return(L);
3914}
3915
3916//********************* End KapurSunWang *************************
3917
3918//********************* Begin ConsLevels ***************************
3919
3920static proc zeroone(int n)
3921{
3922  list L; list L2;
3923  intvec e; intvec e2; intvec e3;
3924  int j;
3925  if(n==1)
3926  {
3927    e[1]=0;
3928    L[1]=e;
3929    e[1]=1;
3930    L[2]=e;
3931    return(L);
3932  }
3933  if(n>1)
3934  {
3935    L=zeroone(n-1);
3936    for(j=1;j<=size(L);j++)
3937    {
3938      e2=L[j];
3939      e3=e2;
3940      e3[size(e3)+1]=0;
3941      L2[size(L2)+1]=e3;
3942      e3=e2;
3943      e3[size(e3)+1]=1;
3944      L2[size(L2)+1]=e3;
3945    }
3946  }
3947  return(L2);
3948}
3949
3950// Auxiliary routine
3951// subsets: the list of subsets of (1,..n)
3952static proc subsets(int n)
3953{
3954  list L; list L1;
3955  int i; int j;
3956  L=zeroone(n);
3957  intvec e; intvec e1;
3958  for(i=1;i<=size(L);i++)
3959  {
3960    e=L[i];
3961    kill e1; intvec e1;
3962    for(j=1;j<=n;j++)
3963    {
3964      if(e[n+1-j]==1)
3965      {
3966        if(e1==intvec(0)){e1[1]=j;}
3967        else{e1[size(e1)+1]=j};
3968      }
3969    }
3970    L1[i]=e1;
3971  }
3972  return(L1);
3973}
3974
3975// Input a list A of locally closed sets in C-rep
3976// Output a list B of a simplified list of A
3977static proc SimplifyUnion(list A)
3978{
3979  int i; int j;
3980  list L=A;
3981  int n=size(L);
3982  if(n<2){return(A);}
3983  for(i=1;i<=size(L);i++)
3984  {
3985    for(j=1;j<=size(L);j++)
3986    {
3987      if(i != j)
3988      {
3989        if(equalideals(L[i][2],L[j][1])==1)
3990        {
3991          L[i][2]=L[j][2];
3992        }
3993      }
3994    }
3995  }
3996  ideal T=ideal(1);
3997  intvec v;
3998  for(i=1;i<=size(L);i++)
3999  {
4000    if(equalideals(L[i][2],ideal(1)))
4001    {
4002      v[size(v)+1]=i;
4003      T=intersect(T,L[i][1]);
4004    }
4005  }
4006  if(size(v)>0)
4007  {
4008    for(i=1; i<=size(v);i++)
4009    {
4010      j=v[size(v)+1-i];
4011      L=elimfromlist(L, j);
4012    }
4013  }
4014  if(equalideals(T,ideal(1))==0){L[size(L)+1]=list(std(T),ideal(1))};
4015  //string("T_n=",n," new n0",size(L));
4016  return(L);
4017}
4018
4019// Input: list(A)
4020//          A is a list of locally closed sets in Crep. A=[[P1,Q1],[P2,Q2],..,[Pr,Qr]]
4021//          whose union is a constructible set from
4022// Output list [Lev,C]:
4023//          where Lev is the Crep of the canonical first level of A, and
4024//          C is the complement of the first level Lev wrt to the closure of A. The elements are given in Crep,
4025static proc FirstLevel(list A)
4026{
4027  int n=size(A);
4028  list T=zeroone(n);
4029  ideal P; ideal Q;
4030  list Cb;  ideal Cc=ideal(1);
4031  int i; int j;
4032  intvec t;
4033  ideal Z=ideal(1);
4034  list C;
4035  for(i=1;i<=size(A);i++)
4036  {
4037    Z=intersect(Z,A[i][1]);
4038  }
4039  for(i=2; i<=size(T);i++)
4040  {
4041    t=T[i];
4042    P=ideal(1); Q=ideal(0);
4043    for(j=1;j<=n;j++)
4044    {
4045      if(t[n+1-j]==1)
4046      {
4047        Q=Q+A[j][2];
4048      }
4049      else
4050      {
4051        P=intersect(P,A[j][1]);
4052      }
4053    }
4054    //"T_Q="; Q; "T_P="; P;
4055    Cb=Crep(Q,P);
4056    //"T_Cb="; Cb;
4057    if(Cb[1][1]<>1)
4058    {
4059      C[size(C)+1]=Cb;
4060      Cc=intersect(Cc,Cb[1]);
4061    }
4062  }
4063  list Lev=list(Z,Cc);                //Crep(Z,Cc);
4064  if(size(C)>1){C=SimplifyUnion(C);}
4065  return(list(Lev,C));
4066}
4067
4068// Input: list(A)
4069//          A is a list of locally closed sets in Crep. A=[[P1,Q1],[P2,Q2],..,[Pr,Qr]]
4070//          whose union is a constructible set from which the algorithm computes its canonical form.
4071// Output:
4072//     list [L,C] where
4073//          where L is the list of canonical levels of A,
4074//          and C is the list of canonical levels of the complement of A wrt to the closure of A.
4075//          All locally closed sets are given in Crep.
4076//          L=[[1,[p1,p2],[3,[p3,p4],..,[2r-1,[p_{2r-1},p_2r]]]] is the list of levels of A in Crep.
4077//          C=[[2,p2,p3],[4,[p4,p5],..,[2s,[p_{2s},p_{2s+1}]]]  is the list of levels of C,
4078//                                              the complement of S wrt the closure of A, in Crep.
4079proc ConsLevels(list A)
4080"USAGE:   ConsLevels(A);
4081          A is a list of locally closed sets in Crep. A=[[P1,Q1],[P2,Q2],..,[Pr,Qr]]
4082          whose union is a constructible set from which the algorithm computes its
4083          canonical form.
4084RETURN: A list with two elements: [L,C]
4085          where L is the list of canonical levels of A, and C is the list of canonical
4086          levels of the
4087          complement of A wrt to the closure of A.
4088          All locally closed sets are given in Crep.
4089          L=[[1,[p1,p2],[3,[p3,p4],..,[2r-1,[p_{2r-1},p_2r]]]]
4090          C=[[2,p2,p3],[4,[p4,p5],..,[2s,[p_{2s},p_{2s+1}]]]
4091NOTE: The basering R, must be of the form Q[a]
4092KEYWORDS: locally closed set, constructible set
4093EXAMPLE:  ConsLevels; shows an example"
4094{
4095  list L; list C; int i;
4096  list B; list T;
4097  for(i=1; i<=size(A);i++)
4098  {
4099    T=Crep(A[i][1],A[i][2]);
4100    B[size(B)+1]=T;
4101  }
4102  int level=0;
4103  list K;
4104  while(size(B)>0)
4105  {
4106    level++;
4107    K=FirstLevel(B);
4108    if(level mod 2==1){L[size(L)+1]=list(level,K[1]);}
4109    else{C[size(C)+1]=list(level,K[1]);}
4110    //"T_L="; L;
4111    //"T_C="; C;
4112    B=K[2];
4113    //"T_size(B)="; size(B);
4114  }
4115  return(list(L,C));
4116}
4117example
4118{ "EXAMPLE:"; echo = 2;
4119// Example of ConsLevels with nice geometrical interpretetion and 2 levels
4120
4121if (defined(R)){kill R;}
4122if (defined(@P)){kill @P; kill @R; kill @RP;}
4123
4124  ring R=0,(x,y,z),lp;
4125  short=0;
4126  ideal P1=x*(x^2+y^2+z^2-1);
4127  ideal Q1=z,x^2+y^2-1;
4128  ideal P2=y,x^2+z^2-1;
4129  ideal Q2=z*(z+1),y,x*(x+1);
4130
4131  list Cr1=Crep(P1,Q1);
4132  list Cr2=Crep(P2,Q2);
4133
4134  list L=list(Cr1,Cr2);
4135  L;
4136  // ConsLevels(L)=
4137  ConsLevels(L);
4138
4139//----------------------------------------------------------------------
4140// Begin Problem S93
4141// Automatic theorem proving
4142// Generalized Steiner-Lehmus Theorem
4143// A.Montes, T.Recio
4144
4145// Bisector of A(-1,0) = Bisector of B(1,0) varying C(a,b)
4146
4147if(defined(R1)){kill R1;}
4148ring R1=(0,a,b),(x1,y1,x2,y2,p,r),dp;
4149ideal S93=(a+1)^2+b^2-(p+1)^2,
4150                    (a-1)^2+b^2-(1-r)^2,
4151                    a*y1-b*x1-y1+b,
4152                    a*y2-b*x2+y2-b,
4153                    -2*y1+b*x1-(a+p)*y1+b,
4154                    2*y2+b*x2-(a+r)*y2-b,
4155                    (x1+1)^2+y1^2-(x2-1)^2-y2^2;
4156
4157short=0;
4158def GC93=grobcov(S93,"nonnull",ideal(b),"rep",1);
4159//"grobcov(S93,'nonnull',ideal(b),"rep",1)="; GC93;
4160
4161list L0;
4162for(int i=1;i<=size(GC93);i++)
4163{
4164   L0[size(L0)+1]=GC93[i][3];
4165}
4166
4167def GC93ab=grobcov(S93,"nonnull",ideal(a*b),"rep",1);
4168
4169ring RR=0,(a,b),lp;
4170
4171list L1;
4172L1=imap(R1,L0);
4173// L1=Total elements of the grobcov(S93,'nonnull',ideal(b),'rep',1) to be added=
4174L1;
4175
4176// Adding all the elements of grobcov(S93,'nonnull',ideal(b),'rep',1)=
4177ConsLevels(L1);
4178}
4179
4180//**************************** End ConsLevels ******************
4181
4182//******************** Begin locus ******************************
4183
4184// indepparameters
4185// Auxiliary routine to detect 'Special' components of the locus
4186// Input: ideal B
4187// Output:
4188//   1 if the solutions of the ideal do not depend on the parameters
4189//   0 if they depend
4190static proc indepparameters(ideal B)
4191{
4192  def R=basering;
4193  ideal v=variables(B);
4194  setring @RP;
4195  def BP=imap(R,B);
4196  def vp=imap(R,v);
4197  ideal varpar=variables(BP);
4198  int te;
4199  te=equalideals(vp,varpar);
4200  setring(R);
4201  if(te){return(1);}
4202  else{return(0);}
4203}
4204
4205// dimP0: Auxiliary routine
4206// if the dimension in @P of an ideal in the parameters has dimension 0 then it returns 0
4207// else it retuns 1
4208static proc dimP0(ideal N)
4209{
4210  def R=basering;
4211  setring(@P);
4212  int te=1;
4213  def NP=imap(R,N);
4214  attrib(NP,"IsSB",1);
4215  int d=dim(std(NP));
4216  if(d==0){te=0;}
4217  setring(R);
4218  return(te);
4219}
4220
4221// Takes a list of intvec and sorts it and eliminates repeated elements.
4222// Auxiliary routine
4223static proc sortpairs(L)
4224{
4225  def L1=sort(L);
4226  def L2=elimrepeated(L1[1]);
4227  return(L2);
4228}
4229
4230// Eliminates the pairs of L1 that are also in L2.
4231// Auxiliary routine
4232static proc minuselements(list L1,list L2)
4233{
4234  int i;
4235  list L3;
4236  for (i=1;i<=size(L1);i++)
4237  {
4238    if(not(memberpos(L1[i],L2)[1])){L3[size(L3)+1]=L1[i];}
4239  }
4240  return(L3);
4241}
4242
4243// NorSing
4244// Input:
4245//   ideal B: the basis of a component of the grobcov
4246//   ideal E: the top of the component (assumed to be of dimension > 0 (single equation)
4247//   ideal N: the holes of the component
4248// Output:
4249//   int d: the dimension of B on the variables reduced by the holes.
4250//     if d>0    then the component is 'Normal'
4251//     if d==0 then the component is 'Singular'
4252static proc NorSing(ideal B, ideal E, ideal N, list #)
4253{
4254  int i; int j; int Fenv=0; int env; int dd;
4255  list DD=#;
4256  def RR=basering;
4257  int moverdim=2;
4258  int version=0;
4259  int nv=nvars(RR);
4260  if(nv<4){version=1;}
4261  int d;
4262  poly F;
4263  for(i=1;i<=(size(DD) div 2);i++)
4264  {
4265    if(DD[2*i-1]=="movdim"){moverdim=DD[2*i];}
4266    if(DD[2*i-1]=="version"){version=DD[2*i];}
4267    if(DD[2*i-1]=="family"){F=DD[2*i];}
4268  }
4269  if(F!=0){Fenv=1;}
4270  //"T_B="; B; "E="; E; "N="; N;
4271  list L0;
4272  if(dimP0(E)==0){L0=2,"Normal";} // 2 es fals pero ha de ser >0 encara que sigui 0
4273  else
4274  {
4275    if(version==0)
4276    {
4277      //"T_B="; B;  // Computing std(B+E,plex(x,y,x1,..xn)) one can detect if there is a first part
4278      // independent of parameters giving the variables with dimension 0
4279     dd=indepparameters(B);
4280      if (dd==1){d=0; L0=d,string(B),determineF(B,F,E);}
4281      else{d=1; L0=2,"Normal";}
4282    }
4283    else
4284    {
4285      def RH=ringlist(RR);
4286      //"T_RH="; RH;
4287      def H=RH;
4288      H[1]=0;
4289      H[2]=RH[1][2]+RH[2];
4290      int n=size(H[2]);
4291      intvec ll;
4292      for(i=1;i<=n;i++)
4293      {
4294        ll[i]=1;
4295      }
4296      H[3][1][1]="lp";
4297      H[3][1][2]=ll;
4298      def RRH=ring(H);
4299      setring(RRH);
4300      ideal BH=imap(RR,B);
4301      ideal EH=imap(RR,E);
4302      ideal NH=imap(RR,N);
4303      if(Fenv==1){poly FH=imap(RR,F);}
4304      for(i=1;i<=size(EH);i++){BH[size(BH)+1]=EH[i];}
4305      BH=std(BH);  // MOLT COSTOS!!!
4306      ideal G;
4307      ideal r; poly q;
4308      for(i=1;i<=size(BH);i++)
4309      {
4310        r=factorize(BH[i],1);
4311        q=1;
4312        for(j=1;j<=size(r);j++)
4313        {
4314          if((pdivi(r[j],NH)[1] != 0) or (equalideals(ideal(NH),ideal(1))))
4315          {
4316            q=q*r[j];
4317          }
4318        }
4319        if(q!=1){G[size(G)+1]=q;}
4320      }
4321      setring RR;
4322      def GG=imap(RRH,G);
4323      ideal GGG;
4324      if(defined(L0)){kill L0; list L0;}
4325      for(i=1;i<=size(GG);i++)
4326      {
4327        if(indepparameters(GG[i])){GGG[size(GGG)+1]=GG[i];}
4328      }
4329      GGG=std(GGG);
4330      ideal GLM;
4331      for(i=1;i<=size(GGG);i++)
4332      {
4333        GLM[i]=leadmonom(GGG[i]);
4334      }
4335      attrib(GLM,"IsSB",1);
4336      d=dim(std(GLM));
4337      string antiim=string(GGG);
4338      L0=d,antiim;
4339      if(d==0)
4340      {
4341        //" ";string("Antiimage of Special component = ", GGG);
4342         if(Fenv==1)
4343        {
4344          L0[3]=determineF(GGG,F,E);
4345        }
4346      }
4347      else
4348      {
4349        L0[2]="Normal";
4350      }
4351    }
4352  }
4353  return(L0);
4354}
4355
4356static proc determineF(ideal A,poly F,ideal E)
4357{
4358  int env; int i;
4359  def RR=basering;
4360  def RH=ringlist(RR);
4361  def H=RH;
4362  H[1]=0;
4363  H[2]=RH[1][2]+RH[2];
4364  int n=size(H[2]);
4365  intvec ll;
4366  for(i=1;i<=n;i++)
4367  {
4368    ll[i]=1;
4369  }
4370  H[3][1][1]="lp";
4371  H[3][1][2]=ll;
4372  def RRH=ring(H);
4373
4374        //" ";string("Antiimage of Special component = ", GGG);
4375
4376   setring(RRH);
4377   list LL;
4378   def AA=imap(RR,A);
4379   def FH=imap(RR,F);
4380   def EH=imap(RR,E);
4381   ideal M=std(AA+FH);
4382   def rh=reduce(EH,M);
4383   if(rh==0){env=1;} else{env=0;}
4384   setring RR;
4385          //L0[3]=env;
4386    return(env);
4387}
4388
4389// DimPar
4390// Auxilliary routine to NorSing determining the dimension of a parametric ideal
4391// Does not use @P and define it directly because is assumes that
4392//                             variables and parameters have been inverted
4393static proc DimPar(ideal E)
4394{
4395  def RRH=basering;
4396  def RHx=ringlist(RRH);
4397  def Prin=ring(RHx[1]);
4398  setring(Prin);
4399  def E2=std(imap(RRH,E));
4400  def d=dim(E2);
4401  setring RRH;
4402  return(d);
4403}
4404
4405// locus0(G): Private routine used by locus (the public routine), that
4406//                builds the diferent components.
4407// input:      The output G of the grobcov (in generic representation, which is the default option)
4408//       Options: The algorithm allows the following options ar pair of arguments:
4409//                "movdim", d  : by default movdim is 2 but it can be set to other values
4410//                "version", v   :  There are two versions of the algorithm. ('version',1) is
4411//                 a full algorithm that always distinguishes correctly between 'Normal'
4412//                 and 'Special' components, whereas ('version',0) can decalre a component
4413//                 as 'Normal' being really 'Special', but is more effective. By default ('version',1)
4414//                 is used when the number of variables is less than 4 and 0 if not.
4415//                 The user can force to use one or other version, but it is not recommended.
4416//                 "system", ideal F: if the initial systrem is passed as an argument. This is actually not used.
4417//                 "comments", c: by default it is 0, but it can be set to 1.
4418//                 Usually locus problems have mover coordinates, variables and tracer coordinates.
4419//                 The mover coordinates are to be placed as the last variables, and by default,
4420//                 its number is 2. If one consider locus problems in higer dimensions, the number of
4421//                 mover coordinates (placed as the last variables) is to be given as an option.
4422// output:
4423//         list, the canonical P-representation of the Normal and Non-Normal locus:
4424//              The Normal locus has two kind of components: Normal and Special.
4425//              The Non-normal locus has two kind of components: Accumulation and Degenerate.
4426//              This routine is compemented by locus that calls it in order to eliminate problems
4427//              with degenerate points of the mover.
4428//         The output components are given as
4429//              ((p1,(p11,..p1s_1),type_1,level_1),..,(pk,(pk1,..pks_k),type_k,level_k)
4430//         The components are given in canonical P-representation of the subset.
4431//              If all levels of a class of locus are 1, then the set is locally closed. Otherwise the level
4432//              gives the depth of the component.
4433static proc locus0(list GG, list #)
4434{
4435  int te=0;
4436  int t1=1; int t2=1; int i;
4437  def R=basering;
4438  //if(defined(@P)==1){te=1; kill @P; kill @R; kill @RP; }
4439  //setglobalrings();
4440  // Options
4441  list DD=#;
4442  int moverdim=nvars(R);
4443  int version=0;
4444  int nv=nvars(R);
4445  if(nv<4){version=1;}
4446  int comment=0;
4447  ideal Fm;
4448  poly F;
4449  for(i=1;i<=(size(DD) div 2);i++)
4450  {
4451    if(DD[2*i-1]=="movdim"){moverdim=DD[2*i];}
4452    if(DD[2*i-1]=="version"){version=DD[2*i];}
4453    if(DD[2*i-1]=="system"){Fm=DD[2*i];}
4454    if(DD[2*i-1]=="comment"){comment=DD[2*i];}
4455    if(DD[2*i-1]=="family"){F=DD[2*i];}
4456  }
4457  list HHH;
4458  if (GG[1][1][1]==1 and GG[1][2][1]==1 and GG[1][3][1][1][1]==0 and GG[1][3][1][2][1]==1){return(HHH);}
4459   list G1; list G2;
4460  def G=GG;
4461  list Q1; list Q2;
4462  int d; int j; int k;
4463  t1=1;
4464  for(i=1;i<=size(G);i++)
4465  {
4466    attrib(G[i][1],"IsSB",1);
4467    d=locusdim(G[i][2],moverdim);
4468    if(d==0){G1[size(G1)+1]=G[i];}
4469    else
4470    {
4471      if(d>0){G2[size(G2)+1]=G[i];}
4472    }
4473  }
4474  if(size(G1)==0){t1=0;}
4475  if(size(G2)==0){t2=0;}
4476  setring(@RP);
4477  if(t1)
4478  {
4479    list G1RP=imap(R,G1);
4480  }
4481  else {list G1RP;}
4482  list P1RP;
4483  ideal B;
4484  for(i=1;i<=size(G1RP);i++)
4485  {
4486     kill B;
4487     ideal B;
4488     for(k=1;k<=size(G1RP[i][3]);k++)
4489     {
4490       attrib(G1RP[i][3][k][1],"IsSB",1);
4491       G1RP[i][3][k][1]=std(G1RP[i][3][k][1]);
4492       for(j=1;j<=size(G1RP[i][2]);j++)
4493       {
4494         B[j]=reduce(G1RP[i][2][j],G1RP[i][3][k][1]);
4495       }
4496       P1RP[size(P1RP)+1]=list(G1RP[i][3][k][1],G1RP[i][3][k][2],B);
4497     }
4498  }
4499  setring(R);
4500  ideal h;
4501  if(t1)
4502  {
4503    def P1=imap(@RP,P1RP);
4504    for(i=1;i<=size(P1);i++)
4505    {
4506      for(j=1;j<=size(P1[i][3]);j++)
4507      {
4508        h=factorize(P1[i][3][j],1);
4509        P1[i][3][j]=h[1];
4510        for(k=2;k<=size(h);k++)
4511        {
4512          P1[i][3][j]=P1[i][3][j]*h[k];
4513        }
4514      }
4515    }
4516  }
4517  else{list P1;}
4518  ideal BB; int dd; list NS;
4519  for(i=1;i<=size(P1);i++)
4520  {
4521       NS=NorSing(P1[i][3],P1[i][1],P1[i][2][1],DD);
4522       dd=NS[1];
4523       if(dd==0){P1[i][3]=NS;} //"Special";
4524       else{P1[i][3]="Normal";}
4525  }
4526  list P2;
4527  for(i=1;i<=size(G2);i++)
4528  {
4529    for(k=1;k<=size(G2[i][3]);k++)
4530    {
4531      P2[size(P2)+1]=list(G2[i][3][k][1],G2[i][3][k][2]);
4532    }
4533  }
4534  list l;
4535  for(i=1;i<=size(P1);i++){Q1[i]=l; Q1[i][1]=P1[i];} P1=Q1;
4536  for(i=1;i<=size(P2);i++){Q2[i]=l; Q2[i][1]=P2[i];} P2=Q2;
4537
4538  setring(@P);
4539  ideal J;
4540  if(t1==1)
4541  {
4542    def C1=imap(R,P1);
4543    def L1=AddLocus(C1);
4544   }
4545  else{list C1; list L1; kill P1; list P1;}
4546  if(t2==1)
4547  {
4548    def C2=imap(R,P2);
4549    def L2=AddLocus(C2);
4550 }
4551  else{list L2; list C2; kill P2; list P2;}
4552    for(i=1;i<=size(L2);i++)
4553    {
4554      J=std(L2[i][2]);
4555      d=dim(J); // AQUI
4556      if(d==0)
4557      {
4558        L2[i][4]=string("Accumulation",L2[i][4]);
4559      }
4560      else{L2[i][4]=string("Degenerate",L2[i][4]);}
4561    }
4562  list LN;
4563  if(t1==1)
4564  {
4565    for(i=1;i<=size(L1);i++){LN[size(LN)+1]=L1[i];}
4566  }
4567  if(t2==1)
4568  {
4569    for(i=1;i<=size(L2);i++){LN[size(LN)+1]=L2[i];}
4570  }
4571  setring(R);
4572  def L=imap(@P,LN);
4573  for(i=1;i<=size(L);i++){if(size(L[i][2])==0){L[i][2]=ideal(1);}}
4574  //if(te==0){kill @R; kill @RP; kill @P;}
4575  list LL;
4576  for(i=1;i<=size(L);i++)
4577  {
4578    if(typeof(L[i][4])=="list") {L[i][4][1]="Special";}
4579    l[1]=L[i][2];
4580    l[2]=L[i][3];
4581    l[3]=L[i][4];
4582    l[4]=L[i][5];
4583    L[i]=l;
4584 }
4585 return(L);
4586}
4587
4588//  locus(G):  Special routine for determining the locus of points
4589//                 of  geometrical constructions.
4590//  input:      The output G of the grobcov (in generic representation, which is the default option for grobcov)
4591//  output:
4592//          list, the canonical P-representation of the Normal and Non-Normal locus:
4593//               The Normal locus has two kind of components: Normal and Special.
4594//               The Non-normal locus has two kind of components: Accumulation and Degenerate.
4595//               Normal components: for each point in the component,
4596//               the number of solutions in the variables is finite, and
4597//               the solutions depend on the point in the component if the component is not 0-dimensional.
4598//               Special components:  for each point in the component,
4599//               the number of solutions in the variables is finite,
4600//               the component is not 0-dimensional, but the solutions do not depend on the
4601//               values of the parameters in the component.
4602//               Accumlation points: are 0-dimensional components for which it exist
4603//               an infinite number of solutions.
4604//               Degenerate components: are components of dimension greater than 0 for which
4605//               for every point in the component there exist infinite solutions.
4606//          The output components are given as
4607//               ((p1,(p11,..p1s_1),type_1,level_1),..,(pk,(pk1,..pks_k),type_k,level_k)
4608//          The components are given in canonical P-representation of the subset.
4609//               If all levels of a class of locus are 1, then the set is locally closed. Otherwise the level
4610//               gives the depth of the component of the constructible set.
4611proc locus(list GG, list #)
4612"USAGE: locus(G)
4613        The input must be the grobcov  of a parametrical ideal in Q[a][x],
4614        (a=parameters, x=variables). In fact a must be the tracer coordinates
4615        and x the mover coordinates and other auxiliary ones.
4616        Special routine for determining the locus of points
4617        of  geometrical constructions. Given a parametric ideal J
4618        representing the system determining the locus of points (a)
4619        who verify certain properties, the call to locus on the output of grobcov( J )
4620        determines the different classes of locus components, following
4621        the taxonomy defined in
4622        Abanades, Botana, Montes, Recio:
4623        \"An Algebraic Taxonomy for Locus Computation in Dynamic Geometry\".
4624        Computer-Aided Design 56 (2014) 22-33.
4625        The components can be Normal, Special, Accumulation, Degenerate.
4626OPTIONS: The algorithm allows the following options as pair of arguments:
4627         \"movdim\", d  : by default movdim is 2 but it can be set to other values,
4628         and represents the number of mever variables. they should be given as
4629         the last variables of the ring.
4630         \"version\", v   :  There are two versions of the algorithm. (\"version\",1) is
4631         a full algorithm that always distinguishes correctly between 'Normal'
4632         and 'Special' components, whereas \("version\",0) can decalre a component
4633         as 'Normal' being really 'Special', but is more effective. By default (\"version\",1)
4634         is used when the number of variables is less than 4 and 0 if not.
4635         The user can force to use one or other version, but it is not recommended.
4636         \"system\", ideal F: if the initial system is passed as an argument. This is actually not used.
4637         \"comments\", c: by default it is 0, but it can be set to 1.
4638         Usually locus problems have mover coordinates, variables and tracer coordinates.
4639         The mover coordinates are to be placed as the last variables, and by default,
4640         its number is 2. If one consider locus problems in higer dimensions, the number of
4641         mover coordinates (placed as the last variables) is to be given as an option.
4642RETURN: The locus. The output is a list of the components ( C_1,.. C_n ) where
4643        C_i =  (p_i,(p_i1,..p_is_i), type_i,l evel_i )   and type_i can be
4644        'Normal', 'Special', Accumulation', 'Degenerate'. The 'Special' components
4645        return more information, namely the antiimage of the component, that
4646        is 0-dimensional for these kind of components.
4647        Normal components: for each point in the component,
4648        the number of solutions in the variables is finite, and
4649        the solutions depend on the point in the component.
4650        Special components:  for each point in the component,
4651        the number of solutions in the variables is finite. The
4652        antiimage of the component is 0-dimensional.
4653        Accumlation points: are 0-dimensional components whose
4654        antiimage is not zero-dimansional.
4655        Degenerate components: are components of dimension greater than 0
4656        whose antiimage is not-zero-diemansional.
4657        The components are given in canonical P-representation.
4658        The levels of a class of locus are 1,
4659        because they represent locally closed. sets.
4660NOTE: It can only be called after computing the grobcov of the
4661      parametrical ideal in generic representation ('ext',0),
4662      which is the default.
4663      The basering R, must be of the form Q[a_1,..,a_m][x_1,..,x_n].
4664KEYWORDS: geometrical locus, locus, loci.
4665EXAMPLE: locus; shows an example"
4666{
4667  int tes=0; int i;
4668  def R=basering;
4669  if(defined(@P)==1){tes=1; kill @P; kill @R; kill @RP;}
4670  setglobalrings();
4671  // Options
4672  list DD=#;
4673  int moverdim=nvars(R);
4674  int version=0;
4675  int nv=nvars(R);
4676  if(nv<4){version=1;}
4677  int comment=0;
4678  ideal Fm;
4679  for(i=1;i<=(size(DD) div 2);i++)
4680  {
4681    if(DD[2*i-1]=="movdim"){moverdim=DD[2*i];}
4682    if(DD[2*i-1]=="version"){version=DD[2*i];}
4683    if(DD[2*i-1]=="system"){Fm=DD[2*i];}
4684    if(DD[2*i-1]=="comment"){comment=DD[2*i];}
4685    if(DD[2*i-1]=="family"){poly F=DD[2*i];}
4686  }
4687  int j; int k;
4688  def B0=GG[1][2];
4689  def H0=GG[1][3][1][1];
4690  if (equalideals(B0,ideal(1)) or (equalideals(H0,ideal(0))==0))
4691  {
4692    return(locus0(GG,DD));
4693  }
4694  else
4695  {
4696    int n=nvars(R);
4697    ideal vmov=var(n-1),var(n);
4698    ideal N;
4699    intvec xw; intvec yw;
4700    for(i=1;i<=n-1;i++){xw[i]=0;}
4701    xw[n]=1;
4702    for(i=1;i<=n;i++){yw[i]=0;}
4703    yw[n-1]=1;
4704    poly px; poly py;
4705    int te=1;
4706    i=1;
4707    while( te and i<=size(B0))
4708    {
4709      if((deg(B0[i],xw)==1) and (deg(B0[i])==1)){px=B0[i]; te=0;}
4710      i++;
4711    }
4712    i=1; te=1;
4713    while( te and i<=size(B0))
4714    {
4715      if((deg(B0[i],yw)==1) and (deg(B0[i])==1)){py=B0[i]; te=0;}
4716      i++;
4717    }
4718    N=px,py;
4719    te=indepparameters(N);
4720    if(te)
4721    {
4722      string("locus detected that the mover must avoid point (",N,") in order to obtain the correct locus");
4723      // eliminates segments of GG where N is contained in the basis
4724      list nGP;
4725      def GP=GG;
4726      ideal BP;
4727      for(j=1;j<=size(GP);j++)
4728      {
4729        te=1; k=1;
4730        BP=GP[j][2];
4731        while((te==1) and (k<=size(N)))
4732        {
4733          if(pdivi(N[k],BP)[1]!=0){te=0;}
4734          k++;
4735        }
4736        if(te==0){nGP[size(nGP)+1]=GP[j];}
4737      }
4738     }
4739    else{"Warning! Problem with more than one mover. Not able to solve it."; list L; return(L);}
4740  }
4741  def LL=locus0(nGP,DD);
4742  kill @RP; kill @P; kill @R;
4743  return(LL);
4744}
4745example
4746{
4747  "EXAMPLE:"; echo = 2;
4748  ring R=(0,a,b),(x,y),dp;
4749  short=0;
4750
4751  // Concoid
4752  ideal S96=x^2+y^2-4,(b-2)*x-a*y+2*a,(a-x)^2+(b-y)^2-1;
4753  // System S96=
4754  S96;
4755  locus(grobcov(S96));
4756  kill R;
4757  // ********************************************
4758  ring R=(0,a,b),(x4,x3,x2,x1),dp;
4759  short=0;
4760  ideal S=(x1-3)^2+(x2-1)^2-9,
4761               (4-x2)*(x3-3)+(x1-3)*(x4-1),
4762               (3-x1)*(x3-x1)+(4-x2)*(x4-x2),
4763               (4-x4)*a+(x3-3)*b+3*x4-4*x3,
4764               (a-x1)^2+(b-x2)^2-(x1-x3)^2-(x2-x4)^2;
4765  // System S=
4766  S;
4767  locus(grobcov(S));
4768  kill R;
4769  //********************************************
4770
4771  ring R=(0,x,y),(x1,x2),dp;
4772  short=0;
4773  ideal S=-(x - 5)*(x1 - 1) - (x2 - 2)*(y - 2),
4774                (x1 - 5)^2 + (x2 - 2)^2 - 4,
4775                -2*(x - 5)*(x2 - 2) + 2*(x1 - 5)*(y - 2);
4776  // System S=
4777  S;
4778  locus(grobcov(S));
4779}
4780
4781//  locusdg(G):  Special routine for determining the locus of points
4782//                 of  geometrical constructions. Given a parametric ideal J with
4783//                 parameters (a_1,..a_m) and variables (x_1,..,xn),
4784//                 representing the system determining
4785//                 the locus of points (a_1,..,a_m) who verify certain
4786//                 properties, computing the grobcov G of
4787//                 J and applying to it locus, determines the different
4788//                 classes of locus components. The components can be
4789//                 Normal, Special, Accumulation point, Degenerate.
4790//                 The output are the components given in P-canonical form
4791//                 of at most 4 constructible sets: Normal, Special, Accumulation,
4792//                 Degenerate.
4793//                 The description of the algorithm and definitions is
4794//                 given in a forthcoming paper by Abanades, Botana, Montes, Recio.
4795//                 Usually locus problems have mover coordinates, variables and tracer coordinates.
4796//                 The mover coordinates are to be placed as the last variables, and by default,
4797//                 its number is 2. If onw consider locus problems in higer dimensions, the number of
4798//                 mover coordinates (placed as the last variables) is to be given as an option.
4799//
4800//  input:      The output of locus(G);
4801//  output:
4802//          list, the canonical P-representation of the Normal and Non-Normal locus:
4803//               The Normal locus has two kind of components: Normal and Special.
4804//               The Non-normal locus has two kind of components: Accumulation and Degenerate.
4805//               Normal components: for each point in the component,
4806//               the number of solutions in the variables is finite, and
4807//               the solutions depend on the point in the component if the component is not 0-dimensional.
4808//               Special components:  for each point in the component,
4809//               the number of solutions in the variables is finite,
4810//               the component is not 0-dimensional, but the solutions do not depend on the
4811//               values of the parameters in the component.
4812//               Accumlation points: are 0-dimensional components for which it exist
4813//               an infinite number of solutions.
4814//               Degenerate components: are components of dimension greater than 0 for which
4815//               for every point in the component there exist infinite solutions.
4816//          The output components are given as
4817//               ((p1,(p11,..p1s_1),type_1,level_1),..,(pk,(pk1,..pks_k),type_k,level_k)
4818//          The components are given in canonical P-representation of the subset.
4819//               If all levels of a class of locus are 1, then the set is locally closed. Otherwise the level
4820//               gives the depth of the component of the constructible set.
4821proc locusdg(list L)
4822"USAGE: locusdg(L)   The call must be locusdg(locus(grobcov(S))).
4823RETURN: The output is the list of the 'Relevant' components of the locus
4824           in Dynamic Geometry:(C1,..,C:m), where
4825                 C_i= ( p_i,(p_i1,..p_is_i), 'Relevant', level_i )
4826           The 'Relevant' components are the 'Normal' and 'Accumulation' components
4827           of the locus. (See help for locus).
4828
4829NOTE: It can only be called after computing the locus.
4830           Calling sequence:    locusdg(locus(grobcov(S)));
4831KEYWORDS: geometrical locus, locus, loci, dynamic geometry
4832EXAMPLE: locusdg; shows an example"
4833{
4834  list LL;
4835  int i;
4836  for(i=1;i<=size(L);i++)
4837  {
4838    if(typeof(L[i][3])=="string")
4839    {
4840      if((L[i][3]=="Normal") or (L[i][3]=="Accumulation")){L[i][3]="Relevant"; LL[size(LL)+1]=L[i];}
4841    }
4842  }
4843  return(LL);
4844}
4845example
4846{
4847  "EXAMPLE:"; echo = 2;
4848  ring R=(0,a,b),(x,y),dp;
4849  short=0;
4850
4851  // Concoid
4852  ideal S96=x^2+y^2-4,(b-2)*x-a*y+2*a,(a-x)^2+(b-y)^2-1;
4853  // System S96=
4854  S96;
4855  locus(grobcov(S96));
4856  locusdg(locus(grobcov(S96)));
4857  kill R;
4858  //********************************************
4859  ring R=(0,a,b),(x4,x3,x2,x1),dp;
4860  ideal S=(x1-3)^2+(x2-1)^2-9,
4861               (4-x2)*(x3-3)+(x1-3)*(x4-1),
4862               (3-x1)*(x3-x1)+(4-x2)*(x4-x2),
4863               (4-x4)*a+(x3-3)*b+3*x4-4*x3,
4864               (a-x1)^2+(b-x2)^2-(x1-x3)^2-(x2-x4)^2;
4865  short=0;
4866  locus(grobcov(S));
4867  locusdg(locus(grobcov(S)));
4868  kill R;
4869  //********************************************
4870
4871  ring R=(0,x,y),(x1,x2),dp;
4872  short=0;
4873  ideal S=-(x - 5)*(x1 - 1) - (x2 - 2)*(y - 2),
4874                (x1 - 5)^2 + (x2 - 2)^2 - 4,
4875                -2*(x - 5)*(x2 - 2) + 2*(x1 - 5)*(y - 2);
4876  locus(grobcov(S));
4877  locusdg(locus(grobcov(S)));
4878}
4879
4880// locusto: Transforms the output of locus, locusdg, envelop and envelopdg
4881//             into a string that can be reed from different computational systems.
4882// input:
4883//     list L: The output of locus
4884// output:
4885//     string s: The output of locus converted to a string readable by other programs
4886proc locusto(list L)
4887"USAGE: locusto(L);
4888          The argument must be the output of locus or locusdg or
4889          envelop or envelopdg.
4890          It transforms the output into a string in standard form
4891          readable in many languages (Geogebra).
4892RETURN: The locus in string standard form
4893NOTE: It can only be called after computing either
4894              - locus(grobcov(F))                -> locusto( locus(grobcov(F)) )
4895              - locusdg(locus(grobcov(F)))  -> locusto( locusdg(locus(grobcov(F))) )
4896              - envelop(F,C)                       -> locusto( envelop(F,C) )
4897              -envelopdg(envelop(F,C))      -> locusto( envelopdg(envelop(F,C)) )
4898KEYWORDS: geometrical locus, locus, loci.
4899EXAMPLE:  locusto; shows an example"
4900{
4901  int i; int j; int k;
4902  string s="["; string sf="]"; string st=s+sf;
4903  if(size(L)==0){return(st);}
4904  ideal p;
4905  ideal q;
4906  for(i=1;i<=size(L);i++)
4907  {
4908    s=string(s,"[[");
4909    for (j=1;j<=size(L[i][1]);j++)
4910    {
4911      s=string(s,L[i][1][j],",");
4912    }
4913    s[size(s)]="]";
4914    s=string(s,",[");
4915    for(j=1;j<=size(L[i][2]);j++)
4916    {
4917      s=string(s,"[");
4918      for(k=1;k<=size(L[i][2][j]);k++)
4919      {
4920        s=string(s,L[i][2][j][k],",");
4921      }
4922      s[size(s)]="]";
4923      s=string(s,",");
4924    }
4925    s[size(s)]="]";
4926    s=string(s,"]");
4927    if(size(L[i])>=3)
4928    {
4929      s=string(s,",[");
4930      if(typeof(L[i][3])=="string")
4931      {
4932        s=string(s,string(L[i][3]),"]]");
4933      }
4934      else
4935      {
4936        for(k=1;k<=size(L[i][3]);k++)
4937        {
4938          s=string(s,"[",L[i][3][k],"],");
4939        }
4940        s[size(s)]="]";
4941        s=string(s,"]");
4942      }
4943    }
4944    if(size(L[i])>=4)
4945    {
4946      s[size(s)]=",";
4947      s=string(s,string(L[i][4]),"],");
4948    }
4949    s[size(s)]="]";
4950    s=string(s,",");
4951  }
4952  s[size(s)]="]";
4953  return(s);
4954}
4955example
4956{
4957  "EXAMPLE:"; echo = 2;
4958  ring R=(0,x,y),(x1,y1),dp;
4959  short=0;
4960  ideal S=x1^2+y1^2-4,(y-2)*x1-x*y1+2*x,(x-x1)^2+(y-y1)^2-1;
4961  locusto(locus(grobcov(S)));
4962  locusto(locusdg(locus(grobcov(S))));
4963  kill R;
4964  //********************************************
4965
4966  // 1. Take a fixed line l: x1-y1=0  and consider
4967  //    the family F of a lines parallel to l passing through the mover point M
4968  // 2. Consider a circle x1^2+x2^2-25, and a mover point M(x1,x2) on it.
4969  // 3. Compute the envelop of the family of lines.
4970
4971  ring R=(0,x,y),(x1,y1),lp;
4972  poly F=(y-y1)-(x-x1);
4973  ideal C=x1^2+y1^2-25;
4974  short=0;
4975
4976  // Curves Family F=
4977  F;
4978  // Conditions C=
4979  C;
4980
4981  locusto(envelop(F,C));
4982  locusto(envelopdg(envelop(F,C)));
4983  kill R;
4984  //********************************************
4985
4986  // Steiner Deltoid
4987  // 1. Consider the circle x1^2+y1^2-1=0, and a mover point M(x1,y1) on it.
4988  // 2. Consider the triangle A(0,1), B(-1,0), C(1,0).
4989  // 3. Consider lines passing through M perpendicular to two sides of ABC triangle.
4990  // 4. Obtain the envelop of the lines above.
4991
4992  ring R=(0,x,y),(x1,y1,x2,y2),lp;
4993  ideal C=(x1)^2+(y1)^2-1,
4994               x2+y2-1,
4995               x2-y2-x1+y1;
4996  matrix M[3][3]=x,y,1,x2,y2,1,x1,0,1;
4997  poly F=det(M);
4998
4999  short=0;
5000
5001  // Curves Family F=
5002  F;
5003  // Conditions C=
5004  C;
5005
5006  locusto(envelop(F,C));
5007  locusto(envelopdg(envelop(F,C)));
5008}
5009
5010// Auxiliary routine
5011// locusdim
5012// input:
5013//    B:         ideal, a basis of a segment of the grobcov
5014//    dgdim: int, the dimension of the mover (for locus)
5015//                by default dgdim is equal to the number of variables
5016static proc locusdim(ideal B, list #)
5017{
5018  def R=basering;
5019  int dgdim;
5020  int nv=nvars(R);
5021  if (size(#)>0){dgdim=#[1];}
5022  else {dgdim=nv;}
5023  int d;
5024  list v;
5025  ideal vi;
5026  int i;
5027  for(i=1;i<=dgdim;i++)
5028  {
5029    v[size(v)+1]=varstr(nv-dgdim+i);
5030    vi[size(v)+1]=var(nv-dgdim+i);
5031  }
5032  ideal B0;
5033  for(i=1;i<=size(B);i++)
5034  {
5035    if(subset(variables(B[i]),vi))
5036    {
5037      B0[size(B0)+1]=B[i];
5038    }
5039  }
5040  def RR=ringlist(R);
5041  def RR0=RR;
5042  RR0[2]=v;
5043  def R0=ring(RR0);
5044  setring(R0);
5045  def B0r=imap(R,B0);
5046  B0r=std(B0r);
5047  d=dim(B0r);
5048  setring R;
5049  return(d);
5050}
5051
5052static proc norspec(ideal F)
5053{
5054  def RR=basering;
5055  def Rx=ringlist(RR);
5056
5057   def Rx=ringlist(RR);
5058  def @P=ring(Rx[1]);
5059  list Lx;
5060  Lx[1]=0;
5061  Lx[2]=Rx[2]+Rx[1][2];
5062  Lx[3]=Rx[1][3];
5063  Lx[4]=Rx[1][4];
5064  Rx[1]=0;
5065  def D=ring(Rx);
5066  def @RP=D+@P;
5067  exportto(Top,@R);      // global ring Q[a][x]
5068  exportto(Top,@P);      // global ring Q[a]
5069  exportto(Top,@RP);     // global ring K[x,a] with product order
5070  setring(RR);
5071}
5072
5073// envelop
5074// Input: n arguments
5075//   poly F: the polynomial defining the family of curves in ring R=0,(x,y),(x1,..,xn),lp;
5076//   ideal C=g1,..,g_{n-1}:  the set of constraints
5077// Output: the components of the envolvent;
5078proc envelop(poly F, ideal C, list #)
5079"USAGE: envelop(F,C);
5080          The first argument F must be the family of curves of which
5081          on want to compute the envelop.
5082          The second argument C must be the ideal of conditions
5083          over the variables, and should contain as polynomials
5084          as the number of variables -1.
5085RETURN: The components of the envelop with its taxonomy:
5086           The taxonomy distinguishes 'Normal',
5087          'Special', 'Accumulation', 'Degenerate' components.
5088          In the case of 'Special' components, it also
5089          outputs the antiimage of the component
5090          and an integer (0-1). If the integer is 0
5091          the component is not a curve of the family and is
5092          not considered as 'Relevant' by the envelopdg routine
5093          applied to it, but is considered as 'Relevant' if the integer is 1.
5094NOTE: grobcov is called internally.
5095          The basering R, must be of the form Q[a][x] (a=parameters, x=variables).
5096KEYWORDS: geometrical locus, locus, loci, envelop
5097EXAMPLE:  envelop; shows an example"
5098{
5099  int tes=0; int i;   int j;
5100  def R=basering;
5101  if(defined(@P)==1){tes=1; kill @P; kill @R; kill @RP;}
5102  setglobalrings();
5103  // Options
5104  list DD=#;
5105  int moverdim=nvars(R);
5106  int version=0;
5107  int nv=nvars(R);
5108  if(nv<4){version=1;}
5109  int comment=0;
5110  ideal Fm;
5111  for(i=1;i<=(size(DD) div 2);i++)
5112  {
5113    if(DD[2*i-1]=="movdim"){moverdim=DD[2*i];}
5114    if(DD[2*i-1]=="version"){version=DD[2*i];}
5115    if(DD[2*i-1]=="system"){Fm=DD[2*i];}
5116    if(DD[2*i-1]=="comment"){comment=DD[2*i];}
5117  }
5118  int n=nvars(R);
5119  list v;
5120  for(i=1;i<=n;i++){v[size(v)+1]=var(i);}
5121  def MF=jacob(F);
5122  def TMF=transpose(MF);
5123  def Mg=MF;
5124  def TMg=TMF;
5125  for(i=1;i<=n-1;i++)
5126  {
5127    Mg=jacob(C[i]);
5128    TMg=transpose(Mg);
5129    TMF=concat(TMF,TMg);
5130  }
5131  poly J=det(TMF);
5132  ideal S=ideal(F)+C+ideal(J);
5133  DD[size(DD)+1]="family";
5134  DD[size(DD)+1]=F;
5135  def G=grobcov(S,DD);
5136   def L=locus(G, DD);
5137  return(L);
5138}
5139example
5140{
5141  "EXAMPLE:"; echo = 2;
5142  // Steiner Deltoid
5143  // 1. Consider the circle x1^2+y1^2-1=0, and a mover point M(x1,y1) on it.
5144  // 2. Consider the triangle A(0,1), B(-1,0), C(1,0).
5145  // 3. Consider lines passing through M perpendicular to two sides of ABC triangle.
5146  // 4. Obtain the envelop of the lines above.
5147
5148  ring R=(0,x,y),(x1,y1,x2,y2),lp;
5149  ideal C=(x1)^2+(y1)^2-1,
5150               x2+y2-1,
5151               x2-y2-x1+y1;
5152  matrix M[3][3]=x,y,1,x2,y2,1,x1,0,1;
5153  poly F=det(M);
5154
5155  short=0;
5156
5157  // Curves Family F=
5158  F;
5159  // Conditions C=
5160  C;
5161
5162  def Env=envelop(F,C);
5163  Env;
5164}
5165
5166// envelopdg
5167// Input: list L: the output of envelop(poly F, ideal C, list #)
5168// Output: the relevant components of the envolvent in dynamic geometry;
5169proc envelopdg(list L)
5170"USAGE: envelopdg(L);
5171          The input list L must be the output of the call to
5172          the routine 'envolop' of the family of curves
5173RETURN: The relevant components of the envelop in Dynamic Geometry.
5174           'Normal' and 'Accumulation' components are always considered
5175           'Relevant'. 'Special' components of the envelop outputs
5176           three objects in its characterization: 'Special', the antiimage ideal,
5177           and the integer 0 or 1, that indicates that the given component is
5178           formed (1) or is not formed (0) by curves of the family. Only if yes,
5179           'envelopdg' considers the component as 'Relevant' .
5180NOTE: It must be called to the output of the 'envelop' routine.
5181          The basering R, must be of the form Q[a,b,..][x,y,..].
5182KEYWORDS: geometrical locus, locus, loci, envelop.
5183EXAMPLE:  envelop; shows an example"
5184{
5185  list LL;
5186  list Li;
5187  int i;
5188  for(i=1;i<=size(L);i++)
5189  {
5190    if(typeof(L[i][3])=="string")
5191    {
5192      if((L[i][3]=="Normal") or (L[i][3]=="Accumulation")){Li=L[i]; Li[3]="Relevant"; LL[size(LL)+1]=Li;}
5193    }
5194    else
5195    {
5196      if(typeof(L[i][3])=="list")
5197      {
5198        if(L[i][3][3]==1)
5199        {
5200          Li=L[i]; Li[3]="Relevant"; LL[size(LL)+1]=Li;
5201        }
5202      }
5203    }
5204  }
5205  return(LL);
5206}
5207example
5208{
5209  "EXAMPLE:"; echo = 2;
5210
5211  // 1. Take a fixed line l: x1-y1=0  and consider
5212  //    the family F of a lines parallel to l passing through the mover point M
5213  // 2. Consider a circle x1^2+x2^2-25, and a mover point M(x1,x2) on it.
5214  // 3. Compute the envelop of the family of lines.
5215
5216  ring R=(0,x,y),(x1,y1),lp;
5217  short=0;
5218  poly F=(y-y1)-(x-x1);
5219  ideal C=x1^2+y1^2-25;
5220  short=0;
5221
5222  // Curves Family F=
5223  F;
5224  // Conditions C=
5225  C;
5226
5227  envelop(F,C);
5228  envelopdg(envelop(F,C));
5229}
5230
5231// AddLocus: auxilliary routine for locus0 that computes the components of the constructible:
5232// Input:  the list of locally closed sets to be added, each with its type as third argument
5233//     L=[ [LC[11],,,LC[1k_1],  .., [LC[r1],,,LC[rk_r] ] where
5234//            LC[1]=[p1,[p11,..,p1k],typ]
5235// Output:  the list of components of the constructible union of the L, with the type of the corresponding top
5236//               and the level of the constructible
5237//     L4= [[v1,p1,[p11,..,p1l],typ_1,level]_1 ,.. [vs,ps,[ps1,..,psl],typ_s,level_s]
5238static proc AddLocus(list L)
5239{
5240//  int te0=0;
5241//  def RR=basering;
5242//  if(defined(@P)){te0=1;  def Rx=@R;  kill @P; setring RR;}
5243  list L1; int i; int j;  list L2; list L3;
5244  list l1; list l2;
5245  intvec v;
5246  for(i=1; i<=size(L); i++)
5247  {
5248    for(j=1;j<=size(L[i]);j++)
5249    {
5250      l1[1]=L[i][j][1];
5251      l1[2]=L[i][j][2];
5252      l2[1]=l1[1];
5253      if(size(L[i][j])>2){l2[3]=L[i][j][3];}
5254      v[1]=i; v[2]=j;
5255      l2[2]=v;
5256      L1[size(L1)+1]=l1;
5257      L2[size(L2)+1]=l2;
5258    }
5259  }
5260  L3=LocusConsLevels(L1);
5261  list L4; int level;
5262  ideal p1; ideal pp1; int t; int k; int k0; string typ; list l4;
5263  for(i=1;i<=size(L3);i++)
5264  {
5265    level=L3[i][1];
5266    for(j=1;j<=size(L3[i][2]);j++)
5267    {
5268      p1=L3[i][2][j][1];
5269      t=1; k=1;
5270      while((t==1) and (k<=size(L2)))
5271      {
5272        pp1=L2[k][1];
5273        if(equalideals(p1,pp1)){t=0; k0=k;}
5274        k++;
5275      }
5276      if(t==0)
5277      {
5278        v=L2[k0][2];
5279      }
5280      else{"ERROR p1 NOT FOUND";}
5281      l4[1]=v; l4[2]=p1; l4[3]=L3[i][2][j][2];  l4[5]=level;
5282      if(size(L2[k0])>2){l4[4]=L2[k0][3];}
5283      L4[size(L4)+1]=l4;
5284    }
5285  }
5286  return(L4);
5287}
5288
5289// Input L: list of components in P-rep to be added
5290//         [  [[p_1,[p_11,..,p_1,r1]],..[p_k,[p_k1,..,p_kr_k]]  ]
5291// Output:
5292//          list of lists of levels of the different locally closed sets of
5293//          the canonical P-rep of the constructible.
5294//          [  [level_1,[ [Comp_11,..Comp_1r_1] ] ], .. ,
5295//             [level_s,[ [Comp_s1,..Comp_sr_1] ]
5296//          ]
5297//          where level_i=i,   Comp_ij=[ p_i,[p_i1,..,p_it_i] ] is a prime component.
5298// LocusConsLevels: given a set of components of locally closed sets in P-representation, it builds the
5299//       canonical P-representation of the corresponding constructible set of its union,
5300//       including levels it they are.
5301static proc LocusConsLevels(list L)
5302{
5303  list Lc; list Sc;
5304  int i;
5305  for(i=1;i<=size(L);i++)
5306  {
5307    Sc=PtoCrep(list(L[i]));
5308    Lc[size(Lc)+1]=Sc;
5309  }
5310  list S=ConsLevels(Lc)[1];
5311  list Sout;
5312  list Lev;
5313  for(i=1;i<=size(S);i++)
5314  {
5315    Lev=list(i,Prep(S[i][2][1],S[i][2][2]));
5316    Sout[size(Sout)+1]=Lev;
5317  }
5318  return(Sout);
5319}
5320
5321//********************* End locus ****************************
5322
Note: See TracBrowser for help on using the repository browser.