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

spielwiese
Last change on this file since acd2e0 was acd2e0, checked in by Hans Schoenemann <hannes@…>, 6 years ago
fix: special case: return empty list
  • Property mode set to 100644
File size: 190.9 KB
Line 
1//
2version="version grobcov.lib 4.1.1.0 Feb_2018 "; // $Id$
3           // version N4; February 2018;
4           // Two routines for Automatic Deduction of Geometric Theorems
5            // have been added: ADGT, intersectpar.
6category="General purpose";
7info="
8LIBRARY:  grobcov.lib  February 2018.
9          Groebner Cover for parametric ideals.
10          Comprehensive Groebner Systems, Groebner Cover,
11          Canonical Forms,  Parametric Polynomial Systems,
12          Automatic Deduction of Geometric Theorems,
13          Dynamic Geometry, Loci, Envelope, Constructible sets.
14          See: A. Montes A, M. Wibmer,
15          \"Groebner Bases for Polynomial Systems with parameters\",
16          Journal of Symbolic Computation 45 (2010) 1391-1425.
17          (https://www.mat.upc.edu//en/people/antonio.montes/).
18
19IMPORTANT: The book,  not yet published:
20           A. Montes. \" The Groebner Cover\":
21           (Discussing Parametric Polynomial Systems).
22           can be used as a user manual of all
23           the  routines included in this library.
24           It defines and proves all the theoretic results used
25           here,  and shows examples of all the routines.
26           It will be published soon.
27           There are many previous papers realted to the subject,
28           but the book actualices all the contents.
29
30AUTHORS:  Antonio Montes (Universitat Politecnica de Catalunya),
31          Hans Schoenemann (Technische Universitaet Kaiserslautern).
32
33OVERVIEW: In 2010, the library was designed to contain
34          Montes-Wibmer's
35          algorithms for computing the Canonical Groebner
36          Cover of a  parametric ideal. The central  routine is
37          grobcov. Given  a  parametric ideal, grobcov outputs
38          its Canonical  Groebner Cover, consisting of a set
39          of triplets of (lpp, basis,  segment). The basis
40          (after normalization) is the reduced  Groebner basis
41          for each point of the segment. The segments
42          are disjoint, locally closed and  correspond to
43          constant lpp (leading power product) of the basis,
44          and are represented in canonical representation.
45          The segments cover the  whole parameter space.
46          The output is canonical, it only depends on the
47          given parametric ideal and the monomial order.
48          This is much more than a simple Comprehensive
49          Groebner System.  The algorithm grobcov allows
50          options to solve  partially the problem when the
51          whole automatic algorithm  does not finish in
52          reasonable time.
53
54          grobcov uses a first algorithm cgsdr that outputs a
55          disjoint  reduced Comprehensive Groebner System
56          with constant lpp. For this purpose, in this library,
57          the implemented algorithm is Kapur-Sun-Wang
58          algorithm, because it is actually the most efficient
59          algorithm known for this purpose.
60          D. Kapur, Y. Sun, and D.K. Wang \"A New Algorithm
61          for  Computing Comprehensive Groebner Systems\".
62          Proceedings of ISSAC'2010, ACM Press, (2010), 29-36.
63
64          The library has evolved to include new applications of
65          the  Groebner Cover, and new theoretical developments
66          have been done. The actual version also includes a
67          routine (ConsLevels) for computing the canonical form
68          of a constructible set, given as a union of locally
69          closed sets. It determines the canonical locally closed
70          level sets of a constructible set. It is described in:
71          J.M. Brunat, A. Montes, \"Computing the canonical
72          representation of constructible sets\".
73          Math.  Comput. Sci. (2016) 19: 165-178.
74
75          A new routine locus has been included to compute
76          loci of points, and determining the taxonomy of the
77          components. It is  described in the book
78          A. Montes. \"The Groebner Cover\" (Discussing
79          Parametric Polynomial Systems).
80          Additional routines to transform the output to string
81          (locusdg,  locusto) are also included and used in the
82          Dynamic Geometry software  GeoGebra. They were
83          described in:
84          M.A. Abanades, F. Botana, A. Montes, T. Recio:
85          \''An Algebraic Taxonomy  for Locus Computation in
86          Dynamic Geometry\''.
87          Computer-Aided Design 56 (2014) 22-33.
88
89          Recently also routines for computing the generalized
90          envelope  of a family of hyper-surfaces (envelop),
91          to be used in Dynamic Geometry, has been included
92          and is described in the book
93          A. Montes. \"The Groebner Cover\" (Discussing
94          Parametric Polynomial Systems).
95
96          The last inclusion is an automatic algorithm for
97          Automatic Deduction of Geometric Theorems,
98          described in the book \"Groebner Cover\".
99
100          This version was finished on 10/02/2018
101
102NOTATIONS: Before calling any routine of the library grobcov,
103          the user  must define the ideal Q[a][x], and all the
104          input polynomials and  ideals defined on it.
105          Internally the routines define and use also other
106          ideals: Q[a], Q[x,a] and so on.
107
108PROCEDURES:
109
110grobcov(F);  Is the basic routine giving the canonical Groebner
111          Cover of the parametric ideal F.  This routine accepts
112          many options, that allow to obtain results even when
113          the canonical  computation does not finish in
114          reasonable time.
115
116cgsdr(F); Is the procedure for obtaining a first disjoint,
117          reduced  Comprehensive Groebner  System that is
118          used in grobcov, but can also be used independently
119          if only a CGS is required. It is a more efficient routine
120          than buildtree (the own routine of 2010 that  is no
121          more available).
122          Now, Kapur-Sun-Wang (KSW) algorithm is used.
123
124pdivi(f,F); Performs a pseudodivision of a parametric
125          polynomial by  a parametric ideal.
126
127pnormalf(f,E,N); Reduces a parametric polynomial f over V(E) \ V(N).
128          E is the null ideal and N the non-null ideal over the parameters.
129
130Crep(N,M); Computes the canonical C-representation of V(N) \ V(M).
131          It can be called in Q[a] or in Q[a][x],
132          but the ideals N,M can only  contain parameters of Q[a].
133
134Prep(N,M); Computes the canonical P-representation of V(N) \ V(M).
135          It can be called in Q[a]  or in Q[a][x],
136          but the ideals N,M can only contain parameters of Q[a].
137
138PtoCrep(L)  Starting from the canonical Prep of a locally closed
139          set  computes its Crep.
140
141extendpoly(f,p,q); Given the generic representation f of an
142          I-regular function F defined by poly f on V(p) \ V(q)
143          it returns its full representation.
144
145extendGC(GC); When the grobcov of an ideal has been
146          computed  with the default option (\"ext\",0) and the
147          explicit option (\"rep\",2) (which is not the default),
148          then one  can call extendGC(GC) (and options) to obtain
149          the full representation of  the bases. With the default
150          option (\"ext\",0) only the generic representation of
151          the bases is computed, and one can obtain the full
152          representation using extendGC.
153
154ConsLevels(L); Given a list L of locally closed sets, it returns
155         the closures of the canonical  levels of the
156         constructible set and its complements of the
157         union of them.
158
159Levels(L);Transforms the output of ConsLevels
160          into the proper Levels of  the constructible set.
161
162locus(G); Special routine for determining the geometrical
163          locus of points verifying given conditions. Given
164          a parametric ideal J in Q[x1,..,xn][u1,..,um]
165          with parameters (x1,..,xn) and variables
166          (u1,..,um), representing the system determining
167          the n-dimensional locus with tracer point (x1,..,xn)
168          verifying certain properties,
169          one can apply locus to the system F, for obtaining the locus.
170
171          locus provides all the components of the locus and
172          determines their taxonomy, that can be:
173           \"Normal\", \"Special\", \"Accumulation\",
174          \"Degenerate\".
175          The coordinates of a mover point, if it exist, should be
176          placed as the n last u-variables.
177
178locusdg(G); Is a special routine that determines the
179          \"Relevant\" components of the locus in dynamic
180          geometry. It is to be called to the output of locus
181          and selects from it the \"Normal\", and\"Accumulation\"
182          components.
183
184envelop(F,C); Special routine for determining the envelop
185          of a family of hyper-surfaces F  in
186          Q[x1,..,xn][t1,..,tm] depending on an ideal of
187          constraints C in Q[t1,..,tm]. It computes the
188          locus of the envelop, and detemines the
189          different components as well as its taxonomy:
190          \"Normal\", \"Special\", \"Accumulation\",
191          \"Degenerate\". (See help for locus).
192
193locusto(L); Transforms the output of locus, locusdg,
194          envelop into a string  that can be reed  from
195          different computational systems.
196
197stdlocus(iF); Simple procedure to determine the components
198          of the locus, alternative to  locus that uses only
199          standard GB computation. Cannot determine the
200          taxonomy of  the irreducible components.
201
202AssocTanToEnv(F,C,E); Having computed an envelop
203          component E of a family of hyper-surfaces F,
204          with constraints C, it returns the parameter values
205          of the associated tangent  hyper-surface of the
206          family passing at one point of the envelop component E.
207
208FamElemsAtEnvCompPoints(F,C,E) Having computed an
209          envelop component E of a family of hyper-surfaces F,
210          with constraints C, it returns the parameter values of
211          all the  hyper-surfaces of the family passing at one
212          point of the envelop component E.
213
214discrim(f,x); Determines the factorized discriminant of a
215          degree 2 polynomial in the variable x. The polynomial
216          can be defined on any ring where x is a variable.
217          The polynomial f can depend on  parameters and
218          variables.
219
220WLemma(F,A); Given an ideal F in Q[a][x] and an ideal A
221          in Q[a], it returns the list (lpp,B,S)  were B is the
222          reduced Groebner basis of the specialized F over
223          the segment S, subset of V(A) with top A,
224          determined by Wibmer's Lemma.
225          S is determined in P-representation
226          (or optionally in C-representation). The basis is
227          given by I-regular functions.
228
229intersectpar(L); Auxiliary routine. Given a list of ideals definend on K[a][x]
230         it determines the intersection of all of them in K[x,a]
231
232ADGT(H,T,H1,T1); Given 4 ideals H,T,H1,T1 in Q[a][x], corresponding to
233        a problem of Automatic Deduction of Geometric Theorems,
234        it determines the supplementary conditions over the parameters
235        for the Proposition (H and not H1) => (T and not T1) to be a
236        Theorem.
237        If H1=1 then H1 is not considered, and analogously for T1.
238
239SEE ALSO: compregb_lib
240";
241
242LIB "poly.lib";
243LIB "primdec.lib";
244LIB "qhmoduli.lib";
245
246// ************ Begin of the grobcov library *********************
247
248// Development of the library:
249// Library grobcov.lib
250// (Groebner Cover):
251// Release 0: (public)
252// Initial data: 21-1-2008
253// Uses buildtree for cgsdr
254// Final data: 3-7-2008
255// Release 2: (prived)
256// Initial data: 6-9-2009
257// Last version using buildtree for cgsdr
258// Final data: 25-10-2011
259// Release B: (prived)
260// Initial data: 1-7-2012
261// Uses both buildtree and KSW for cgsdr
262// Final data: 4-9-2012
263// Release G: (public)
264// Initial data: 4-9-2012
265// Uses KSW algorithm for cgsdr
266// Final data: 21-11-2013
267// Release L: (public)
268// New routine ConsLevels: 25-1-2016
269// Updated locus: 10-7-2015 (uses ConsLevels)
270// Release M: (public)
271// New routines for computing the envelope of a family of
272//    hyper-surfaces and associated questions: 22-4-2016: 20-9-2016
273// New routine WLemma for computing the result of
274//    Wibmer's Lemma:  19-9-2016
275// Final data October 2016
276// Updated locus (messages) // Updated locus (messages)
277// Final data Mars 2017
278// Release N4: (public)
279// New routines for ADGT: 21-1-2018
280// Final data February 2018
281//*************Auxiliary routines**************
282
283// elimintfromideal: elimine the constant numbers from an ideal
284//        (designed for W, nonnull conditions)
285// Input: ideal J
286// Output:ideal K with the elements of J that are non constants, in the
287//        ring Q[x1,..,xm]
288static proc elimintfromideal(ideal J)
289{
290  int i;
291  int j=0;
292  ideal K;
293  if (size(J)==0){return(ideal(0));}
294  for (i=1;i<=ncols(J);i++){if (size(variables(J[i])) !=0){j++; K[j]=J[i];}}
295  return(K);
296}
297
298// delfromideal: deletes the i-th polynomial from the ideal F
299//    Works in any kind of ideal
300static proc delfromideal(ideal F, int i)
301{
302  int j;
303  ideal G;
304  if (size(F)<i){ERROR("delfromideal was called with incorrect arguments");}
305  if (size(F)<=1){return(ideal(0));}
306  if (i==0){return(F)};
307  for (j=1;j<=ncols(F);j++)
308  {
309    if (j!=i){G[ncols(G)+1]=F[j];}
310  }
311  return(G);
312}
313
314// delidfromid: deletes the polynomials in J that are in I
315// Input: ideals I, J
316// Output: the ideal J without the polynomials in I
317//   Works in any kind of ideal
318static proc delidfromid(ideal I, ideal J)
319{
320  int i; list r;
321  ideal JJ=J;
322  for (i=1;i<=size(I);i++)
323  {
324    r=memberpos(I[i],JJ);
325    if (r[1])
326    {
327      JJ=delfromideal(JJ,r[2]);
328    }
329  }
330  return(JJ);
331}
332
333// eliminates the ith element from a list or an intvec
334static proc elimfromlist(l, int i)
335{
336  if(typeof(l)=="list"){list L;}
337  if (typeof(l)=="intvec"){intvec L;}
338  if (typeof(l)=="ideal"){ideal L;}
339  int j;
340  if((size(l)==0) or (size(l)==1 and i!=1)){return(l);}
341  if (size(l)==1 and i==1){return(L);}
342  // L=l[1];
343  if(i>1)
344  {
345    for(j=1;j<=i-1;j++)
346    {
347      L[size(L)+1]=l[j];
348    }
349  }
350  for(j=i+1;j<=size(l);j++)
351  {
352    L[size(L)+1]=l[j];
353  }
354  return(L);
355}
356
357// eliminates repeated elements form an ideal or matrix or module or intmat or bigintmat
358static proc elimrepeated(F)
359{
360  int i;
361  int nt;
362  if (typeof(F)=="ideal"){nt=ncols(F);}
363  else{nt=size(F);}
364
365  def FF=F;
366  FF=F[1];
367  for (i=2;i<=nt;i++)
368  {
369    if (not(memberpos(F[i],FF)[1]))
370    {
371      FF[size(FF)+1]=F[i];
372    }
373  }
374  return(FF);
375}
376
377// equalideals
378// Input: ideals F and G;
379// Output: 1 if they are identical (the same polynomials in the same order)
380//         0 else
381static proc equalideals(ideal F, ideal G)
382{
383  int i=1; int t=1;
384  if (size(F)!=size(G)){return(0);}
385  while ((i<=size(F)) and (t))
386  {
387      if (F[i]!=G[i]){t=0;}
388    i++;
389  }
390  return(t);
391}
392
393// returns 1 if the two lists of ideals are equal and 0 if not
394static proc equallistideals(list L, list M)
395{
396  int t; int i;
397  if (size(L)!=size(M)){return(0);}
398  else
399  {
400    t=1;
401    if (size(L)>0)
402    {
403      i=1;
404      while ((t) and (i<=size(L)))
405      {
406        if (equalideals(L[i],M[i])==0){t=0;}
407        i++;
408      }
409    }
410    return(t);
411  }
412}
413
414// idcontains
415// Input: ideal p, ideal q
416// Output: 1 if p contains q,  0 otherwise
417// If the routine is to be called from the top, a previous call to
418static proc idcontains(ideal p, ideal q)
419{
420  int t; int i;
421  t=1; i=1;
422  def P=p; def Q=q;
423  attrib(P,"isSB",1);
424  poly r;
425  while ((t) and (i<=size(Q)))
426  {
427    r=reduce(Q[i],P,5);
428    if (r!=0){t=0;}
429    i++;
430  }
431  return(t);
432}
433
434// selectminideals
435//   given a list of ideals returns the list of integers corresponding
436//   to the minimal ideals in the list
437// Input: L (list of ideals)
438// Output: the list of integers corresponding to the minimal ideals in L
439//   Works in Q[u_1,..,u_m]
440static proc selectminideals(list L)
441{
442  list P; int i; int j; int t;
443  if(size(L)==0){return(L)};
444  if(size(L)==1){P[1]=1; return(P);}
445  for (i=1;i<=size(L);i++)
446  {
447    t=1;
448    j=1;
449    while ((t) and (j<=size(L)))
450    {
451      if (i!=j)
452      {
453        if(idcontains(L[i],L[j])==1)
454        {
455          t=0;
456        }
457      }
458      j++;
459    }
460    if (t){P[size(P)+1]=i;}
461  }
462  return(P);
463}
464
465static proc memberpos(f,J)
466//"USAGE:  memberpos(f,J);
467//         (f,J) expected (polynomial,ideal)
468//               or       (int,list(int))
469//               or       (int,intvec)
470//               or       (intvec,list(intvec))
471//               or       (list(int),list(list(int)))
472//               or       (ideal,list(ideal))
473//               or       (list(intvec),  list(list(intvec))).
474//         Works in any kind of ideals
475//RETURN:  The list (t,pos) t int; pos int;
476//         t is 1 if f belongs to J and 0 if not.
477//         pos gives the position in J (or 0 if f does not belong).
478//EXAMPLE: memberpos; shows an example"
479{
480  int pos=0;
481  int i=1;
482  int j;
483  int t=0;
484  int nt;
485  if (typeof(J)=="ideal"){nt=ncols(J);}
486  else{nt=size(J);}
487  if ((typeof(f)=="poly") or (typeof(f)=="int"))
488  { // (poly,ideal)  or
489    // (poly,list(poly))
490    // (int,list(int)) or
491    // (int,intvec)
492    i=1;
493    while(i<=nt)
494    {
495      if (f==J[i]){return(list(1,i));}
496      i++;
497    }
498    return(list(0,0));
499  }
500  else
501  {
502    if ((typeof(f)=="intvec") or ((typeof(f)=="list") and (typeof(f[1])=="int")))
503    { // (intvec,list(intvec)) or
504      // (list(int),list(list(int)))
505      i=1;
506      t=0;
507      pos=0;
508      while((i<=nt) and (t==0))
509      {
510        t=1;
511        j=1;
512        if (size(f)!=size(J[i])){t=0;}
513        else
514        {
515          while ((j<=size(f)) and t)
516          {
517            if (f[j]!=J[i][j]){t=0;}
518            j++;
519          }
520        }
521        if (t){pos=i;}
522        i++;
523      }
524      if (t){return(list(1,pos));}
525      else{return(list(0,0));}
526    }
527    else
528    {
529      if (typeof(f)=="ideal")
530      { // (ideal,list(ideal))
531        i=1;
532        t=0;
533        pos=0;
534        while((i<=nt) and (t==0))
535        {
536          t=1;
537          j=1;
538          if (ncols(f)!=ncols(J[i])){t=0;}
539          else
540          {
541            while ((j<=ncols(f)) and t)
542            {
543              if (f[j]!=J[i][j]){t=0;}
544              j++;
545            }
546          }
547          if (t){pos=i;}
548          i++;
549        }
550        if (t){return(list(1,pos));}
551        else{return(list(0,0));}
552      }
553      else
554      {
555        if ((typeof(f)=="list") and (typeof(f[1])=="intvec"))
556        { // (list(intvec),list(list(intvec)))
557          i=1;
558          t=0;
559          pos=0;
560          while((i<=nt) and (t==0))
561          {
562            t=1;
563            j=1;
564            if (size(f)!=size(J[i])){t=0;}
565            else
566            {
567              while ((j<=size(f)) and t)
568              {
569                if (f[j]!=J[i][j]){t=0;}
570                j++;
571              }
572            }
573            if (t){pos=i;}
574            i++;
575          }
576          if (t){return(list(1,pos));}
577          else{return(list(0,0));}
578        }
579      }
580    }
581  }
582}
583//example
584//{ "EXAMPLE:"; echo = 2;
585//  list L=(7,4,5,1,1,4,9);
586//  memberpos(1,L);
587//}
588
589// Auxiliary routine
590// pos
591// Input:  intvec p of zeros and ones
592// Output: intvec W of the positions where p has ones.
593static proc pos(intvec p)
594{
595  int i;
596  intvec W; int j=1;
597  for (i=1; i<=size(p); i++)
598  {
599    if (p[i]==1){W[j]=i; j++;}
600  }
601  return(W);
602}
603
604// Input:
605//  A,B: lists of ideals
606// Output:
607//   1 if both lists of ideals are equal, or 0 if not
608static proc equallistsofideals(list A, list B)
609{
610 int i;
611 int tes=0;
612 if (size(A)!=size(B)){return(tes);}
613 tes=1; i=1;
614 while(tes==1 and i<=size(A))
615 {
616   if (equalideals(A[i],B[i])==0){tes=0; return(tes);}
617   i++;
618 }
619 return(tes);
620}
621
622// Input:
623//  A,B:  lists of P-rep, i.e. of the form [p_i,[p_{i1},..,p_{ij_i}]]
624// Output:
625//   1 if both lists of P-reps are equal, or 0 if not
626static proc equallistsA(list A, list B)
627{
628  int tes=0;
629  if(equalideals(A[1],B[1])==0){return(tes);}
630  tes=equallistsofideals(A[2],B[2]);
631  return(tes);
632}
633
634// Input:
635//  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}]]
636// Output:
637//   1 if both lists of lists of P-rep are equal, or 0 if not
638static proc equallistsAall(list A,list B)
639{
640 int i; int tes;
641 if(size(A)!=size(B)){return(tes);}
642 tes=1; i=1;
643 while(tes and i<=size(A))
644 {
645   tes=equallistsA(A[i],B[i]);
646   i++;
647 }
648 return(tes);
649}
650
651// idint: ideal intersection
652//        in the ring @P.
653//        it works in an extended ring
654// input: two ideals in the ring @P
655// output the intersection of both (is not a GB)
656static proc idint(ideal I, ideal J)
657{
658  def RR=basering;
659  ring T=0,t,lp;
660  def K=T+RR;
661  setring(K);
662  def Ia=imap(RR,I);
663  def Ja=imap(RR,J);
664  ideal IJ;
665  int i;
666  for(i=1;i<=size(Ia);i++){IJ[i]=t*Ia[i];}
667  for(i=1;i<=size(Ja);i++){IJ[size(Ia)+i]=(1-t)*Ja[i];}
668  ideal eIJ=eliminate(IJ,t);
669  setring(RR);
670  return(imap(K,eIJ));
671}
672
673//purpose ideal intersection called in @R and computed in @P
674static proc idintR(ideal N, ideal M)
675{
676  def RR=basering;
677  def Rx=ringlist(RR);
678  def P=ring(Rx[1]);
679  setring(P);
680  def Np=imap(RR,N);
681  def Mp=imap(RR,M);
682  def Jp=idint(Np,Mp);
683  setring(RR);
684  return(imap(P,Jp));
685}
686
687// Auxiliary routine
688// comb: the list of combinations of elements (1,..n) of order p
689static proc comb(int n, int p)
690{
691  list L; list L0;
692  intvec c; intvec d;
693  int i; int j; int last;
694  if ((n<0) or (n<p))
695  {
696    return(L);
697  }
698  if (p==1)
699  {
700    for (i=1;i<=n;i++)
701    {
702      c=i;
703      L[size(L)+1]=c;
704    }
705    return(L);
706  }
707  else
708  {
709    L0=comb(n,p-1);
710    for (i=1;i<=size(L0);i++)
711    {
712      c=L0[i]; d=c;
713      last=c[size(c)];
714      for (j=last+1;j<=n;j++)
715      {
716        d[size(c)+1]=j;
717        L[size(L)+1]=d;
718      }
719    }
720    return(L);
721  }
722}
723
724// Auxiliary routine
725// combrep
726// Input: V=(n_1,..,n_i)
727// Output: L=(v_1,..,v_p) where p=prod_j=1^i (n_j)
728//    is the list of all intvec v_j=(v_j1,..,v_ji) where 1<=v_jk<=n_i
729static proc combrep(intvec V)
730{
731  list L; list LL;
732  int i; int j; int k;  intvec W;
733  if (size(V)==1)
734  {
735    for (i=1;i<=V[1];i++)
736    {
737      L[i]=intvec(i);
738    }
739    return(L);
740  }
741  for (i=1;i<size(V);i++)
742  {
743    W[i]=V[i];
744  }
745  LL=combrep(W);
746  for (i=1;i<=size(LL);i++)
747  {
748    W=LL[i];
749    for (j=1;j<=V[size(V)];j++)
750    {
751      W[size(V)]=j;
752      L[size(L)+1]=W;
753    }
754  }
755  return(L);
756}
757
758// input ideal J, ideal K
759// output 1 if all the polynomials in J are members of K
760//            0 if not
761static proc subset(J,K)
762//"USAGE:   subset(J,K);
763//          (J,K)  expected (ideal,ideal)
764//                  or     (list, list)
765//RETURN:   1 if all the elements of J are in K, 0 if not.
766//EXAMPLE:  subset; shows an example;"
767{
768  int i=1;
769  int nt;
770  if (typeof(J)=="ideal"){nt=ncols(J);}
771  else{nt=size(J);}
772  if (size(J)==0){return(1);}
773  while(i<=nt)
774  {
775    if (memberpos(J[i],K)[1]){i++;}
776    else {return(0);}
777  }
778  return(1);
779}
780//example
781//{ "EXAMPLE:"; echo = 2;
782//  list J=list(7,3,2);
783//  list K=list(1,2,3,5,7,8);
784//  subset(J,K);
785//}
786
787// cld : clears denominators of an ideal and normalizes to content 1
788//        can be used in @R or @P or @RP
789// input:
790//        ideal J (J can be also poly), but the output is an ideal;
791// output:
792//        ideal Jc (the new form of ideal J without denominators and
793//        normalized to content 1)
794static proc cld(ideal J)
795{
796  if (size(J)==0){return(ideal(0));}
797  int te=0;
798  def RR=basering;
799  def Rx=ringlist(RR);
800  if(size(Rx[1])==4)
801  {
802    te=1;
803    def P=ring(Rx[1]);
804    Rx[1]=0;
805    def D=ring(Rx);
806    def RP=D+P;
807    setring(RP);
808    def Ja=imap(RR,J);
809  }
810  else{ def Ja=J;}
811  ideal Jb;
812  if (size(Ja)==0){setring(RR); return(ideal(0));}
813  int i;
814  def j=0;
815  for (i=1;i<=ncols(Ja);i++){if (size(Ja[i])!=0){j++; Jb[j]=cleardenom(Ja[i]);}}
816  if(te==1)
817  {
818    setring(RR);
819    def Jc=imap(RP,Jb);
820  }
821  else{def Jc=Jb;}
822  // if(te){kill @R; kill @RP; kill @P;}
823  return(Jc);
824};
825
826// simpqcoeffs : simplifies a quotient of two polynomials
827// input: two coeficients (or terms), that are considered as a quotient
828// output: the two coeficients reduced without common factors
829static proc simpqcoeffs(poly n,poly m)
830{
831  def nc=content(n);
832  def mc=content(m);
833  def gc=gcd(nc,mc);
834  ideal s=n/gc,m/gc;
835  return (s);
836}
837
838// pdivi : pseudodivision of a parametric polynomial f by a parametric ideal F in Q[a][x].
839// input:
840//   poly  f
841//   ideal F
842// output:
843//   list (poly r, ideal q, poly mu)
844//   mu*f=sum(q_i*F_i)+r
845//   no monomial of r is divisible by no lpp of F
846proc pdivi(poly f,ideal F)
847"USAGE: pdivi(poly f,ideal F);
848          poly f: the polynomial in Q[a][x] to be divided
849          ideal F: the divisor ideal in Q[a][x].
850          (a=parameters, x=variables).
851RETURN: A list (poly r, ideal q, poly m). r is the remainder
852          of the pseudodivision, q is the set of quotients,
853          and m is the coefficient factor by which f is to
854          be multiplied.
855NOTE: pseudodivision of a poly f by an ideal F in Q[a][x].
856          Returns a list (r,q,m) such that
857          m*f=r+sum(q.F),
858          and no lpp of a divisor divides a pp of r.
859KEYWORDS: division; reduce
860EXAMPLE:  pdivi; shows an example"
861{
862  F=simplify(F,2);
863  int i;
864  int j;
865  poly v=1;
866  for(i=1;i<=nvars(basering);i++){v=v*var(i);}
867  poly r=0;
868  poly mu=1;
869  def p=f;
870  ideal q;
871  for (i=1; i<=ncols(F); i++){q[i]=0;};
872  ideal lpf;
873  ideal lcf;
874  for (i=1;i<=ncols(F);i++){lpf[i]=leadmonom(F[i]);}
875  for (i=1;i<=ncols(F);i++){lcf[i]=leadcoef(F[i]);}
876  poly lpp;
877  poly lcp;
878  poly qlm;
879  poly nu;
880  poly rho;
881  int divoc=0;
882  ideal qlc;
883  while (p!=0)
884  {
885    i=1;
886    divoc=0;
887    lpp=leadmonom(p);
888    lcp=leadcoef(p);
889    while (divoc==0 and i<=size(F))
890    {
891      qlm=lpp/lpf[i];
892      if (qlm!=0)
893      {
894        qlc=simpqcoeffs(lcp,lcf[i]);
895        //string("T_i=",i,";  qlc=",qlc);
896        nu=qlc[2];
897        mu=mu*nu;
898        rho=qlc[1]*qlm;
899        //"T_nu="; nu; "mu="; mu; "rho="; rho;
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        //"T_q[i]="; q[i];
905        divoc=1;
906      }
907      else {i++;}
908    }
909    if (divoc==0)
910    {
911      r=r+lcp*lpp;
912      p=p-lcp*lpp;
913    }
914    //"T_r="; r; "p="; p;
915  }
916  list res=r,q,mu;
917  return(res);
918}
919example
920{
921  echo = 2;
922  "EXAMPLE:";
923  if(defined(R)){kill R;}
924  ring R=(0,a,b,c),(x,y),dp;
925  short=0;
926  // Divisor
927  poly f=(ab-ac)*xy+(ab)*x+(5c);
928  // Dividends
929  ideal F=ax+b,cy+a;
930  // (Remainder, quotients, factor)
931  def r=pdivi(f,F);
932  r;
933  // Verifying the division
934  r[3]*f-(r[2][1]*F[1]+r[2][2]*F[2]+r[1]);
935}
936
937// pspol : S-poly of two polynomials in @R
938// @R
939// input:
940//   poly f (given in the ring @R)
941//   poly g (given in the ring @R)
942// output:
943//   list (S, red):  S is the S-poly(f,g) and red is a Boolean variable
944//                if red then S reduces by Buchberger 1st criterion
945//                (not used)
946static proc pspol(poly f,poly g)
947{
948  def lcf=leadcoef(f);
949  def lcg=leadcoef(g);
950  def lpf=leadmonom(f);
951  def lpg=leadmonom(g);
952  def v=gcd(lpf,lpg);
953  def s=simpqcoeffs(lcf,lcg);
954  def vf=lpf/v;
955  def vg=lpg/v;
956  poly S=s[2]*vg*f-s[1]*vf*g;
957  return(S);
958}
959
960// facvar: Returns all the free-square factors of the elements
961//         of ideal J (non repeated). Integer factors are ignored,
962//         even 0 is ignored. It can be called from ideal Q[a][x], but
963//         the given ideal J must only contain poynomials in the
964//         parameters a.
965//         Operates in the ring Q[a], but can be called from ring Q[a][x],
966// input:  ideal J
967// output: ideal Jc: Returns all the free-square factors of the elements
968//         of ideal J (non repeated). Integer factors are ignored,
969//         even 0 is ignored.
970static proc facvar(ideal J)
971//"USAGE:   facvar(J);
972//          J: an ideal in the parameters
973//RETURN:   all the free-square factors of the elements
974//          of ideal J (non repeated). Integer factors are ignored,
975//          even 0 is ignored. It can be called from ideal @R, but
976//          the given ideal J must only contain poynomials in the
977//          parameters.
978//NOTE:     Operates in the ring @P, and the ideal J must contain only
979//          polynomials in the parameters, but can be called from ring @R.
980//KEYWORDS: factor
981//EXAMPLE:  facvar; shows an example"
982{
983  int i;
984  def RR=basering;
985  def Rx=ringlist(RR);
986  def P=ring(Rx[1]);
987  setring(P);
988  def Ja=imap(RR,J);
989  if(size(Ja)==0){setring(RR); return(ideal(0));}
990  Ja=elimintfromideal(Ja); // also in ideal @P
991  ideal Jb;
992  if (size(Ja)==0){Jb=ideal(0);}
993  else
994  {
995    for (i=1;i<=ncols(Ja);i++){if(size(Ja[i])!=0){Jb=Jb,factorize(Ja[i],1);}}
996    Jb=simplify(Jb,2+4+8);
997    Jb=cld(Jb);
998    Jb=elimintfromideal(Jb); // also in ideal @P
999  }
1000  setring(RR);
1001  def Jc=imap(P,Jb);
1002  return(Jc);
1003}
1004//example
1005//{ "EXAMPLE:"; echo = 2;
1006//  ring R=(0,a,b,c),(x,y,z),dp;
1007//  setglobalrings();
1008//  ideal J=a2-b2,a2-2ab+b2,abc-bc;
1009//  facvar(J);
1010//}
1011
1012// Ered: eliminates the factors in the polynom f that are non-null.
1013//       In ring Q[a][x]
1014// input:
1015//   poly f:
1016//   ideal E  of null-conditions
1017//   ideal N  of non-null conditions
1018//        (E,N) represents V(E) \ V(N),
1019//        Ered eliminates the non-null factors of f in V(E) \ V(N)
1020// output:
1021//   poly f2  where the non-null conditions have been dropped from f
1022static proc Ered(poly f,ideal E, ideal N)
1023{
1024  def RR=basering;
1025  if((f==0) or (equalideals(N,ideal(1)))){ return(f);}
1026  def v=variables(f);
1027  int i;
1028  poly X=1;
1029  for(i=1;i<=size(v);i++){X=X*v[i];}
1030  matrix M=coef(f,X);
1031  poly g=M[2,1];
1032  if (size(M)!=2)
1033  {
1034    for(i=2;i<=size(M) div 2;i++)
1035    {
1036      g=gcd(g,M[2,i]);
1037    }
1038  }
1039  if (g==1){ return(f);}
1040  else
1041  {
1042    def wg=factorize(g,2);
1043    if (wg[1][1]==1){ return(f);}
1044    else
1045    {
1046      poly simp=1;
1047      int te;
1048      for(i=1;i<=size(wg[1]);i++)
1049      {
1050        te=inconsistent(RPE+wg[1][i],RPN);
1051        if(te)
1052        {
1053          simp=simp*(wg[1][i])^(wg[2][i]);
1054        }
1055      }
1056    }
1057    if (simp==1){ return(f);}
1058    else
1059    {
1060      //def simp0=imap(P,simp);
1061      def f2=f/simp;
1062      return(f2);
1063    }
1064  }
1065}
1066
1067// pnormalf: reduces a polynomial f wrt a V(E) \ V(N)
1068//           dividing by E and eliminating factors in N.
1069//           called in the ring @R,
1070//           operates in the ring @RP.
1071// input:
1072//         poly  f
1073//         ideal E  (depends only on the parameters)
1074//         ideal N  (depends only on the parameters)
1075//                  (E,N) represents V(E) \ V(N)
1076//         optional:
1077// output: poly f2 reduced wrt to V(E) \ V(N)
1078proc pnormalf(poly f, ideal E, ideal N)
1079"USAGE: pnormalf(poly f,ideal E,ideal N);
1080          f: the polynomial in Q[a][x]  (a=parameters,
1081          x=variables) to be reduced modulo V(E) \ V(N)
1082          of a segment in Q[a].
1083          E: the null conditions ideal in Q[a]
1084          N: the non-null conditions in Q[a]
1085RETURN: a reduced polynomial g of f, whose coefficients are
1086          reduced modulo E and having no factor in N.
1087NOTE: Should be called from ring Q[a][x]. Ideals E and N must
1088          be given by polynomials in Q[a].
1089KEYWORDS: division; pdivi; reduce
1090EXAMPLE: pnormalf; shows an example"
1091{
1092    def RR=basering;
1093    int te=0;
1094    def Rx=ringlist(RR);
1095    def P=ring(Rx[1]);
1096    Rx[1]=0;
1097    def D=ring(Rx);
1098    def RP=D+P;
1099    setring(RP);
1100    def fa=imap(RR,f);
1101    def Ea=imap(RR,E);
1102    def Na=imap(RR,N);
1103    option(redSB);
1104    Ea=std(Ea);
1105    def r=cld(reduce(fa,Ea));
1106    poly f1=r[1];
1107    f1=Ered(r[1],Ea,Na);
1108    setring(RR);
1109    def f2=imap(RP,f1);
1110    // if(te==0){kill @R; kill @RP; kill @P;}
1111    return(f2)
1112};
1113example
1114{
1115"EXAMPLE:"; echo = 2;
1116  if(defined(R)){kill R;}
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 p=c-1;
1121  ideal q=a-b;
1122  pnormalf(f,p,q);
1123}
1124
1125// lesspol: compare two polynomials by its leading power products
1126// input:  two polynomials f,g in the ring @R
1127// output: 0 if f<g,  1 if f>=g
1128static proc lesspol(poly f, poly g)
1129{
1130  if (leadmonom(f)<leadmonom(g)){return(1);}
1131  else
1132  {
1133    if (leadmonom(g)<leadmonom(f)){return(0);}
1134    else
1135    {
1136      if (leadcoef(f)<leadcoef(g)){return(1);}
1137      else {return(0);}
1138    }
1139  }
1140};
1141
1142// sortideal: sorts the polynomials in an ideal by lm in ascending order
1143static proc sortideal(ideal Fi)
1144{
1145  def RR=basering;
1146  def Rx=ringlist(RR);
1147  def P=ring(Rx[1]);
1148  Rx[1]=0;
1149  def D=ring(Rx);
1150  def RP=D+P;
1151  setring(RP);
1152  def F=imap(RR,Fi);
1153  def H=F;
1154  ideal G;
1155  int i;
1156  int j;
1157  poly p;
1158  while (size(H)!=0)
1159  {
1160    j=1;
1161    p=H[1];
1162    for (i=1;i<=ncols(H);i++)
1163    {
1164      if(lesspol(H[i],p)){j=i;p=H[j];}
1165    }
1166    G[ncols(G)+1]=p;
1167    H=delfromideal(H,j);
1168    H=simplify(H,2);
1169  }
1170  setring(RR);
1171  def GG=imap(RP,G);
1172  GG=simplify(GG,2);
1173  return(GG);
1174}
1175
1176// mingb: given a basis (gb reducing) it
1177// order the polynomials in ascending order and
1178// eliminates the polynomials whose lpp are divisible by some
1179// smaller one
1180static proc mingb(ideal F)
1181{
1182  int t; int i; int j;
1183  def H=sortideal(F);
1184  ideal G;
1185  if (ncols(H)<=1){return(H);}
1186  G=H[1];
1187  for (i=2; i<=ncols(H); i++)
1188  {
1189    t=1;
1190    j=1;
1191    while (t and (j<i))
1192    {
1193      if((leadmonom(H[i])/leadmonom(H[j]))!=0) {t=0;}
1194      j++;
1195    }
1196    if (t) {G[size(G)+1]=H[i];}
1197  }
1198  return(G);
1199}
1200
1201// redgbn: given a minimal basis (gb reducing) it
1202// reduces each polynomial wrt to V(E) \ V(N)
1203static proc redgbn(ideal F, ideal E, ideal N)
1204{
1205  int te=0;
1206  ideal G=F;
1207  ideal H;
1208  int i;
1209  if (size(G)==0){return(ideal(0));}
1210  for (i=1;i<=size(G);i++)
1211  {
1212    H=delfromideal(G,i);
1213    G[i]=pnormalf(pdivi(G[i],H)[1],E,N);
1214    G[i]=primepartZ(G[i]);
1215  }
1216  // if(te==1){setglobalrings();}
1217  return(G);
1218}
1219
1220//**************Begin homogenizing************************
1221
1222// ishomog:
1223// Purpose: test if a polynomial is homogeneous in the variables or not
1224// input:  poly f
1225// output  1 if f is homogeneous, 0 if not
1226static proc ishomog(f)
1227{
1228  int i; poly r; int d; int dr;
1229  if (f==0){return(1);}
1230  d=deg(f); dr=d; r=f;
1231  while ((d==dr) and (r!=0))
1232  {
1233    r=r-lead(r);
1234    dr=deg(r);
1235  }
1236  if (r==0){return(1);}
1237  else{return(0);}
1238}
1239
1240// postredgb: given a minimal basis (gb reducing) it
1241// reduces each polynomial wrt to the others
1242static proc postredgb(ideal F)
1243{
1244  int te=0;
1245  ideal G;
1246  ideal H;
1247  int i;
1248  if (size(F)==0){return(ideal(0));}
1249  for (i=1;i<=size(F);i++)
1250  {
1251    H=delfromideal(F,i);
1252    G[i]=pdivi(F[i],H)[1];
1253  }
1254  return(G);
1255}
1256
1257
1258//purpose reduced Groebner basis called in @R and computed in @P
1259static proc gbR(ideal N)
1260{
1261  def RR=basering;
1262  def Rx=ringlist(RR);
1263  def P=ring(Rx[1]);
1264  setring(P);
1265  def Np=imap(RR,N);
1266  option(redSB);
1267  Np=std(Np);
1268  setring(RR);
1269  return(imap(P,Np));
1270}
1271
1272//**************End homogenizing************************
1273
1274//**************Begin of Groebner Cover*****************
1275
1276// incquotient
1277// incremental quotient
1278// Input: ideal N: a Groebner basis of an ideal
1279//        poly f:
1280// Output: Na = N:<f>
1281static proc incquotient(ideal N, poly f)
1282{
1283  poly g; int i;
1284  ideal Nb; ideal Na=N;
1285  if (size(Na)==1)
1286  {
1287    g=gcd(Na[1],f);
1288    if (g!=1)
1289    {
1290      Na[1]=Na[1]/g;
1291    }
1292    attrib(Na,"IsSB",1);
1293    return(Na);
1294  }
1295  def P=basering;
1296  poly @t;
1297  ring H=0,@t,lp;
1298  def HP=H+P;
1299  setring(HP);
1300  def fh=imap(P,f);
1301  def Nh=imap(P,N);
1302  ideal Nht;
1303  for (i=1;i<=size(Nh);i++)
1304  {
1305    Nht[i]=Nh[i]*@t;
1306  }
1307  attrib(Nht,"isSB",1);
1308  def fht=(1-@t)*fh;
1309  option(redSB);
1310  Nht=std(Nht,fht);
1311  ideal Nc; ideal v;
1312  for (i=1;i<=size(Nht);i++)
1313  {
1314    v=variables(Nht[i]);
1315    if(memberpos(@t,v)[1]==0)
1316    {
1317      Nc[size(Nc)+1]=Nht[i]/fh;
1318    }
1319  }
1320  setring(P);
1321  ideal HH;
1322  def Nd=imap(HP,Nc); Nb=Nd;
1323  option(redSB);
1324  Nb=std(Nd);
1325  return(Nb);
1326}
1327
1328// Auxiliary routine to define an order for ideals
1329// Returns 1 if the ideal a is shoud precede ideal b by sorting them in idbefid order
1330//             2 if the the contrary happen
1331//             0 if the order is not relevant
1332static proc idbefid(ideal a, ideal b)
1333{
1334  poly fa; poly fb; poly la; poly lb;
1335  int te=1; int i; int j;
1336  int na=size(a);
1337  int nb=size(b);
1338  int nm;
1339  if (na<=nb){nm=na;} else{nm=nb;}
1340  for (i=1;i<=nm; i++)
1341  {
1342    fa=a[i]; fb=b[i];
1343    while((fa!=0) or (fb!=0))
1344    {
1345      la=lead(fa);
1346      lb=lead(fb);
1347      fa=fa-la;
1348      fb=fb-lb;
1349      la=leadmonom(la);
1350      lb=leadmonom(lb);
1351      if(leadmonom(la+lb)!=la){return(1);}
1352      else{if(leadmonom(la+lb)!=lb){return(2);}}
1353    }
1354  }
1355  if(na<nb){return(1);}
1356  else
1357  {
1358    if(na>nb){return(2);}
1359    else{return(0);}
1360  }
1361}
1362
1363// sort a list of ideals using idbefid
1364static proc sortlistideals(list L)
1365{
1366  int i; int j; int n;
1367  ideal a; ideal b;
1368  list LL=L;
1369  list NL;
1370  int k; int te;
1371  i=1;
1372  while(size(LL)>0)
1373  {
1374    k=1;
1375    for(j=2;j<=size(LL);j++)
1376    {
1377      te=idbefid(LL[k],LL[j]);
1378      if (te==2){k=j;}
1379    }
1380    NL[size(NL)+1]=LL[k];
1381    n=size(LL);
1382    if (n>1){LL=elimfromlist(LL,k);} else{LL=list();}
1383  }
1384  return(NL);
1385}
1386
1387// Crep
1388// Computes the C-representation of V(N) \ V(M).
1389// input:
1390//    ideal N (null ideal) (not necessarily radical nor maximal)
1391//    ideal M (hole ideal) (not necessarily containing N)
1392// output:
1393//    the list (a,b) of the canonical ideals
1394//    the Crep of V(N) \ V(M)
1395// Assumed to be called in the ring Q[a] or Q[x]
1396proc Crep(ideal N, ideal M)
1397"USAGE:  Crep(ideal N,ideal M);
1398        ideal N (null ideal) (not necessarily radical nor
1399        maximal) in Q[a]. (a=parameters, x=variables).
1400        ideal M (hole ideal) (not necessarily containing N)
1401        in Q[a]. To be called in a ring Q[a][x] or a ring Q[a].
1402        But the ideals can contain only the parameters
1403        in Q[a].
1404RETURN: The canonical C-representation [P,Q] of the
1405        locally closed set, formed by a pair of radical
1406        ideals with P included in Q, representing the set
1407        V(P) \ V(Q) = V(N) \ V(M)
1408KEYWORDS: locally closed set; canoncial form
1409EXAMPLE:  Crep; shows an example"
1410{
1411  int te;
1412  def RR=basering;
1413  def Rx=ringlist(RR);
1414  if(size(Rx[1])==4)
1415  { te=1;
1416    def P=ring(Rx[1]);
1417  }
1418  if(te==1)
1419  {
1420    setring(P); ideal Np=imap(RR,N); ideal Mp=imap(RR,M);
1421  }
1422  else {te=0; def Np=N; def Mp=M;}
1423  def La=Crep0(Np,Mp);
1424  if(size(La)==0)
1425  {
1426    if(te==1) {setring(RR); list LL;}
1427    if(te==0){list LL;}
1428    return(LL);
1429  }
1430  else
1431  {
1432    if(te==1) {setring(RR); def LL=imap(P,La);}
1433    if(te==0){def LL=La;}
1434  return(LL);
1435  }
1436}
1437example
1438{
1439  "EXAMPLE:"; echo = 2;
1440  short=0;
1441  if(defined(R)){kill R;}
1442  ring R=0,(a,b,c),lp;
1443  ideal p=a*b;
1444  ideal q=a,b-2;;
1445  Crep(p,q);
1446}
1447
1448// Crep0
1449// Computes the C-representation of V(N) \ V(M).
1450// input:
1451//    ideal N (null ideal) (not necessarily radical nor maximal)
1452//    ideal M (hole ideal) (not necessarily containing N)
1453// output:
1454//    the list (a,b) of the canonical ideals
1455//    the Crep0 of V(N) \ V(M)
1456// Assumed to be called in a ring Q[x] (example @P)
1457static proc Crep0(ideal N, ideal M)
1458{
1459  list l;
1460  ideal Np=std(N);
1461  if (equalideals(Np,ideal(1)))
1462  {
1463    l=ideal(1),ideal(1);
1464    return(l);
1465  }
1466  int i;
1467  list L;
1468  ideal Q=Np+M;
1469  ideal P=ideal(1);
1470  L=minGTZ(Np);
1471  for(i=1;i<=size(L);i++)
1472  {
1473    L[i]=std(L[i]);
1474    if(idcontains(L[i],Q)==0)
1475    {
1476      P=intersect(P,L[i]);
1477    }
1478  }
1479  P=std(P);
1480  Q=std(radical(Q+P));
1481  if(equalideals(P,Q)){return(l);}
1482  list T=P,Q;
1483  return(T);
1484}
1485
1486// Prep
1487// Computes the P-representation of V(N) \ V(M).
1488// input:
1489//    ideal N (null ideal) (not necessarily radical nor maximal)
1490//    ideal M (hole ideal) (not necessarily containing N)
1491// output:
1492//    the ((p_1,(p_11,p_1k_1)),..,(p_r,(p_r1,p_rk_r)));
1493//    the Prep of V(N) \ V(M)
1494// Assumed to be called in the ring ring Q[a][x]. But the data must only contain parameters.
1495proc Prep(ideal N, ideal M)
1496"USAGE: Prep(ideal N,ideal M);
1497       ideal N (null ideal) (not necessarily radical nor
1498       maximal) in Q[a]. (a=parameters, x=variables).
1499       ideal M (hole ideal) (not necessarily containing N)
1500       in Q[a]. To be called in a ring Q[a][x] or a ring
1501       Q[a]. But the ideals can contain only the
1502       parameters in Q[a].
1503RETURN: The canonical P-representation of the locally closed
1504       set V(N) \ V(M)
1505       Output: [Comp_1, .. , Comp_s ] where
1506       Comp_i=[p_i,[p_i1,..,p_is_i]]
1507KEYWORDS: locally closed set; canoncial form
1508EXAMPLE:  Prep; shows an example"
1509{
1510  int te;
1511  def RR=basering;
1512  def Rx=ringlist(RR);
1513  if(size(Rx[1])==4)
1514  {
1515    def P=ring(Rx[1]);
1516    te=1; setring(P); ideal Np=imap(RR,N); ideal Mp=imap(RR,M);
1517  }
1518  else {te=0; def Np=N; def Mp=M;}
1519  def La=Prep0(Np,Mp);
1520  if(te==1) {setring(RR); def LL=imap(P,La); }
1521  if(te==0){def LL=La;}
1522  return(LL);
1523}
1524example
1525{
1526  "EXAMPLE:"; echo = 2;
1527  short=0;
1528  if(defined(R)){kill R;}
1529  ring R=0,(a,b,c),lp;
1530  ideal p=a*b;;
1531  ideal q=a,b-1;
1532  Prep(p,q);
1533}
1534
1535// Prep0
1536// Computes the P-representation of V(N) \ V(M).
1537// input:
1538//    ideal N (null ideal) (not necessarily radical nor maximal)
1539//    ideal M (hole ideal) (not necessarily containing N)
1540// output:
1541//    the ((p_1,(p_11,p_1k_1)),..,(p_r,(p_r1,p_rk_r)));
1542//    the Prep of V(N) \ V(M)
1543// Assumed to be called in a ring Q[x] (example @P)
1544static proc Prep0(ideal N, ideal M)
1545{
1546  int te;
1547  if (N[1]==1)
1548  {
1549    return(list(list(ideal(1),list(ideal(1)))));
1550  }
1551  int i; int j; list L0;
1552  list Ni=minGTZ(N);
1553  list prep;
1554  for(j=1;j<=size(Ni);j++)
1555  {
1556    option(redSB);
1557    Ni[j]=std(Ni[j]);
1558  }
1559  list Mij;
1560  for (i=1;i<=size(Ni);i++)
1561  {
1562    Mij=minGTZ(Ni[i]+M);
1563    for(j=1;j<=size(Mij);j++)
1564    {
1565      option(redSB);
1566      Mij[j]=std(Mij[j]);
1567    }
1568    if ((size(Mij)==1) and (equalideals(Ni[i],Mij[1])==1)){;}
1569    else
1570    {
1571        prep[size(prep)+1]=list(Ni[i],Mij);
1572    }
1573  }
1574  //"T_before="; prep;
1575  if (size(prep)==0){prep=list(list(ideal(1),list(ideal(1))));}
1576  //"T_Prep="; prep;
1577  //def Lout=CompleteA(prep,prep);
1578  //"T_Lout="; Lout;
1579  return(prep);
1580}
1581
1582// PtoCrep
1583// Computes the C-representation from the P-representation.
1584// input:
1585//    list ((p_1,(p_11,p_1k_1)),..,(p_r,(p_r1,p_rk_r)));
1586//         the P-representation of V(N) \ V(M)
1587// output:
1588//    list (ideal ida, ideal idb)
1589//    the C-representaion of V(N) \ V(M) = V(ida) \ V(idb)
1590// Assumed to be called in the ring Q[a] or Q[x]
1591proc PtoCrep(list L)
1592"USAGE: PtoCrep(list L)
1593       list L=  [ Comp_1, .. , Comp_s ] where
1594       list Comp_i=[p_i,[p_i1,..,p_is_i] ], is the
1595       P-representation of a locally closed set
1596       V(N) \ V(M). To be called in a ring Q[a][x]
1597       or a ring Q[a]. But the ideals can contain
1598       only the parameters in Q[a].
1599RETURN:The canonical C-representation [P,Q] of the
1600       locally closed set. A pair of radical ideals with
1601       P included in Q, representing the
1602       set V(P) \ V(Q)
1603KEYWORDS: locally closed set; canoncial form
1604EXAMPLE:  PtoCrep; shows an example"
1605{
1606  int te;
1607  def RR=basering;
1608  def Rx=ringlist(RR);
1609  if(size(Rx[1])==0){return(PtoCrep0(L));}
1610  else
1611  {
1612    def P=ring(Rx[1]);
1613    setring(P);
1614    list Lp=imap(RR,L);
1615    def LLp=PtoCrep0(Lp);
1616    setring(RR);
1617    def LL=imap(P,LLp);
1618    return(LL);
1619  }
1620}
1621example
1622{
1623 "EXAMPLE:"; echo = 2;
1624  if(defined(R)){kill R;}
1625  ring R=0,(a,b,c),lp;
1626  short=0;
1627  ideal p=a*(a^2+b^2+c^2-25);
1628  ideal q=a*(a-3),b-4;
1629  def Cr=Crep(p,q);
1630  Cr;
1631  def L=Prep(p,q);
1632  L;
1633  PtoCrep(L);
1634}
1635
1636// PtoCrep0
1637// Computes the C-representation from the P-representation.
1638// input:
1639//    list ((p_1,(p_11,p_1k_1)),..,(p_r,(p_r1,p_rk_r)));
1640//         the P-representation of V(N) \ V(M)
1641// output:
1642//    list (ideal ida, ideal idb)
1643//    the C-representation of V(N) \ V(M) = V(ida) \ V(idb)
1644// Assumed to be called in a ring Q[x] (example @P)
1645static proc PtoCrep0(list L)
1646{
1647  int te=0;
1648  def Lp=L;
1649  int i; int j;
1650  ideal ida=ideal(1); ideal idb=ideal(1); list Lb; ideal N;
1651  for (i=1;i<=size(Lp);i++)
1652  {
1653    option(returnSB);
1654    //"T_Lp[i]="; Lp[i];
1655    N=Lp[i][1];
1656    Lb=Lp[i][2];
1657    //"T_Lb="; Lb;
1658    ida=intersect(ida,N);
1659    for(j=1;j<=size(Lb);j++)
1660    {
1661      idb=intersect(idb,Lb[j]);
1662    }
1663  }
1664  //idb=radical(idb);
1665  def La=list(ida,idb);
1666  return(La);
1667}
1668
1669// input: F a parametric ideal in Q[a][x]
1670// output: a disjoint and reduced Groebner System.
1671//      It uses Kapur-Sun-Wang algorithm, and with the options
1672//      can compute the homogenization before  (('can',0) or ( 'can',1))
1673//      and dehomogenize the result.
1674proc cgsdr(ideal F, list #)
1675"USAGE: cgsdr(ideal F);
1676       F: ideal in Q[a][x] (a=parameters, x=variables) to be
1677       discussed. Computes a disjoint, reduced Comprehensive
1678       Groebner System (CGS). cgsdr is the starting point of
1679       the fundamental routine grobcov.
1680       The basering R, must be of the form Q[a][x],
1681       (a=parameters, x=variables),
1682       and should be defined previously.
1683RETURN: Returns a list T describing a reduced and disjoint
1684       Comprehensive Groebner System (CGS). The output
1685       is a list of  (full,hole,basis), where the  ideals
1686       full and hole represent the segment V(full) \ V(hole).
1687       With option (\"out\",0) the segments are grouped
1688       by leading power products (lpp) of the reduced
1689       Groebner basis and given in P-representation.
1690       The returned list is of the form:
1691        [ [lpp, [num,basis,segment],...,
1692                [num,basis,segment],lpph],  ... ,
1693          [lpp, [num,basis,segment],...,
1694                [num,basis,segment],lpph] ].
1695       The bases are the reduced Groebner bases (after
1696       normalization) for each point of the corresponding
1697       segment. The third element lpph of each lpp
1698       segment is the lpp of the homogenized ideal
1699       used ideal in the CGS  as a string, that
1700       is shown only when option  (\"can\",1) is used.
1701       With option (\"can\",0) the homogenized basis is used.
1702       With option (\"can\",1) the homogenized ideal is used.
1703       With option (\"can\",2) the given basis is used.
1704       With option (\"out\",1) (default) only KSW is applied and
1705       segments are given as difference of varieties and are
1706       not grouped The returned list is of the form:
1707       [[E,N,B],..[E,N,B]]
1708       E is the top variety
1709       N is the hole variety.
1710       Segment = V(E) \ V(N)
1711       B is the reduced Groebner basis
1712OPTIONS:  An option is a pair of arguments: string, integer.
1713       To modify the default options, pairs of arguments
1714       -option name, value- of valid options must be
1715       added to the call. Inside grobcov the default option
1716       is \"can\",1. It can be used also with option
1717       \"can\",0 but then the output is not the canonical
1718       Groebner Cover. grobcov cannot be used with
1719       option \"can\",2.
1720       When cgsdr is called directly, the options are
1721       \"can\",0-1-2: The default value is \"can\",2.
1722       In this case no homogenization is done. With option
1723       (\"can\",0) the given basis is homogenized,
1724       and with option (\"can\",1) the whole given ideal
1725       is homogenized before computing the cgs
1726       and dehomogenized after.
1727       With option (\"can\",0) the homogenized basis is used.
1728       With option (\"can\",1) the homogenized ideal is used.
1729       With option (\"can\",2) the given basis is used.
1730       \"null\",ideal E: The default is (\"null\",ideal(0)).
1731       \"nonnull\",ideal N: The default (\"nonnull\",ideal(1)).
1732       When options \"null\" and/or \"nonnull\" are given,
1733       then the parameter space is restricted to V(E) \ V(N).
1734       \"comment\",0-1: The default is (\"comment\",0).
1735       Setting (\"comment\",1) will provide information
1736       about the development of the computation.
1737       \"out\",0-1: (default is 1) the output segments are
1738       given as as difference of varieties.
1739       With option \"out\",0 the output segments are
1740       given in P-representation and  the segments
1741       grouped by lpp.
1742       With options (\"can\",0) and (\"can\",1) the option
1743       (\"out\",1) is set to (\"out\",0) because
1744       it is not compatible.
1745       One can give none or whatever of these options.
1746       With the default options (\"can\",2,\"out\",1),
1747       only the Kapur-Sun-Wang algorithm is computed.
1748       The algorithm used is:
1749          D. Kapur, Y. Sun, and D.K. Wang \"A New Algorithm
1750          for  Computing Comprehensive Groebner Systems\".
1751          Proceedings of ISSAC'2010, ACM Press, (2010), 29-36.
1752       It is very efficient but is only the starting point
1753       for the computation of grobcov.
1754       When grobcov is computed, the call to cgsdr
1755       inside uses specific options that are
1756       more expensive (\"can\",0-1,\"out\",0).
1757KEYWORDS: CGS; disjoint; reduced; Comprehensive Groebner System
1758EXAMPLE:  cgsdr; shows an example"
1759{
1760  int te;
1761  def RR=basering;
1762  def Rx=ringlist(RR);
1763  def P=ring(Rx[1]);
1764  // if(size(Rx[1])==4){te=1; Rx[1]=0; def D=ring(Rx); def RP=D+P;}
1765  // else{te=0;} //setglobalrings();}
1766  // INITIALIZING OPTIONS
1767  int i; int j;
1768  def E=ideal(0);
1769  def N=ideal(1);
1770  int comment=0;
1771  int can=2;
1772  int out=1;
1773  poly f;
1774  ideal B;
1775  int start=timer;
1776  list L=#;
1777  for(i=1;i<=size(L) div 2;i++)
1778  {
1779    if(L[2*i-1]=="null"){E=L[2*i];}
1780    else
1781    {
1782      if(L[2*i-1]=="nonnull"){N=L[2*i];}
1783      else
1784      {
1785        if(L[2*i-1]=="comment"){comment=L[2*i];}
1786        else
1787        {
1788          if(L[2*i-1]=="can"){can=L[2*i];}
1789          else
1790          {
1791            if(L[2*i-1]=="out"){out=L[2*i];}
1792          }
1793        }
1794      }
1795    }
1796  }
1797  //if(can==2){out=1;}
1798  B=F;
1799  if ((printlevel) and (comment==0)){comment=printlevel;}
1800  if((can<2) and (out>0)){"Option out,1 is not compatible with can,0,1"; out=0;}
1801  // DEFINING OPTIONS
1802  list LL;
1803  LL[1]="can";     LL[2]=can;
1804  LL[3]="comment"; LL[4]=comment;
1805  LL[5]="out";     LL[6]=out;
1806  LL[7]="null";    LL[8]=E;
1807  LL[9]="nonnull"; LL[10]=N;
1808  if(comment>=1)
1809  {
1810    " "; string("Begin cgsdr with options: ",LL);
1811  }
1812  int ish;
1813  for (i=1;i<=size(B);i++){ish=ishomog(B[i]); if(ish==0){break;};}
1814  if (ish)
1815  {
1816    if(comment>0){" "; string("The given system is homogneous");}
1817    def GS=KSW(B,LL);
1818    //can=0;
1819  }
1820  else
1821  {
1822  // ACTING DEPENDING ON OPTIONS
1823  if(can==2)
1824  {
1825    // WITHOUT HOMOHGENIZING
1826    if(comment>0){" "; string("Option of cgsdr: do not homogenize");}
1827    def GS=KSW(B,LL);
1828    // setglobalrings();
1829  }
1830  else
1831  {
1832    if(can==1)
1833    {
1834      // COMPUTING THE HOMOGOENIZED IDEAL
1835      if(comment>0){" "; string("Homogenizing the whole ideal: option can=1");}
1836      list RRL=ringlist(RR);
1837      RRL[3][1][1]="dp";
1838      def Pa=ring(RRL[1]);
1839      list Lx;
1840      Lx[1]=0;
1841      Lx[2]=RRL[2]+RRL[1][2];
1842      Lx[3]=RRL[1][3];
1843      Lx[4]=RRL[1][4];
1844      RRL[1]=0;
1845      def D=ring(RRL);
1846      def RP=D+Pa;
1847      setring(RP);
1848      def B1=imap(RR,B);
1849      option(redSB);
1850      if(comment>0){" ";string("Basis before computing its std basis="); B1;}
1851      B1=std(B1);
1852      if(comment>0){" ";string("Basis after computing its std basis="); B1;}
1853      setring(RR);
1854      def B2=imap(RP,B1);
1855    }
1856    else
1857    { // (can=0)
1858       if(comment>0){" "; string( "Homogenizing the basis: option can=0");}
1859      def B2=B;
1860    }
1861    // COMPUTING HOMOGENIZED CGS
1862    poly @t;
1863    ring H=0,@t,dp;
1864    def RH=RR+H;
1865    setring(RH);
1866    // setglobalrings();
1867    def BH=imap(RR,B2);
1868    def LH=imap(RR,LL);
1869    for (i=1;i<=size(BH);i++)
1870    {
1871      BH[i]=homog(BH[i],@t);
1872    }
1873    if (comment>0){" "; string("Homogenized system = "); BH;}
1874    def RHx=ringlist(RH);
1875    def PH=ring(RHx[1]);
1876    RHx[1]=0;
1877    def DH=ring(RHx);
1878    def RPH=DH+PH;
1879    def GSH=KSW(BH,LH);
1880    //setglobalrings();
1881    // DEHOMOGENIZING THE RESULT
1882    if(out==0)
1883    {
1884      for (i=1;i<=size(GSH);i++)
1885      {
1886        GSH[i][1]=subst(GSH[i][1],@t,1);
1887        for(j=1;j<=size(GSH[i][2]);j++)
1888        {
1889          GSH[i][2][j][2]=subst(GSH[i][2][j][2],@t,1);
1890        }
1891      }
1892    }
1893    else
1894    {
1895      for (i=1;i<=size(GSH);i++)
1896      {
1897        GSH[i][3]=subst(GSH[i][3],@t,1);
1898        GSH[i][7]=subst(GSH[i][7],@t,1);
1899      }
1900    }
1901    setring(RR);
1902    def GS=imap(RH,GSH);
1903    }
1904    // setglobalrings();
1905    if(out==0)
1906    {
1907      for (i=1;i<=size(GS);i++)
1908      {
1909        GS[i][1]=postredgb(mingb(GS[i][1]));
1910        for(j=1;j<=size(GS[i][2]);j++)
1911        {
1912          GS[i][2][j][2]=postredgb(mingb(GS[i][2][j][2]));
1913        }
1914      }
1915    }
1916    else
1917    {
1918      for (i=1;i<=size(GS);i++)
1919      {
1920        if(GS[i][2]==1)
1921        {
1922          GS[i][3]=postredgb(mingb(GS[i][3]));
1923          if (typeof(GS[i][7])=="ideal")
1924          { GS[i][7]=postredgb(mingb(GS[i][7]));}
1925        }
1926      }
1927    }
1928  }
1929  return(GS);
1930}
1931example
1932{
1933  "EXAMPLE:"; echo = 2;
1934  // Casas conjecture for degree 4:
1935  if(defined(R)){kill R;}
1936  ring R=(0,a0,a1,a2,a3,a4),(x1,x2,x3),dp;
1937  short=0;
1938  ideal F=x1^4+(4*a3)*x1^3+(6*a2)*x1^2+(4*a1)*x1+(a0),
1939          x1^3+(3*a3)*x1^2+(3*a2)*x1+(a1),
1940          x2^4+(4*a3)*x2^3+(6*a2)*x2^2+(4*a1)*x2+(a0),
1941          x2^2+(2*a3)*x2+(a2),
1942          x3^4+(4*a3)*x3^3+(6*a2)*x3^2+(4*a1)*x3+(a0),
1943          x3+(a3);
1944  cgsdr(F);
1945}
1946
1947// input:  internal routine called by cgsdr at the end to group the
1948//            lpp segments and improve the output
1949// output: grouped segments by lpp obtained in cgsdr
1950static proc grsegments(list T)
1951{
1952  int i;
1953  list L;
1954  list lpp;
1955  list lp;
1956  list ls;
1957  int n=size(T);
1958  lpp[1]=T[n][1];
1959  L[1]=list(lpp[1],list(list(T[n][2],T[n][3],T[n][4])));
1960  if (n>1)
1961  {
1962    for (i=1;i<=size(T)-1;i++)
1963    {
1964      lp=memberpos(T[n-i][1],lpp);
1965      if(lp[1]==1)
1966      {
1967        ls=L[lp[2]][2];
1968        ls[size(ls)+1]=list(T[n-i][2],T[n-i][3],T[n-i][4]);
1969        L[lp[2]][2]=ls;
1970      }
1971      else
1972      {
1973        lpp[size(lpp)+1]=T[n-i][1];
1974        L[size(L)+1]=list(T[n-i][1],list(list(T[n-i][2],T[n-i][3],T[n-i][4])));
1975      }
1976    }
1977  }
1978  return(L);
1979}
1980
1981// LCUnion
1982// Given a list of the P-representations of locally closed segments
1983// for which we know that the union is also locally closed
1984// it returns the P-representation of its union
1985// input:  L list of segments in P-representation
1986//      ((p_j^i,(p_j1^i,...,p_jk_j^i | j=1..t_i)) | i=1..s )
1987//      where i represents a segment
1988// output: P-representation of the union
1989//       ((P_j,(P_j1,...,P_jk_j | j=1..t)))
1990static proc LCUnion(list LL)
1991{
1992  def RR=basering;
1993  def Rx=ringlist(RR);
1994  def PP=ring(Rx[1]);
1995  setring(PP);
1996  def L=imap(RR,LL);
1997  int i; int j; int k; list H; list C; list T;
1998  list L0; list P0; list P; list Q0; list Q;
1999  for (i=1;i<=size(L);i++)
2000  {
2001    for (j=1;j<=size(L[i]);j++)
2002    {
2003      P0[size(P0)+1]=L[i][j][1];
2004      L0[size(L0)+1]=intvec(i,j);
2005    }
2006  }
2007  Q0=selectminideals(P0);
2008  for (i=1;i<=size(Q0);i++)
2009  {
2010    Q[i]=L0[Q0[i]];
2011    P[i]=L[Q[i][1]][Q[i][2]];
2012  }
2013  //"T_P="; P;
2014  // P is the list of the maximal components of the union
2015  //   with the corresponding initial holes.
2016  // Q is the list of intvec positions in L of the first element of the P's
2017  //   Its elements give (num of segment, num of max component (=min ideal))
2018  for (k=1;k<=size(Q);k++)
2019  {
2020    H=P[k][2]; // holes of P[k][1]
2021    for (i=1;i<=size(L);i++)
2022    {
2023      if (i!=Q[k][1])
2024      {
2025        for (j=1;j<=size(L[i]);j++)
2026        {
2027          C[size(C)+1]=L[i][j];
2028        }
2029      }
2030    }
2031    T[size(T)+1]=list(Q[k],P[k][1],addpart(H,C));
2032  }
2033  setring(RR);
2034  def TT=imap(PP,T);
2035  return(TT);
2036}
2037
2038// LCUnionN
2039// Given a list of the P-representations of locally closed segments
2040// for which we know that the union is also locally closed
2041// it returns the P-representation of its union
2042// input:  L list of segments in P-representation
2043//      ((p_j^i,(p_j1^i,...,p_jk_j^i | j=1..t_i)) | i=1..s )
2044//      where i represents a segment
2045// output: P-representation of the union
2046//       ((P_j,(P_j1,...,P_jk_j | j=1..t)))
2047static proc LCUnionN(list L)
2048{
2049  int i; int j; int k; list H; list C; list T;
2050  list L0; list P0; list P; list Q0; list Q;
2051  //"T_L="; L;
2052  for (i=1;i<=size(L);i++)
2053  {
2054    P0[size(P0)+1]=L[i][1];
2055    for (j=1;j<=size(L[i]);j++)
2056    {
2057      L0[size(L0)+1]=intvec(i,j);
2058    }
2059  }
2060  //"T_P0="; P0;
2061  Q0=selectminideals(P0);
2062  //"T_Q0="; Q0;
2063  for (i=1;i<=size(Q0);i++)
2064  {
2065    //Q[i]=L0[Q0[i]];
2066    P[i]=L[Q0[i][1]];// [Q[i][2]];
2067  }
2068  //"T_P="; P;
2069  // P is the list of the maximal components of the union
2070  //   with the corresponding initial holes.
2071  // Q is the list of intvec positions in L of the first element of the P's
2072  //   Its elements give (num of segment, num of max component (=min ideal))
2073  // list C;
2074  for (k=1;k<=size(Q0);k++)
2075  {
2076    kill C; list C;
2077    H=P[k][2]; // holes of P[k][1]
2078    for (i=1;i<=size(L);i++)
2079    {
2080      if (i!=Q0[k]) // (i!=Q0[k])
2081      {
2082        //for (j=1;j<=size(L[i]);j++)
2083        //{
2084          C[size(C)+1]=L[i];
2085        //}
2086      }
2087    }
2088    T[size(T)+1]=list(P[k][1],addpart(H,C)); // Q0[k],
2089  }
2090  return(T);
2091}
2092
2093
2094// Auxiliary routine
2095// called by LCUnion to modify the holes of a primepart of the union
2096// by the addition of the segments that do not correspond to that part
2097// Works on Q[a] ring.
2098// Input:
2099//   H=(p_i1,..,p_is) the holes of a component to be transformed by the addition of
2100//        the segments C that do not correspond to that component
2101//   C=((q_1,(q_11,..,q_1l_1),pos1),..,(q_k,(q_k1,..,q_kl_k),posk))
2102// posi=(i,j) position of the component
2103//        the list of segments to be added to the holes
2104static proc addpart(list H, list C)
2105{
2106  list Q; int i; int j; int k; int l; int t; int t1;
2107  Q=H; intvec notQ; list QQ; list addq;
2108  //          plus those of the components added to the holes.
2109  ideal q;
2110  i=1;
2111  while (i<=size(Q))
2112  {
2113    if (memberpos(i,notQ)[1]==0)
2114    {
2115      q=Q[i];
2116      t=1; j=1;
2117      while ((t) and (j<=size(C)))
2118      {
2119        if (equalideals(q,C[j][1]))
2120        {
2121          t=0;
2122          for (k=1;k<=size(C[j][2]);k++)
2123          {
2124            t1=1;
2125            l=1;
2126            while((t1) and (l<=size(Q)))
2127            {
2128              if ((l!=i) and (memberpos(l,notQ)[1]==0))
2129              {
2130                if (idcontains(C[j][2][k],Q[l]))
2131                {
2132                  t1=0;
2133                }
2134              }
2135              l++;
2136            }
2137            if (t1)
2138            {
2139              addq[size(addq)+1]=C[j][2][k];
2140            }
2141          }
2142          if((size(notQ)==1) and (notQ[1]==0)){notQ[1]=i;}
2143          else {notQ[size(notQ)+1]=i;}
2144        }
2145        j++;
2146      }
2147      if (size(addq)>0)
2148      {
2149        for (k=1;k<=size(addq);k++)
2150        {
2151          Q[size(Q)+1]=addq[k];
2152        }
2153        kill addq;
2154        list addq;
2155      }
2156    }
2157    i++;
2158  }
2159  for (i=1;i<=size(Q);i++)
2160  {
2161    if(memberpos(i,notQ)[1]==0)
2162    {
2163      QQ[size(QQ)+1]=Q[i];
2164    }
2165  }
2166  if (size(QQ)==0){QQ[1]=ideal(1);}
2167  return(addpartfine(QQ,C));
2168}
2169
2170// Auxiliary routine called by addpart to finish the modification of the holes of a primepart
2171// of the union by the addition of the segments that do not correspond to
2172// that part.
2173// Works on Q[a] ring.
2174static proc addpartfine(list H, list C0)
2175{
2176  //"T_H="; H;
2177  int i; int j; int k; int te; intvec notQ; int l; list sel;
2178  intvec jtesC;
2179  if ((size(H)==1) and (equalideals(H[1],ideal(1)))){return(H);}
2180  if (size(C0)==0){return(H);}
2181  list newQ; list nQ; list Q; list nQ1; list Q0;
2182  def Q1=H;
2183  //Q1=sortlistideals(Q1,idbefid);
2184  def C=C0;
2185  while(equallistideals(Q0,Q1)==0)
2186  {
2187    Q0=Q1;
2188    i=0;
2189    Q=Q1;
2190    kill notQ; intvec notQ;
2191    while(i<size(Q))
2192    {
2193      i++;
2194      for(j=1;j<=size(C);j++)
2195      {
2196        te=idcontains(Q[i],C[j][1]);
2197        if(te)
2198        {
2199          for(k=1;k<=size(C[j][2]);k++)
2200          {
2201            if(idcontains(Q[i],C[j][2][k]))
2202            {
2203              te=0; break;
2204            }
2205          }
2206          if (te)
2207          {
2208            if ((size(notQ)==1) and (notQ[1]==0)){notQ[1]=i;}
2209            else{notQ[size(notQ)+1]=i;}
2210            kill newQ; list newQ;
2211            for(k=1;k<=size(C[j][2]);k++)
2212            {
2213              nQ=minGTZ(Q[i]+C[j][2][k]);
2214              for(l=1;l<=size(nQ);l++)
2215              {
2216                option(redSB);
2217                nQ[l]=std(nQ[l]);
2218                newQ[size(newQ)+1]=nQ[l];
2219              }
2220            }
2221            sel=selectminideals(newQ);
2222            kill nQ1; list nQ1;
2223            for(l=1;l<=size(sel);l++)
2224            {
2225              nQ1[l]=newQ[sel[l]];
2226            }
2227            newQ=nQ1;
2228            for(l=1;l<=size(newQ);l++)
2229            {
2230              Q[size(Q)+1]=newQ[l];
2231            }
2232            break;
2233          }
2234        }
2235      }
2236    }
2237    kill Q1; list Q1;
2238    for(i=1;i<=size(Q);i++)
2239    {
2240      if(memberpos(i,notQ)[1]==0)
2241      {
2242        Q1[size(Q1)+1]=Q[i];
2243      }
2244    }
2245    sel=selectminideals(Q1);
2246    kill nQ1; list nQ1;
2247    for(l=1;l<=size(sel);l++)
2248    {
2249      nQ1[l]=Q1[sel[l]];
2250    }
2251    Q1=nQ1;
2252  }
2253  if(size(Q1)==0){Q1=ideal(1),ideal(1);}
2254  return(Q1);
2255}
2256
2257// Auxiliary rutine for gcover
2258// Deciding if combine is needed
2259// input: list LCU=( (basis1, p_1, (p11,..p1s1)), .. (basisr, p_r, (pr1,..prsr))
2260// output: (tes); if tes==1 then combine is needed, else not.
2261static proc needcombine(list LCU,ideal N)
2262{
2263  //"Deciding if combine is needed";;
2264  ideal BB;
2265  int tes=0; int m=1; int j; int k; poly sp;
2266  while((tes==0) and (m<=size(LCU[1][1])))
2267  {
2268    j=1;
2269    while((tes==0) and (j<=size(LCU)))
2270    {
2271      k=1;
2272      while((tes==0) and (k<=size(LCU)))
2273      {
2274        if(j!=k)
2275        {
2276          sp=pnormalf(pspol(LCU[j][1][m],LCU[k][1][m]),LCU[k][2],N);
2277          if(sp!=0){tes=1;}
2278        }
2279        k++;
2280      }
2281      j++;
2282    }
2283    if(tes){break;}
2284    m++;
2285  }
2286  return(tes);
2287}
2288
2289// Auxiliary routine
2290// precombine
2291// input:  L: list of ideals (works in @P)
2292// output: F0: ideal of polys. F0[i] is a poly in the intersection of
2293//             all ideals in L except in the ith one, where it is not.
2294//             L=(p1,..,ps);  F0=(f1,..,fs);
2295//             F0[i] \in intersect_{j#i} p_i
2296static proc precombine(list L)
2297{
2298  int i; int j; int tes;
2299  def RR=basering;
2300  def Rx=ringlist(RR);
2301  def P=ring(Rx[1]);
2302  setring(P);
2303  list L0; list L1; list L2; list L3; ideal F;
2304  L0=imap(RR,L);
2305  L1[1]=L0[1]; L2[1]=L0[size(L0)];
2306  for (i=2;i<=size(L0)-1;i++)
2307  {
2308    L1[i]=intersect(L1[i-1],L0[i]);
2309    L2[i]=intersect(L2[i-1],L0[size(L0)-i+1]);
2310  }
2311  L3[1]=L2[size(L2)];
2312  for (i=2;i<=size(L0)-1;i++)
2313  {
2314    L3[i]=intersect(L1[i-1],L2[size(L0)-i]);
2315  }
2316  L3[size(L0)]=L1[size(L1)];
2317  for (i=1;i<=size(L3);i++)
2318  {
2319    option(redSB); L3[i]=std(L3[i]);
2320  }
2321  for (i=1;i<=size(L3);i++)
2322  {
2323    tes=1; j=0;
2324    while((tes) and (j<size(L3[i])))
2325    {
2326      j++;
2327      option(redSB);
2328      L0[i]=std(L0[i]);
2329      if(reduce(L3[i][j],L0[i],5)!=0){tes=0; F[i]=L3[i][j];}
2330    }
2331    if (tes){"ERROR a polynomial in all p_j except p_i was not found";}
2332  }
2333  setring(RR);
2334  def F0=imap(P,F);
2335  return(F0);
2336}
2337
2338// Auxiliary routine
2339// combine
2340// input: a list of pairs ((p1,P1),..,(pr,Pr)) where
2341//    ideal pi is a prime component
2342//    poly Pi is the polynomial in Q[a][x] on V(pi) \ V(Mi)
2343//    (p1,..,pr) are the prime decomposition of the lpp-segment
2344//    list crep =(ideal ida,ideal idb): the Crep of the segment.
2345//    list Pci of the intersecctions of all pj except the ith one
2346// output:
2347//    poly P on an open and dense set of V(p_1 int ... p_r)
2348static proc combine(list L, ideal F)
2349{
2350  // ATTENTION REVISE AND USE Pci and F
2351  int i; poly f;
2352  f=0;
2353  for(i=1;i<=size(L);i++)
2354  {
2355    f=f+F[i]*L[i][2];
2356  }
2357//   f=elimconstfac(f);
2358  f=primepartZ(f);
2359  return(f);
2360}
2361
2362// Central routine for grobcov: ideal F is assumed to be homogeneous
2363// gcover
2364// input: ideal F: a generating set of a homogeneous ideal in Q[a][x]
2365//    list #: optional
2366// output: the list
2367//   S=((lpp, generic basis, Prep, Crep),..,(lpp, generic basis, Prep, Crep))
2368//      where a Prep is ( (p1,(p11,..,p1k_1)),..,(pj,(pj1,..,p1k_j)) )
2369//            a Crep is ( ida, idb )
2370static proc gcover(ideal F,list #)
2371{
2372  int i; int j; int k; ideal lpp; list GPi2; list pairspP; ideal B; int ti;
2373  int i1; int tes; int j1; int selind; int i2; //int m;
2374  list prep; list crep; list LCU; poly p; poly lcp; ideal FF;
2375  list lpi;
2376  def RR=basering;
2377  string lpph;
2378  list L=#;
2379  int canop=1;
2380  int extop=1;
2381  int repop=0;
2382  ideal E=ideal(0);;
2383  ideal N=ideal(1);;
2384  int comment;
2385  for(i=1;i<=size(L) div 2;i++)
2386  {
2387    if(L[2*i-1]=="can"){canop=L[2*i];}
2388    else
2389    {
2390      if(L[2*i-1]=="ext"){extop=L[2*i];}
2391      else
2392      {
2393        if(L[2*i-1]=="rep"){repop=L[2*i];}
2394        else
2395        {
2396          if(L[2*i-1]=="null"){E=L[2*i];}
2397          else
2398          {
2399            if(L[2*i-1]=="nonnull"){N=L[2*i];}
2400            else
2401            {
2402              if (L[2*i-1]=="comment"){comment=L[2*i];}
2403            }
2404          }
2405        }
2406      }
2407    }
2408  }
2409  list GS; list GP;
2410  GS=cgsdr(F,L); // "null",NW[1],"nonnull",NW[2],"cgs",CGS,"comment",comment);
2411  int start=timer;
2412  GP=GS;
2413  ideal lppr;
2414  list LL;
2415  list S;
2416  poly sp;
2417  for (i=1;i<=size(GP);i++)
2418  {
2419    kill LL;
2420    list LL;
2421    lpp=GP[i][1];
2422    GPi2=GP[i][2];
2423    lpph=GP[i][3];
2424    kill pairspP; list pairspP;
2425    for(j=1;j<=size(GPi2);j++)
2426    {
2427      pairspP[size(pairspP)+1]=GPi2[j][3];
2428    }
2429    LCU=LCUnion(pairspP);
2430    kill prep; list prep;
2431    kill crep; list crep;
2432    for(k=1;k<=size(LCU);k++)
2433    {
2434      prep[k]=list(LCU[k][2],LCU[k][3]);
2435      B=GPi2[LCU[k][1][1]][2]; // ATENTION last 1 has been changed to [2]
2436      LCU[k][1]=B;
2437    }
2438    //"Deciding if combine is needed";
2439    crep=PtoCrep(prep);
2440    if(size(LCU)>1){tes=1;}
2441    else
2442    {
2443      tes=0;
2444      for(k=1;k<=size(B);k++){B[k]=pnormalf(B[k],crep[1],crep[2]);}
2445    }
2446    if(tes)
2447    {
2448      // combine is needed
2449      kill B; ideal B;
2450      for (j=1;j<=size(LCU);j++)
2451      {
2452        LL[j]=LCU[j][2];
2453      }
2454      FF=precombine(LL);
2455      for (k=1;k<=size(lpp);k++)
2456      {
2457        kill L; list L;
2458        for (j=1;j<=size(LCU);j++)
2459        {
2460          L[j]=list(LCU[j][2],LCU[j][1][k]);
2461        }
2462        B[k]=combine(L,FF);
2463      }
2464    }
2465    for(j=1;j<=size(B);j++)
2466    {
2467      B[j]=pnormalf(B[j],crep[1],crep[2]);
2468    }
2469    S[i]=list(lpp,B,prep,crep,lpph);
2470    if(comment>=1)
2471    {
2472      lpi[size(lpi)+1]=string("[",i,"]");
2473      lpi[size(lpi)+1]=S[i][1];
2474    }
2475  }
2476  if(comment>=1)
2477  {
2478    string("Time in LCUnion + combine = ",timer-start);
2479    if(comment>=2){string("lpp=",lpi)};
2480  }
2481  return(S);
2482}
2483
2484// grobcov
2485// input:
2486//    ideal F: a parametric ideal in Q[a][x], (a=parameters, x=variables).
2487//    list #: (options) list("null",N,"nonnull",W,"can",0-1,ext",0-1, "rep",0-1-2)
2488//            where
2489//            N is the null conditions ideal (if desired)
2490//            W is the ideal of non-null conditions (if desired)
2491//            The value of \"can\" is 1 by default and can be set to 0 if we do not
2492//            need to obtain the canonical GC, but only a GC.
2493//            The value of \"ext\" is 0 by default and so the generic representation
2494//             of the bases is given. It can be set to 1, and then the full
2495//             representation of the bases is given.
2496//            The value of \"rep\" is 0 by default, and then the segments
2497//            are given in canonical P-representation. It can be set to 1
2498//            and then they are given in canonical C-representation.
2499//            If it is set to 2, then both representations are given.
2500// output:
2501//    list S: ((lpp,basis,(idp_1,(idp_11,..,idp_1s_1))), ..
2502//             (lpp,basis,(idp_r,(idp_r1,..,idp_rs_r))) ) where
2503//            each element of S corresponds to a lpp-segment
2504//            given by the lpp, the basis, and the P-representation of the segment
2505proc grobcov(ideal F,list #)
2506"USAGE: grobcov(ideal F[,options]);
2507       F: ideal in Q[a][x] (a=parameters, x=variables) to be
2508       discussed.This is the fundamental routine of the
2509       library. It computes the Groebner Cover of a parametric
2510       ideal F in Q[a][x]. See
2511       A. Montes , M. Wibmer, \"Groebner Bases for Polynomial
2512       Systems with parameters\".
2513       JSC 45 (2010) 1391-1425.)
2514       or the not yet published book
2515       A. Montes. \" The Groebner Cover\" (Discussing
2516       Parametric Polynomial Systems).
2517       The Groebner Cover of a parametric ideal F consist
2518       of a set of pairs(S_i,B_i), where the S_i are disjoint
2519       locally closed segments of the parameter space,
2520       and the B_i are the reducedGroebner bases of the
2521       ideal on every point of S_i. The ideal F must be
2522       defined on a parametric ring Q[a][x] (a=parameters,
2523       x=variables).
2524RETURN: The list  [[lpp_1,basis_1,segment_1],  ...,
2525       [lpp_s,basis_s,segment_s]]
2526       optionally  [[ lpp_1,basis_1,segment_1,lpph_1],  ...,
2527       [lpp_s,basis_s,segment_s,lpph_s]]
2528       The lpp are constant over a segment and
2529       correspond to the set of lpp of the reduced
2530       Groebner basis for each point of the segment.
2531       With option (\"showhom\",1) the lpph will be
2532       shown: The lpph corresponds to the lpp of the
2533       homogenized ideal and is different for each
2534       segment. It is given as a string, and shown
2535       only for information. With the default option
2536       \"can\",1, the segments have different lpph.
2537       Basis: to each element of lpp corresponds
2538       an I-regular function given in full
2539       representation (by option (\"ext\",1)) or
2540       in generic representation (default option (\"ext\",0)).
2541       The I-regular function is the corresponding
2542       element of the reduced Groebner basis for
2543       each point of the segment with the given lpp.
2544       For each point in the segment, the polynomial
2545       or the set of polynomials  representing it,
2546       if they do not specialize to 0, then after
2547       normalization, specializes to the corresponding
2548       element of the reduced Groebner basis.
2549       In the full representation at least one of the
2550       polynomials representing the I-regular function
2551       specializes to non-zero.
2552       With the default option (\"rep\",0) the
2553       representation of the segment is the
2554       P-representation.
2555       With option (\"rep\",1) the representation
2556       of the segment is the C-representation.
2557       With option (\"rep\",2) both representations
2558       of the segment are given.
2559       The P-representation of a segment is of the form
2560       [[p_1,[p_11,..,p_1k1]],..,[p_r,[p_r1,..,p_rkr]]]
2561       representing the segment
2562       Union_i ( V(p_i) \ ( Union_j V(p_ij) ) ),
2563       where the p's are prime ideals.
2564       The C-representation of a segment is of the form
2565       (E,N) representing V(E) \ V(N), and the ideals E
2566       and N are radical and N contains E.
2567OPTIONS: An option is a pair of arguments: string,
2568       integer. To modify the default options, pairs
2569       of arguments -option name, value- of valid options
2570       must be added to the call.
2571       \"null\",ideal E: The default is (\"null\",ideal(0)).
2572       \"nonnull\",ideal N: The default is
2573       (\"nonnull\",ideal(1)).
2574       When options \"null\" and/or \"nonnull\" are given,
2575       then the parameter space is restricted to V(E) \ V(N).
2576       \"can\",0-1: The default is (\"can\",1).
2577       With the default option the homogenized
2578       ideal is computed before obtaining the Groebner
2579       Cover, so that the result is the canonical Groebner
2580       Cover. Setting (\"can\",0) only homogenizes the
2581       basis so the result is not exactly canonical,
2582       but the computation is shorter.
2583       \"ext\",0-1: The default is (\"ext\",0).
2584       With the default (\"ext\",0), only the generic
2585       representation of the bases is computed
2586       (single polynomials, but not specializing
2587       to non-zero for every point of the segment.
2588       With option (\"ext\",1) the full representation
2589       of the bases is computed (possible sheaves)
2590       and sometimes a simpler result is obtained,
2591       but the computation is more time consuming.
2592       \"rep\",0-1-2: The default is (\"rep\",0)
2593       and then the segments are given in canonical
2594       P-representation.
2595       Option (\"rep\",1) represents the segments
2596       in canonical C-representation, and
2597       option (\"rep\",2) gives both representations.
2598       \"comment\",0-3: The default is (\"comment\",0).
2599       Setting \"comment\" higher will provide
2600       information about the development of the
2601       computation.
2602       \"showhom\",0-1: The default is (\"showhom\",0).
2603       Setting \"showhom\",1 will output the set
2604       of lpp of the homogenized ideal of each segment
2605       as last element. One can give none or whatever
2606       of these options.
2607NOTE:    The basering R, must be of the form Q[a][x],
2608       (a=parameters, x=variables), and
2609       should be defined previously. The ideal
2610       must be defined on R.
2611KEYWORDS: Groebner cover; parametric ideal; canonical; discussion of parametric ideal
2612EXAMPLE:  grobcov; shows an example"
2613{
2614  list S; int i; int ish=1; list GBR; list BR; int j; int k;
2615  ideal idp; ideal idq; int s; ideal ext; list SS;
2616  ideal E; ideal N; int canop;  int extop; int repop;
2617  int comment=0; int m;
2618  def RR=basering;
2619  def Rx=ringlist(RR);
2620  def P=ring(Rx[1]);
2621  Rx[1]=0;
2622  def D=ring(Rx);
2623  def RP=D+P;
2624  list L0=#;
2625  list Se;
2626  int out=0;
2627  int showhom=0;
2628  int hom;
2629  L0[size(L0)+1]="res"; L0[size(L0)+1]=ideal(1);
2630  // default options
2631  int start=timer;
2632  E=ideal(0);
2633  N=ideal(1);
2634  canop=1; // canop=0 for homogenizing the basis but not the ideal (not canonical)
2635           // canop=1 for working with the homogenized ideal
2636  repop=0; // repop=0 for representing the segments in Prep
2637           // repop=1 for representing the segments in Crep
2638           // repop=2 for representing the segments in Prep and Crep
2639  extop=0; // extop=0 if only generic representation of the bases are to be computed
2640           // extop=1 if the full representation of the bases are to be computed
2641  for(i=1;i<=size(L0) div 2;i++)
2642  {
2643    if(L0[2*i-1]=="can"){canop=L0[2*i];}
2644    else
2645    {
2646      if(L0[2*i-1]=="ext"){extop=L0[2*i];}
2647      else
2648      {
2649        if(L0[2*i-1]=="rep"){repop=L0[2*i];}
2650        else
2651        {
2652          if(L0[2*i-1]=="null"){E=L0[2*i];}
2653          else
2654          {
2655            if(L0[2*i-1]=="nonnull"){N=L0[2*i];}
2656            else
2657            {
2658              if (L0[2*i-1]=="comment"){comment=L0[2*i];}
2659              else
2660              {
2661                if (L0[2*i-1]=="showhom"){showhom=L0[2*i];}
2662              }
2663            }
2664          }
2665        }
2666      }
2667    }
2668  }
2669  if(not((canop==0) or (canop==1)))
2670  {
2671    string("Option can = ",canop," is not supported. It is changed to can = 1");
2672    canop=1;
2673  }
2674  for(i=1;i<=size(L0) div 2;i++)
2675  {
2676    if(L0[2*i-1]=="can"){L0[2*i]=canop;}
2677  }
2678  if ((printlevel) and (comment==0)){comment=printlevel;}
2679  list LL;
2680  LL[1]="can";     LL[2]=canop;
2681  LL[3]="comment"; LL[4]=comment;
2682  LL[5]="out";     LL[6]=0;
2683  LL[7]="null";    LL[8]=E;
2684  LL[9]="nonnull"; LL[10]=N;
2685  LL[11]="ext";    LL[12]=extop;
2686  LL[13]="rep";    LL[14]=repop;
2687  LL[15]="showhom";    LL[16]=showhom;
2688  if (comment>=1)
2689  {
2690    string("Begin grobcov with options: ",LL);
2691  }
2692  kill S;
2693  def S=gcover(F,LL);
2694  // NOW extendGC
2695  if(extop)
2696  {
2697    S=extendGC(S,LL);
2698  }
2699  // NOW repop and showhom
2700  list Si; list nS;
2701  for(i=1;i<=size(S);i++)
2702  {
2703    if(repop==0){Si=list(S[i][1],S[i][2],S[i][3]);}
2704    if(repop==1){Si=list(S[i][1],S[i][2],S[i][4]);}
2705    if(repop==2){Si=list(S[i][1],S[i][2],S[i][3],S[i][4]);}
2706    if(showhom==1){Si[size(Si)+1]=S[i][5];}
2707    nS[size(nS)+1]=Si;
2708  }
2709  S=nS;
2710  if (comment>=1)
2711  {
2712    string("Time in grobcov = ", timer-start);
2713    string("Number of segments of grobcov = ", size(S));
2714  }
2715  return(S);
2716}
2717example
2718{
2719"EXAMPLE:"; echo = 2;
2720// Casas conjecture for degree 4:
2721  if(defined(R)){kill R;}
2722  ring R=(0,a0,a1,a2,a3,a4),(x1,x2,x3),dp;
2723  short=0;
2724  ideal F=x1^4+(4*a3)*x1^3+(6*a2)*x1^2+(4*a1)*x1+(a0),
2725            x1^3+(3*a3)*x1^2+(3*a2)*x1+(a1),
2726            x2^4+(4*a3)*x2^3+(6*a2)*x2^2+(4*a1)*x2+(a0),
2727            x2^2+(2*a3)*x2+(a2),
2728            x3^4+(4*a3)*x3^3+(6*a2)*x3^2+(4*a1)*x3+(a0),
2729            x3+(a3);
2730  grobcov(F);
2731// EXAMPLE:
2732  // M. Rychlik robot;
2733  // Complexity and Applications of Parametric Algorithms of
2734  //    Computational Algebraic Geometry.;
2735  // In: Dynamics of Algorithms, R. de la Llave, L. Petzold and J. Lorenz eds.;
2736  // IMA Volumes in Mathematics and its Applications,
2737  //    Springer-Verlag 118: 1-29 (2000).;
2738  //    (18. Mathematical robotics: Problem 4, two-arm robot)."
2739  if (defined(R)){kill R;}
2740  ring R=(0,a,b,l2,l3),(c3,s3,c1,s1), dp;
2741  short=0;
2742  ideal S12=a-l3*c3-l2*c1,b-l3*s3-l2*s1,c1^2+s1^2-1,c3^2+s3^2-1;
2743  S12;
2744  grobcov(S12);
2745}
2746
2747// Auxiliary routine called by extendGC
2748// extendpoly
2749// input:
2750//   poly f: a generic polynomial in the basis
2751//   ideal idp: such that ideal(S)=idp
2752//   ideal idq: such that S=V(idp) \ V(idq)
2753////   NW the list of ((N1,W1),..,(Ns,Ws)) of red-rep of the grouped
2754////      segments in the lpp-segment  NO MORE USED
2755// output:
2756proc extendpoly(poly f, ideal idp, ideal idq)
2757"USAGE: extendGC(poly f,ideal p,ideal q);
2758       f is a polynomial in Q[a][x] in generic representation
2759       of an I-regular function F defined on the locally
2760       closed segment S=V(p) \ V(q).
2761       p,q are ideals in Q[a], representing the Crep of
2762       segment S.
2763RETURN: the extended representation of F in S.
2764       It can consist of a single polynomial or a set of
2765       polynomials when needed.
2766NOTE: The basering R, must be of the form Q[a][x],
2767       (a=parameters,x=variables), and should be
2768       defined previously. The ideals must be defined on R.
2769KEYWORDS: Groebner cover; parametric ideal; locally closed set;
2770       parametric ideal; generic representation; full representation;
2771       I-regular function
2772EXAMPLE:  extendpoly; shows an example"
2773{
2774  int te=0;
2775  def RR=basering;
2776  def Rx=ringlist(RR);
2777  def P=ring(Rx[1]);
2778  Rx[1]=0;
2779  def D=ring(Rx);
2780  def RP=D+P;
2781  matrix CC; poly Q; list NewMonoms;
2782  int i;  int j;  poly fout; ideal idout;
2783  list L=monoms(f);
2784  int nummonoms=size(L)-1;
2785  Q=L[1][1];
2786  if (nummonoms==0){return(f);}
2787  for (i=2;i<=size(L);i++)
2788  {
2789    CC=matrix(extendcoef(L[i][1],Q,idp,idq));
2790    NewMonoms[i-1]=list(CC,L[i][2]);
2791  }
2792  if (nummonoms==1)
2793  {
2794    for(j=1;j<=ncols(NewMonoms[1][1]);j++)
2795    {
2796      fout=NewMonoms[1][1][2,j]*L[1][2]+NewMonoms[1][1][1,j]*NewMonoms[1][2];
2797      //fout=pnormalf(fout,idp,W);
2798      if(ncols(NewMonoms[1][1])>1){idout[j]=fout;}
2799    }
2800    if(ncols(NewMonoms[1][1])==1)
2801    {
2802      return(fout);
2803    }
2804    else
2805    {
2806      return(idout);
2807    }
2808  }
2809  else
2810  {
2811    list cfi;
2812    list coefs;
2813    for (i=1;i<=nummonoms;i++)
2814    {
2815      kill cfi; list cfi;
2816      for(j=1;j<=ncols(NewMonoms[i][1]);j++)
2817      {
2818        cfi[size(cfi)+1]=NewMonoms[i][1][2,j];
2819      }
2820      coefs[i]=cfi;
2821    }
2822    def indexpolys=findindexpolys(coefs);
2823    for(i=1;i<=size(indexpolys);i++)
2824    {
2825      fout=L[1][2];
2826      for(j=1;j<=nummonoms;j++)
2827      {
2828        fout=fout+(NewMonoms[j][1][1,indexpolys[i][j]])/(NewMonoms[j][1][2,indexpolys[i][j]])*NewMonoms[j][2];
2829      }
2830      fout=cleardenom(fout);
2831      if(size(indexpolys)>1){idout[i]=fout;}
2832    }
2833    if (size(indexpolys)==1)
2834    {
2835      return(fout);
2836    }
2837    else
2838    {
2839      return(idout);
2840    }
2841  }
2842}
2843example
2844{
2845  echo = 2; "EXAMPLE:";
2846  if(defined(R)){kill R;}
2847  ring R=(0,a1,a2),(x),lp;
2848  short=0;
2849  poly f=(a1^2-4*a1+a2^2-a2)*x+(a1^4-16*a1+a2^3-4*a2);
2850  ideal p=a1*a2;
2851  ideal q=a2^2-a2,a1*a2,a1^2-4*a1;
2852  extendpoly(f,p,q);" ";
2853// EXAMPLE;
2854  if (defined(R)){kill R;}
2855  ring R=(0,a0,b0,c0,a1,b1,c1,a2,b2,c2),(x), dp;
2856  short=0;
2857  poly f=(b1*a2*c2-c1*a2*b2)*x+(-a1*c2^2+b1*b2*c2+c1*a2*c2-c1*b2^2);
2858  ideal p=
2859  (-a0*b1*c2+a0*c1*b2+b0*a1*c2-b0*c1*a2-c0*a1*b2+c0*b1*a2),
2860  (a1^2*c2^2-a1*b1*b2*c2-2*a1*c1*a2*c2+a1*c1*b2^2+b1^2*a2*c2-b1*c1*a2*b2+c1^2*a2^2),
2861  (a0*a1*c2^2-a0*b1*b2*c2-a0*c1*a2*c2+a0*c1*b2^2+b0*b1*a2*c2-b0*c1*a2*b2-c0*a1*a2*c2+c0*c1*a2^2),
2862  (a0^2*c2^2-a0*b0*b2*c2-2*a0*c0*a2*c2+a0*c0*b2^2+b0^2*a2*c2-b0*c0*a2*b2+c0^2*a2^2),
2863  (a0*a1*c1*c2-a0*b1^2*c2+a0*b1*c1*b2-a0*c1^2*a2+b0*a1*b1*c2-b0*a1*c1*b2-c0*a1^2*c2+c0*a1*c1*a2),
2864  (a0^2*c1*c2-a0*b0*b1*c2-a0*c0*a1*c2+a0*c0*b1*b2-a0*c0*c1*a2+b0^2*a1*c2-b0*c0*a1*b2+c0^2*a1*a2),
2865  (a0^2*c1^2-a0*b0*b1*c1-2*a0*c0*a1*c1+a0*c0*b1^2+b0^2*a1*c1-b0*c0*a1*b1+c0^2*a1^2),
2866  (2*a0*a1*b1*c1*c2-a0*a1*c1^2*b2-a0*b1^3*c2+a0*b1^2*c1*b2-a0*b1*c1^2*a2
2867  -b0*a1^2*c1*c2+b0*a1*b1^2*c2-b0*a1*b1*c1*b2+b0*a1*c1^2*a2-c0*a1^2*b1*c2+c0*a1^2*c1*b2);
2868  ideal q=
2869  (-a1*c2+c1*a2),
2870  (-a1*b2+b1*a2),
2871  (-a0*c2+c0*a2),
2872  (-a0*b2+b0*a2),
2873  (-a0*c1+c0*a1),
2874  (-a0*b1+b0*a1),
2875  (-a1*b1*c2+a1*c1*b2),
2876  (-a0*b1*c2+a0*c1*b2),
2877  (-a0*b0*c2+a0*c0*b2),
2878  (-a0*b0*c1+a0*c0*b1);
2879  extendpoly(f,p,q);
2880}
2881
2882// if L is a list(ideal,ideal)  return 1 else returns 0;
2883static proc typeofCrep(L)
2884{
2885  if(typeof(L)!="list"){return(0);}
2886  if(size(L)!=2){return(0);}
2887  if((typeof(L[1])!="ideal") or (typeof(L[2])!="ideal")){return(0);}
2888  return(1);
2889}
2890
2891// Input. GC the grobcov of an ideal in generic representation of the
2892//        bases computed with option option ("rep",2).
2893// Output The grobcov in full representation.
2894// Option ("comment",1) shows the time.
2895// Can be called from the top
2896proc extendGC(list GC)
2897"USAGE: extendGC(list GC);
2898       list GC must the grobcov of a parametric ideal computed
2899       with option \"rep\",2. It determines the full
2900       representation.
2901       The default option of grobcov provides the bases in
2902       generic representation (the I-regular functions forming
2903       the bases are then given by a single polynomial.
2904       They can specialize to zero for some points of the
2905       segments, but in general, it is sufficient for many
2906       purposes. Nevertheless the I-regular functions allow a
2907       full representation given by a set of polynomials
2908       specializing to the value of the function (after
2909       normalization) or to zero, but at least one of the
2910       polynomials specializes to non-zero. The full
2911       representation can be obtained by computing
2912       the grobcov with option \"ext\",1. (The default
2913       option there is \"ext\",0).
2914       With option \"ext\",1 the computation can be
2915       much more time consuming, but the result can
2916       be simpler.
2917       Alternatively, one can compute the full representation
2918       of the bases after computing grobcov with the default
2919       option for \"ext\" and the option \"rep\",2,
2920       that outputs both the Prep and the Crep of the
2921       segments, and then call \"extendGC\" to its output.
2922RETURN: When calling extendGC(grobcov(S,\"rep\",2)) the
2923       result is of the form
2924       [[[lpp_1,basis_1,segment_1,lpph_1], ... ,
2925           [lpp_s,basis_s,segment_s,lpph_s]] ],
2926       where each function of the basis can be given
2927       by an ideal of representants.
2928NOTE: The basering R, must be of the form Q[a][x],
2929       (a=parameters, x=variables),
2930       and should be defined previously. The ideal
2931       must be defined on R.
2932KEYWORDS: Groebner cover; parametric ideal; canonical,
2933       discussion of parametric ideal; full representation
2934EXAMPLE:  extendGC; shows an example"
2935{
2936  int te;
2937  def RR=basering;
2938  def Rx=ringlist(RR);
2939  def P=ring(Rx[1]);
2940  Rx[1]=0;
2941  def D=ring(Rx);
2942  def RP=D+P;
2943  list S=GC;
2944  ideal idp;
2945  ideal idq;
2946  int i; int j; int m; int s; int k;
2947  m=0; i=1;
2948  while((i<=size(S)) and (m==0))
2949  {
2950    if(typeof(S[i][2])=="list"){m=1;}
2951    i++;
2952  }
2953  if(m==1)
2954  {
2955    "Warning! grobcov has already extended bases";
2956    return(S);
2957  }
2958  if(typeofCrep(S[1][3])){k=3;}
2959  else{if(typeofCrep(S[1][4])){k=4;};}
2960  if(k==0)
2961  {
2962    "Warning! extendGC make sense only when grobcov has been called with option 'rep',1 or 'rep',2";
2963    // if(te==0){kill @R; kill @RP; kill @P;}
2964    return(S);
2965  }
2966  poly leadc;
2967  poly ext;
2968  list SS;
2969  // Now extendGC
2970  for (i=1;i<=size(S);i++)
2971  {
2972    m=size(S[i][2]);
2973     for (j=1;j<=m;j++)
2974    {
2975      idp=S[i][k][1];
2976      idq=S[i][k][2];
2977      if (size(idp)>0)
2978      {
2979        leadc=leadcoef(S[i][2][j]);
2980        kill ext;
2981        def ext=extendpoly(S[i][2][j],idp,idq);
2982        if (typeof(ext)=="poly")
2983        {
2984          S[i][2][j]=pnormalf(ext,idp,idq);
2985        }
2986        else
2987        {
2988          if(size(ext)==1)
2989          {
2990            S[i][2][j]=ext[1];
2991          }
2992          else
2993          {
2994            kill SS; list SS;
2995            for(s=1;s<=size(ext);s++)
2996            {
2997              ext[s]=pnormalf(ext[s],idp,idq);
2998            }
2999            for(s=1;s<=size(S[i][2]);s++)
3000            {
3001              if(s!=j){SS[s]=S[i][2][s];}
3002              else{SS[s]=ext;}
3003            }
3004            S[i][2]=SS;
3005          }
3006        }
3007      }
3008    }
3009  }
3010  return(S);
3011}
3012example
3013{
3014  "EXAMPLE:"; echo = 2;
3015  if(defined(R)){kill R;}
3016  ring R=(0,a0,b0,c0,a1,b1,c1),(x), dp;
3017  short=0;
3018  ideal S=a0*x^2+b0*x+c0,
3019          a1*x^2+b1*x+c1;
3020  def GCS=grobcov(S,"rep",2);
3021  GCS;
3022  def FGC=extendGC(GCS,"rep",1);
3023  // Full representation=
3024  FGC;
3025}
3026
3027// Auxiliary routine
3028// nonzerodivisor
3029// input:
3030//    poly g in Q[a],
3031//    list P=(p_1,..p_r) representing a minimal prime decomposition
3032// output
3033//    poly f such that f notin p_i for all i and
3034//           g-f in p_i for all i such that g notin p_i
3035static proc nonzerodivisor(poly gr, list Pr)
3036{
3037  def RR=basering;
3038  def Rx=ringlist(RR);
3039  def P=ring(Rx[1]);
3040  setring(P);
3041  def g=imap(RR,gr);
3042  def P=imap(RR,Pr);
3043  int i; int k;  list J; ideal F;
3044  def f=g;
3045  ideal Pi;
3046  for (i=1;i<=size(P);i++)
3047  {
3048    option(redSB);
3049    Pi=std(P[i]);
3050    //attrib(Pi,"isSB",1);
3051    if (reduce(g,Pi,5)==0){J[size(J)+1]=i;}
3052  }
3053  for (i=1;i<=size(J);i++)
3054  {
3055    F=ideal(1);
3056    for (k=1;k<=size(P);k++)
3057    {
3058      if (k!=J[i])
3059      {
3060        F=idint(F,P[k]);
3061      }
3062    }
3063    f=f+F[1];
3064  }
3065  setring(RR);
3066  def fr=imap(P,f);
3067  return(fr);
3068}
3069
3070//Auxiliary routine
3071// nullin
3072// input:
3073//   poly f:  a polynomial in Q[a]
3074//   ideal P: an ideal in Q[a]
3075//   called from ring @R
3076// output:
3077//   t:  with value 1 if f reduces modulo P, 0 if not.
3078static proc nullin(poly f,ideal P)
3079{
3080  int t;
3081  def RR=basering;
3082  def Rx=ringlist(RR);
3083  def P=ring(Rx[1]);
3084  setring(P);
3085  def f0=imap(RR,f);
3086  def P0=imap(RR,P);
3087  attrib(P0,"isSB",1);
3088  if (reduce(f0,P0,5)==0){t=1;}
3089  else{t=0;}
3090  setring(RR);
3091  return(t);
3092}
3093
3094// Auxiliary routine
3095// monoms
3096// Input: A polynomial f
3097// Output: The list of leading terms
3098static proc monoms(poly f)
3099{
3100  list L;
3101  poly lm; poly lc; poly lp; poly Q; poly mQ;
3102  def p=f;
3103  int i=1;
3104  while (p!=0)
3105  {
3106    lm=lead(p);
3107    p=p-lm;
3108    lc=leadcoef(lm);
3109    lp=leadmonom(lm);
3110    L[size(L)+1]=list(lc,lp);
3111    i++;
3112  }
3113  return(L);
3114}
3115
3116
3117// Auxiliary routine
3118// findindexpolys
3119// input:
3120//   list coefs=( (q11,..,q1r_1),..,(qs1,..,qsr_1) )
3121//               of denominators of the monoms
3122// output:
3123//   list ind=(v_1,..,v_t) of intvec
3124//        each intvec v=(i_1,..,is) corresponds to a polynomial in the sheaf
3125//        that will be built from it in extend procedures.
3126static proc findindexpolys(list coefs)
3127{
3128  int i; int j; intvec numdens;
3129  for(i=1;i<=size(coefs);i++)
3130  {
3131    numdens[i]=size(coefs[i]);
3132  }
3133//  def RR=basering;
3134//  def Rx=ringlist(RR);
3135//  def P=ring(Rx[1]);
3136//  setring(P);
3137//  def coefsp=imap(RR,coefs);
3138  def coefsp=coefs;
3139  ideal cof; list combpolys; intvec v; int te; list mp;
3140  for(i=1;i<=size(coefsp);i++)
3141  {
3142    cof=ideal(0);
3143    for(j=1;j<=size(coefsp[i]);j++)
3144    {
3145      cof[j]=factorize(coefsp[i][j],3);
3146    }
3147    coefsp[i]=cof;
3148  }
3149  for(j=1;j<=size(coefsp[1]);j++)
3150  {
3151    v[1]=j;
3152    te=1;
3153    for (i=2;i<=size(coefsp);i++)
3154    {
3155      mp=memberpos(coefsp[1][j],coefsp[i]);
3156      if(mp[1])
3157      {
3158        v[i]=mp[2];
3159      }
3160      else{v[i]=0;}
3161    }
3162    combpolys[j]=v;
3163  }
3164  combpolys=reform(combpolys,numdens);
3165  //"T_combpolys="; combpolys;
3166  //setring(RR);
3167  //def combpolysT=imap(P,combpolys);
3168 // return(combpolysT);
3169 return(combpolys);
3170}
3171
3172// Auxiliary routine
3173// extendcoef: given Q,P in Q[a] where P/Q specializes on an open and dense subset
3174//      of the whole V(p1 int...int pr), it returns a basis of the module
3175//      of all syzygies equivalent to P/Q,
3176static proc extendcoef(poly fP, poly fQ, ideal idp, ideal idq)
3177{
3178  def RR=basering;
3179  def Rx=ringlist(RR);
3180  def P=ring(Rx[1]);
3181  setring(P);
3182  def PL=ringlist(P);
3183  PL[3][1][1]="dp";
3184  def P1=ring(PL);
3185  setring(P1);
3186  ideal idp0=imap(RR,idp);
3187  option(redSB);
3188  qring q=std(idp0);
3189  poly P0=imap(RR,fP);
3190  poly Q0=imap(RR,fQ);
3191  ideal PQ=Q0,-P0;
3192  module C=syz(PQ);
3193  setring(P);
3194  def idp1=imap(RR,idp);
3195  def idq1=imap(RR,idq);
3196  def C1=matrix(imap(q,C));
3197  def redC=selectregularfun(C1,idp1,idq1);
3198  setring(RR);
3199  def CC=imap(P,redC);
3200  return(CC);
3201}
3202
3203// Auxiliary routine
3204// selectregularfun
3205// input:
3206//   list L of the polynomials matrix CC
3207//      (we assume that one of them is non-null on V(N) \ V(M))
3208//   ideal N, ideal M: ideals representing the locally closed set V(N) \ V(M)
3209// assume to work in @P
3210static proc selectregularfun(matrix C, ideal N, ideal M)
3211{
3212  int numcombused;
3213//   def RR=basering;
3214//   def Rx=ringlist(RR);
3215//   def P=ring(Rx[1]);
3216//   setring(P);
3217//   def C=imap(RR,CC);
3218//   def N=imap(RR,NN);
3219//   def M=imap(RR,MM);
3220  if (ncols(C)==1){return(C);}
3221
3222  int i; int j; int k; list c; intvec ci; intvec c0; intvec c1;
3223  list T; list T0; list T1; list LL; ideal N1;ideal M1; int te=0;
3224  for(i=1;i<=ncols(C);i++)
3225  {
3226    if((C[1,i]!=0) and (C[2,i]!=0))
3227    {
3228      if(c0==intvec(0)){c0[1]=i;}
3229      else{c0[size(c0)+1]=i;}
3230    }
3231  }
3232  def C1=submat(C,1..2,c0);
3233  for (i=1;i<=ncols(C1);i++)
3234  {
3235    c=comb(ncols(C1),i);
3236    for(j=1;j<=size(c);j++)
3237    {
3238      ci=c[j];
3239      numcombused++;
3240      if(i==1){N1=N+C1[2,j]; M1=M;}
3241      if(i>1)
3242      {
3243        kill c0; intvec c0 ; kill c1; intvec c1;
3244        c1=ci[size(ci)];
3245        for(k=1;k<size(ci);k++){c0[k]=ci[k];}
3246        T0=searchinlist(c0,LL);
3247        T1=searchinlist(c1,LL);
3248        N1=T0[1]+T1[1];
3249        M1=intersect(T0[2],T1[2]);
3250      }
3251      T=list(ci,PtoCrep0(Prep0(N1,M1)));
3252      LL[size(LL)+1]=T;
3253      if(equalideals(T[2][1],ideal(1))){te=1; break;}
3254    }
3255    if(te){break;}
3256  }
3257  ci=T[1];
3258  def Cs=submat(C1,1..2,ci);
3259//  setring(RR);
3260//  return(imap(P,Cs));
3261  return(Cs);
3262}
3263
3264// Auxiliary routine
3265// searchinlist
3266// input:
3267//   intvec c:
3268//   list L=( (c1,T1),..(ck,Tk) )
3269//      where the c's are assumed to be intvects
3270// output:
3271//   object T with index c
3272static proc searchinlist(intvec c,list L)
3273{
3274  int i; list T;
3275  for(i=1;i<=size(L);i++)
3276  {
3277    if (L[i][1]==c)
3278    {
3279      T=L[i][2];
3280      break;
3281    }
3282  }
3283  return(T);
3284}
3285
3286// Auxiliary routine
3287// selectminsheaves
3288// Input: L=((v_11,..,v_1k_1),..,(v_s1,..,v_sk_s))
3289//    where:
3290//    The s lists correspond to the s coefficients of the polynomial f
3291//    (v_i1,..,v_ik_i) correspond to the k_i intvec v_ij of the
3292//    spezializations of the jth rekpresentant (Q,P) of the ith coefficient
3293//    v_ij is an intvec of size equal to the number of little segments
3294//    forming the lpp-segment of 0,1, where 1 represents that it specializes
3295//    to non-zedro an the whole little segment and 0 if not.
3296// Output: S=(w_1,..,w_j)
3297//    where the w_l=(n_l1,..,n_ls) are intvec of length size(L), where
3298//    n_lt fixes which element of (v_t1,..,v_tk_t) is to be
3299//    choosen to form the tth (Q,P) for the lth element of the sheaf
3300//    representing the I-regular function.
3301// The selection is done to obtian the minimal number of elements
3302//    of the sheaf that specializes to non-null everywhere.
3303static proc selectminsheaves(list L)
3304{
3305  list C=allsheaves(L);
3306  return(smsheaves(C[1],C[2]));
3307}
3308
3309// Auxiliary routine
3310// smsheaves
3311// Input:
3312//   list C of all the combrep
3313//   list L of the intvec that correesponds to each element of C
3314// Output:
3315//   list LL of the subsets of C that cover all the subsegments
3316//   (the union of the corresponding L(C) has all 1).
3317static proc smsheaves(list C, list L)
3318{
3319  int i; int i0; intvec W;
3320  int nor; int norn;
3321  intvec p;
3322  int sp=size(L[1]); int j0=1;
3323  for (i=1;i<=sp;i++){p[i]=1;}
3324  while (p!=0)
3325  {
3326    i0=0; nor=0;
3327    for (i=1; i<=size(L); i++)
3328    {
3329      norn=numones(L[i],pos(p));
3330      if (nor<norn){nor=norn; i0=i;}
3331    }
3332    W[j0]=i0;
3333    j0++;
3334    p=actualize(p,L[i0]);
3335  }
3336  list LL;
3337  for (i=1;i<=size(W);i++)
3338  {
3339    LL[size(LL)+1]=C[W[i]];
3340  }
3341  return(LL);
3342}
3343
3344// Auxiliary routine
3345// allsheaves
3346// Input: L=((v_11,..,v_1k_1),..,(v_s1,..,v_sk_s))
3347//    where:
3348//    The s lists correspond to the s coefficients of the polynomial f
3349//    (v_i1,..,v_ik_i) correspond to the k_i intvec v_ij of the
3350//    spezializations of the jth rekpresentant (Q,P) of the ith coefficient
3351//    v_ij is an intvec of size equal to the number of little segments
3352//    forming the lpp-segment of 0,1, where 1 represents that it specializes
3353//    to non-zero on the whole little segment and 1 if not.
3354// Output:
3355//    (list LL, list LLS)  where
3356//    LL is the list of all combrep
3357//    LLS is the list of intvec of the corresponding elements of LL
3358static proc allsheaves(list L)
3359{
3360  intvec V; list LL; intvec W; int r; intvec U;
3361  int i; int j; int k;
3362  int s=size(L[1][1]); // s = number of little segments of the lpp-segment
3363  list LLS;
3364  for (i=1;i<=size(L);i++)
3365  {
3366    V[i]=size(L[i]);
3367  }
3368  LL=combrep(V);
3369  for (i=1;i<=size(LL);i++)
3370  {
3371    W=LL[i];   // size(W)= number of coefficients of the polynomial
3372    kill U; intvec U;
3373    for (j=1;j<=s;j++)
3374    {
3375      k=1; r=1; U[j]=1;
3376      while((r==1) and (k<=size(W)))
3377      {
3378        if(L[k][W[k]][j]==0){r=0; U[j]=0;}
3379        k++;
3380      }
3381    }
3382    LLS[i]=U;
3383  }
3384  return(list(LL,LLS));
3385}
3386
3387// Auxiliary routine
3388// numones
3389// Input:
3390//   intvec v of (0,1) in each position
3391//   intvec pos: the positions to test
3392// Output:
3393//   int nor: the nuber of 1 of v in the positions given by pos.
3394static proc numones(intvec v, intvec pos)
3395{
3396  int i; int n;
3397  for (i=1;i<=size(pos);i++)
3398  {
3399    if (v[pos[i]]==1){n++;}
3400  }
3401  return(n);
3402}
3403
3404// Auxiliary routine
3405// actualize: actualizes zeroes of p
3406// Input:
3407//   intvec p: of zeroes and ones
3408//   intvec c: of zeroes and ones (of the same length)
3409// Output;
3410//   intvec pp: of zeroes and ones, where a 0 stays in pp[i] if either
3411//   already p[i]==0 or c[i]==1.
3412static proc actualize(intvec p, intvec c)
3413{
3414  int i; intvec pp=p;
3415  for (i=1;i<=size(p);i++)
3416  {
3417    if ((pp[i]==1) and (c[i]==1)){pp[i]=0;}
3418  }
3419  return(pp);
3420}
3421
3422// Auxiliary routine
3423// intersp: computes the intersection of the ideals in S in @P
3424static proc intersp(list S)
3425{
3426  def RR=basering;
3427  def Rx=ringlist(RR);
3428  def P=ring(Rx[1]);
3429  setring(P);
3430  def SP=imap(RR,S);
3431  option(returnSB);
3432  def NP=intersect(SP[1..size(SP)]);
3433  setring(RR);
3434  return(imap(P,NP));
3435}
3436
3437// Auxiliary routine
3438// radicalmember
3439static proc radicalmember(poly f,ideal ida)
3440{
3441  int te;
3442  def RR=basering;
3443  def Rx=ringlist(RR);
3444  def P=ring(Rx[1]);
3445  setring(P);
3446  def fp=imap(RR,f);
3447  def idap=imap(RR,ida);
3448  poly @t;
3449  ring H=0,@t,dp;
3450  def PH=P+H;
3451  setring(PH);
3452  def fH=imap(P,fp);
3453  def idaH=imap(P,idap);
3454  idaH[size(idaH)+1]=1-@t*fH;
3455  option(redSB);
3456  def G=std(idaH);
3457  if (G==1){te=1;} else {te=0;}
3458  setring(RR);
3459  return(te);
3460}
3461
3462// Auxiliary routine
3463// selectextendcoef
3464// input:
3465//    matrix CC: CC=(p_a1 .. p_ar_a)
3466//                  (q_a1 .. q_ar_a)
3467//            the matrix of elements of a coefficient in oo[a].
3468//    (ideal ida, ideal idb): the canonical representation of the segment S.
3469// output:
3470//    list caout
3471//            the minimum set of elements of CC needed such that at least one
3472//            of the q's is non-null on S, as well as the C-rep of of the
3473//            points where the q's are null on S.
3474//            The elements of caout are of the form (p,q,prep);
3475static proc selectextendcoef(matrix CC, ideal ida, ideal idb)
3476{
3477  def RR=basering;
3478  def Rx=ringlist(RR);
3479  def P=ring(Rx[1]);
3480  setring(P);
3481  def ca=imap(RR,CC);
3482  def E0=imap(RR,ida);
3483  ideal E;
3484  def N=imap(RR,idb);
3485  int r=ncols(ca);
3486  int i; int te=1; list com; int j; int k; intvec c; list prep;
3487  list cs; list caout;
3488  i=1;
3489  while ((i<=r) and (te))
3490  {
3491    com=comb(r,i);
3492    j=1;
3493    while((j<=size(com)) and (te))
3494    {
3495      E=E0;
3496      c=com[j];
3497      for (k=1;k<=i;k++)
3498      {
3499        E=E+ca[2,c[k]];
3500      }
3501      prep=Prep(E,N);
3502      if (i==1)
3503      {
3504        cs[j]=list(ca[1,j],ca[2,j],prep);
3505      }
3506      if ((size(prep)==1) and (equalideals(prep[1][1],ideal(1))))
3507      {
3508        te=0;
3509        for(k=1;k<=size(c);k++)
3510        {
3511          caout[k]=cs[c[k]];
3512        }
3513      }
3514      j++;
3515    }
3516    i++;
3517  }
3518  if (te){"error: extendcoef does not extend to the whole S";}
3519  setring(RR);
3520  return(imap(P,caout));
3521}
3522
3523// Auxiliary routine
3524// plusP
3525// Input:
3526//   ideal E1: in some basering (depends only on the parameters)
3527//   ideal E2: in some basering (depends only on the parameters)
3528// Output:
3529//   ideal Ep=E1+E2; computed in @P
3530static proc plusP(ideal E1,ideal E2)
3531{
3532  def RR=basering;
3533  def Rx=ringlist(RR);
3534  def P=ring(Rx[1]);
3535  setring(P);
3536  def E1p=imap(RR,E1);
3537  def E2p=imap(RR,E2);
3538  def Ep=E1p+E2p;
3539  setring(RR);
3540  return(imap(P,Ep));
3541}
3542
3543// Auxiliary routine
3544// reform
3545// input:
3546//   list combpolys: (v1,..,vs)
3547//      where vi are intvec.
3548//   output outcomb: (w1,..,wt)
3549//      whre wi are intvec.
3550//      All the vi without zeroes are in outcomb, and those with zeroes are
3551//         combined to form new intvec with the rest
3552static proc reform(list combpolys, intvec numdens)
3553{
3554  list combp0; list combp1; int i; int j; int k; int l; list rest; intvec notfree;
3555  list free; intvec free1; int te; intvec v;  intvec w;
3556  int nummonoms=size(combpolys[1]);
3557  for(i=1;i<=size(combpolys);i++)
3558  {
3559    if(memberpos(0,combpolys[i])[1])
3560    {
3561      combp0[size(combp0)+1]=combpolys[i];
3562    }
3563    else {combp1[size(combp1)+1]=combpolys[i];}
3564  }
3565  for(i=1;i<=nummonoms;i++)
3566  {
3567    kill notfree; intvec notfree;
3568    for(j=1;j<=size(combpolys);j++)
3569    {
3570      if(combpolys[j][i]<>0)
3571      {
3572        if(notfree[1]==0){notfree[1]=combpolys[j][i];}
3573        else{notfree[size(notfree)+1]=combpolys[j][i];}
3574      }
3575    }
3576    kill free1; intvec free1;
3577    for(j=1;j<=numdens[i];j++)
3578    {
3579      if(memberpos(j,notfree)[1]==0)
3580      {
3581        if(free1[1]==0){free1[1]=j;}
3582        else{free1[size(free1)+1]=j;}
3583      }
3584      free[i]=free1;
3585    }
3586  }
3587  list amplcombp; list aux;
3588  for(i=1;i<=size(combp0);i++)
3589  {
3590    v=combp0[i];
3591    kill amplcombp; list amplcombp;
3592    amplcombp[1]=intvec(v[1]);
3593    for(j=2;j<=size(v);j++)
3594    {
3595      if(v[j]!=0)
3596      {
3597        for(k=1;k<=size(amplcombp);k++)
3598        {
3599          w=amplcombp[k];
3600          w[size(w)+1]=v[j];
3601          amplcombp[k]=w;
3602        }
3603      }
3604      else
3605      {
3606        kill aux; list aux;
3607        for(k=1;k<=size(amplcombp);k++)
3608        {
3609          for(l=1;l<=size(free[j]);l++)
3610          {
3611            w=amplcombp[k];
3612            w[size(w)+1]=free[j][l];
3613            aux[size(aux)+1]=w;
3614          }
3615        }
3616        amplcombp=aux;
3617      }
3618    }
3619    for(j=1;j<=size(amplcombp);j++)
3620    {
3621      combp1[size(combp1)+1]=amplcombp[j];
3622    }
3623  }
3624  return(combp1);
3625}
3626
3627// Auxiliary routine
3628// precombint
3629// input:  L: list of ideals (works in @P)
3630// output: F0: ideal of polys. F0[i] is a poly in the intersection of
3631//             all ideals in L except in the ith one, where it is not.
3632//             L=(p1,..,ps);  F0=(f1,..,fs);
3633//             F0[i] \in intersect_{j#i} p_i
3634static proc precombint(list L)
3635{
3636  int i; int j; int tes;
3637  def RR=basering;
3638  def Rx=ringlist(RR);
3639  def P=ring(Rx[1]);
3640  setring(P);
3641  list L0; list L1; list L2; list L3; ideal F;
3642  L0=imap(RR,L);
3643  L1[1]=L0[1]; L2[1]=L0[size(L0)];
3644  for (i=2;i<=size(L0)-1;i++)
3645  {
3646    L1[i]=intersect(L1[i-1],L0[i]);
3647    L2[i]=intersect(L2[i-1],L0[size(L0)-i+1]);
3648  }
3649  L3[1]=L2[size(L2)];
3650  for (i=2;i<=size(L0)-1;i++)
3651  {
3652    L3[i]=intersect(L1[i-1],L2[size(L0)-i]);
3653  }
3654  L3[size(L0)]=L1[size(L1)];
3655  for (i=1;i<=size(L3);i++)
3656  {
3657    option(redSB); L3[i]=std(L3[i]);
3658  }
3659  for (i=1;i<=size(L3);i++)
3660  {
3661    tes=1; j=0;
3662    while((tes) and (j<size(L3[i])))
3663    {
3664      j++;
3665      option(redSB);
3666      L0[i]=std(L0[i]);
3667      if(reduce(L3[i][j],L0[i],5)!=0){tes=0; F[i]=L3[i][j];}
3668    }
3669    if (tes){"ERROR a polynomial in all p_j except p_i was not found";}
3670  }
3671  setring(RR);
3672  def F0=imap(P,F);
3673  return(F0);
3674}
3675
3676// Auxiliary routine
3677// minAssGTZ eliminating denominators
3678static proc minGTZ(ideal N);
3679{
3680  int i; int j;
3681  def L=minAssGTZ(N);
3682  for(i=1;i<=size(L);i++)
3683  {
3684    for(j=1;j<=size(L[i]);j++)
3685    {
3686      L[i][j]=cleardenom(L[i][j]);
3687    }
3688  }
3689  return(L);
3690}
3691
3692//********************* Begin KapurSunWang *************************
3693
3694// Auxiliary routine
3695// inconsistent
3696// Input:
3697//   ideal E: of null conditions
3698//   ideal N: of non-null conditions representing V(E) \ V(N)
3699// Output:
3700//   1 if V(E) \ V(N) = empty
3701//   0 if not
3702static proc inconsistent(ideal E, ideal N)
3703{
3704  int j;
3705  int te=1;
3706  int tt;
3707  def RR=basering;
3708  def Rx=ringlist(RR);
3709  if(size(Rx[1])==4)
3710  {
3711    tt=1;
3712    def P=ring(Rx[1]);
3713    setring(P);
3714    def EP=imap(RR,E);
3715    def NP=imap(RR,N);
3716  }
3717  else
3718  {
3719    def EP=E;
3720    def NP=N;
3721  }
3722  poly @t;
3723  ring H=0,@t,dp;
3724  if(tt==1)
3725  {
3726    def RH=P+H;
3727   setring(RH);
3728   def EH=imap(P,EP);
3729   def NH=imap(P,NP);
3730  }
3731  else
3732  {
3733    def RH=RR+H;
3734    setring(RH);
3735    def EH=imap(RR,EP);
3736    def NH=imap(RR,NP);
3737  }
3738  ideal G;
3739  j=1;
3740  while((te==1) and j<=size(NH))
3741  {
3742    G=EH+(1-@t*NH[j]);
3743    option(redSB);
3744    G=std(G);
3745    if (G[1]!=1){te=0;}
3746    j++;
3747  }
3748  setring(RR);
3749  return(te);
3750}
3751
3752// Auxiliary routine
3753// MDBasis: Minimal Dickson Basis
3754static proc MDBasis(ideal G)
3755{
3756  int i; int j; int te=1;
3757  G=sortideal(G);
3758  ideal MD=G[1];
3759  poly lm;
3760  for (i=2;i<=size(G);i++)
3761  {
3762    te=1;
3763    lm=leadmonom(G[i]);
3764    j=1;
3765    while ((te==1) and (j<=size(MD)))
3766    {
3767      if (lm/leadmonom(MD[j])!=0){te=0;}
3768      j++;
3769    }
3770    if (te==1)
3771    {
3772      MD[size(MD)+1]=(G[i]);
3773    }
3774  }
3775  return(MD);
3776}
3777
3778// Auxiliary routine
3779// primepartZ
3780static proc primepartZ(poly f);
3781{
3782  def cp=content(f);
3783  def fp=f/cp;
3784  return(fp);
3785}
3786
3787// LCMLC
3788static proc LCMLC(ideal H)
3789{
3790  int i;
3791  def RR=basering;
3792  def Rx=ringlist(RR);
3793  def P=ring(Rx[1]);
3794  Rx[1]=0;
3795  def D=ring(Rx);
3796  def RP=D+P;
3797  setring(RP);
3798  def HH=imap(RR,H);
3799  poly h=1;
3800  for (i=1;i<=size(HH);i++)
3801  {
3802    h=lcm(h,HH[i]);
3803  }
3804  setring(RR);
3805  def hh=imap(RP,h);
3806  return(hh);
3807}
3808
3809// KSW: Kapur-Sun-Wang algorithm for computing a CGS
3810// Input:
3811//   F:   parametric ideal to be discussed
3812//   Options:
3813//     \"out\",0 Transforms the description of the segments into
3814//     canonical P-representation form.
3815//     \"out\",1 Original KSW routine describing the segments as
3816//     difference of varieties
3817//   The ideal must be defined on C[parameters][variables]
3818// Output:
3819//   With option \"out\",0 :
3820//     ((lpp,
3821//       (1,B,((p_1,(p_11,..,p_1k_1)),..,(p_s,(p_s1,..,p_sk_s)))),
3822//       string(lpp)
3823//      )
3824//      ,..,
3825//      (lpp,
3826//       (k,B,((p_1,(p_11,..,p_1k_1)),..,(p_s,(p_s1,..,p_sk_s)))),
3827//       string(lpp))
3828//      )
3829//     )
3830//   With option \"out\",1 ((default, original KSW) (shorter to be computed,
3831//                    but without canonical description of the segments.
3832//     ((B,E,N),..,(B,E,N))
3833static proc KSW(ideal F, list #)
3834{
3835//   def RR=basering;
3836//   def Rx=ringlist(RR);
3837//   def P=ring(Rx[1]);
3838//   Rx[1]=0;
3839//   def D=ring(Rx);
3840//   def RP=D+p;
3841//   // setglobalrings();
3842  int start=timer;
3843  ideal E=ideal(0);
3844  ideal N=ideal(1);
3845  int comment=0;
3846  int out=1;
3847  int i;
3848  def L=#;
3849  if(size(L)>0)
3850  {
3851    for (i=1;i<=size(L) div 2;i++)
3852    {
3853      if (L[2*i-1]=="null"){E=L[2*i];}
3854      else
3855      {
3856        if (L[2*i-1]=="nonnull"){N=L[2*i];}
3857        else
3858        {
3859          if (L[2*i-1]=="comment"){comment=L[2*i];}
3860          else
3861          {
3862            if (L[2*i-1]=="out"){out=L[2*i];}
3863          }
3864        }
3865      }
3866    }
3867  }
3868  if (comment>0){string("Begin KSW with null = ",E," nonnull = ",N);}
3869  def CG=KSW0(F,E,N,comment);
3870  if (comment>0)
3871  {
3872    string("Number of segments in KSW (total) = ",size(CG));
3873    string("Time in KSW = ",timer-start);
3874  }
3875  if(out==0)
3876  {
3877    CG=KSWtocgsdr(CG);
3878    //"T_CG="; CG;
3879    if( size(CG)>0)
3880    {
3881      CG=groupKSWsegments(CG);
3882      if (comment>0)
3883      {
3884        string("Number of lpp segments = ",size(CG));
3885        string("Time in KSW + group + Prep = ",timer-start);
3886      }
3887    }
3888  }
3889  return(CG);
3890}
3891
3892// Auxiliary routine
3893// sqf
3894static proc sqf(poly f)
3895{
3896  def RR=basering;
3897  def Rx=ringlist(RR);
3898  def P=ring(Rx[1]);
3899  setring(P);
3900  def ff=imap(RR,f);
3901  poly fff=sqrfree(ff,3);
3902  setring(RR);
3903  def ffff=imap(P,fff);
3904  return(ffff);
3905}
3906
3907// Auxiliary routine
3908// KSW0: Kapur-Sun-Wang algorithm for computing a CGS, called by KSW
3909// Input:
3910//   F:   parametric ideal to be discussed
3911//   Options:
3912//   The ideal must be defined on C[parameters][variables]
3913// Output:
3914static proc KSW0(ideal F, ideal E, ideal N, int comment)
3915{
3916  def RR=basering;
3917  def Rx=ringlist(RR);
3918  def P=ring(Rx[1]);
3919  Rx[1]=0;
3920  def D=ring(Rx);
3921  def RP=D+P;
3922  int i; int j; list emp;
3923  list CGS;
3924  ideal N0;
3925  for (i=1;i<=size(N);i++)
3926  {
3927    N0[i]=sqf(N[i]);
3928  }
3929  ideal E0;
3930  for (i=1;i<=size(E);i++)
3931  {
3932    E0[i]=sqf(leadcoef(E[i]));
3933  }
3934  setring(P);
3935  ideal E1=imap(RR,E0);
3936  E1=std(E1);
3937  ideal N1=imap(RR,N0);
3938  N1=std(N1);
3939  setring(RR);
3940  E0=imap(P,E1);
3941  N0=imap(P,N1);
3942  if (inconsistent(E0,N0)==1)
3943  {
3944    return(emp);
3945  }
3946  setring(RP);
3947  def FRP=imap(RR,F);
3948  def ERP=imap(RR,E);
3949  FRP=FRP+ERP;
3950  option(redSB);
3951  def GRP=std(FRP);
3952  setring(RR);
3953  def G=imap(RP,GRP);
3954  if (memberpos(1,G)[1]==1)
3955  {
3956    if(comment>1){"Basis 1 is found"; E; N;}
3957    list KK; KK[1]=list(E0,N0,ideal(1));
3958    return(KK);
3959   }
3960  ideal Gr; ideal Gm; ideal GM;
3961  for (i=1;i<=size(G);i++)
3962  {
3963    if (variables(G[i])[1]==0){Gr[size(Gr)+1]=G[i];}
3964    else{Gm[size(Gm)+1]=G[i];}
3965  }
3966  ideal Gr0;
3967  for (i=1;i<=size(Gr);i++)
3968  {
3969    Gr0[i]=sqf(Gr[i]);
3970  }
3971
3972
3973  Gr=elimrepeated(Gr0);
3974  ideal GrN;
3975  for (i=1;i<=size(Gr);i++)
3976   {
3977    for (j=1;j<=size(N0);j++)
3978    {
3979      GrN[size(GrN)+1]=sqf(Gr[i]*N0[j]);
3980    }
3981  }
3982  if (inconsistent(E,GrN)){;}
3983  else
3984  {
3985    if(comment>1){"Basis 1 is found in a branch with arguments"; E; GrN;}
3986    CGS[size(CGS)+1]=list(E,GrN,ideal(1));
3987  }
3988  if (inconsistent(Gr,N0)){return(CGS);}
3989  GM=Gm;
3990  Gm=MDBasis(Gm);
3991  ideal H;
3992  for (i=1;i<=size(Gm);i++)
3993  {
3994    H[i]=sqf(leadcoef(Gm[i]));
3995  }
3996  H=facvar(H);
3997  poly h=sqf(LCMLC(H));
3998  if(comment>1){"H = "; H; "h = "; h;}
3999  ideal Nh=N0;
4000  if(size(N0)==0){Nh=h;}
4001  else
4002  {
4003    for (i=1;i<=size(N0);i++)
4004    {
4005      Nh[i]=sqf(N0[i]*h);
4006    }
4007  }
4008  if (inconsistent(Gr,Nh)){;}
4009  else
4010  {
4011    CGS[size(CGS)+1]=list(Gr,Nh,Gm);
4012  }
4013  poly hc=1;
4014  list KS;
4015  ideal GrHi;
4016  for (i=1;i<=size(H);i++)
4017  {
4018    kill GrHi;
4019    ideal GrHi;
4020    Nh=N0;
4021    if (i>1){hc=sqf(hc*H[i-1]);}
4022    for (j=1;j<=size(N0);j++){Nh[j]=sqf(N0[j]*hc);}
4023    if (equalideals(Gr,ideal(0))==1){GrHi=H[i];}
4024    else {GrHi=Gr,H[i];}
4025    if(comment>1){"Call to KSW with arguments "; GM; GrHi;  Nh;}
4026    KS=KSW0(GM,GrHi,Nh,comment);
4027    for (j=1;j<=size(KS);j++)
4028    {
4029      CGS[size(CGS)+1]=KS[j];
4030    }
4031    if(comment>1){"CGS after KSW = "; CGS;}
4032  }
4033  return(CGS);
4034}
4035
4036// Auxiliary routine
4037// KSWtocgsdr
4038static proc KSWtocgsdr(list L)
4039{
4040  int i; list CG; ideal B; ideal lpp; int j; list NKrep;
4041  for(i=1;i<=size(L);i++)
4042  {
4043    B=redgbn(L[i][3],L[i][1],L[i][2]);
4044    lpp=ideal(0);
4045    for(j=1;j<=size(B);j++)
4046    {
4047      lpp[j]=leadmonom(B[j]);
4048    }
4049    NKrep=KtoPrep(L[i][1],L[i][2]);
4050    CG[i]=list(lpp,B,NKrep);
4051  }
4052  return(CG);
4053}
4054
4055// Auxiliary routine
4056// KtoPrep
4057// Computes the P-representaion of a K-representation (N,W) of a set
4058// input:
4059//    ideal E (null conditions)
4060//    ideal N (non-null conditions ideal)
4061// output:
4062//    the ((p_1,(p_11,..,p_1k_1)),..,(p_r,(p_r1,..,p_rk_r)));
4063//    the Prep of V(N) \ V(W)
4064static proc KtoPrep(ideal N, ideal W)
4065{
4066  int i; int j;
4067  if (N[1]==1)
4068  {
4069    L0[1]=list(ideal(1),list(ideal(1)));
4070    return(L0);
4071  }
4072  def RR=basering;
4073  def Rx=ringlist(RR);
4074  def P=ring(Rx[1]);
4075  setring(P);
4076  ideal B; int te; poly f;
4077  ideal Np=imap(RR,N);
4078  ideal Wp=imap(RR,W);
4079  list L;
4080  list L0; list T0;
4081  L0=minGTZ(Np);
4082  for(j=1;j<=size(L0);j++)
4083  {
4084    option(redSB);
4085    L0[j]=std(L0[j]);
4086  }
4087  for(i=1;i<=size(L0);i++)
4088  {
4089    if(inconsistent(L0[i],Wp)==0)
4090    {
4091      B=L0[i]+Wp;
4092      T0=minGTZ(B);
4093      option(redSB);
4094      for(j=1;j<=size(T0);j++)
4095      {
4096        T0[j]=std(T0[j]);
4097      }
4098      L[size(L)+1]=list(L0[i],T0);
4099    }
4100  }
4101  setring(RR);
4102  def LL=imap(P,L);
4103  return(LL);
4104}
4105
4106// Auxiliary routine
4107// groupKSWsegments
4108// input:  the list of vertices of KSW
4109// output: the same terminal vertices grouped by lpp
4110static proc groupKSWsegments(list T)
4111{
4112  int i; int j;
4113  list L;
4114  list lpp; list lppor;
4115  list kk;
4116  lpp[1]=T[1][1]; j=1;
4117  lppor[1]=intvec(1);
4118  for(i=2;i<=size(T);i++)
4119  {
4120    kk=memberpos(T[i][1],lpp);
4121    if(kk[1]==0){j++; lpp[j]=T[i][1]; lppor[j]=intvec(i);}
4122    else{lppor[kk[2]][size(lppor[kk[2]])+1]=i;}
4123  }
4124  list ll;
4125  for (j=1;j<=size(lpp);j++)
4126  {
4127    kill ll; list ll;
4128    for(i=1;i<=size(lppor[j]);i++)
4129    {
4130      ll[size(ll)+1]=list(i,T[lppor[j][i]][2],T[lppor[j][i]][3]);
4131    }
4132    L[j]=list(lpp[j],ll,string(lpp[j]));
4133  }
4134  return(L);
4135}
4136
4137//********************* End KapurSunWang *************************
4138
4139//********************* Begin ConsLevels ***************************
4140
4141static proc zeroone(int n)
4142{
4143  list L; list L2;
4144  intvec e; intvec e2; intvec e3;
4145  int j;
4146  if(n==1)
4147  {
4148    e[1]=0;
4149    L[1]=e;
4150    e[1]=1;
4151    L[2]=e;
4152    return(L);
4153  }
4154  if(n>1)
4155  {
4156    L=zeroone(n-1);
4157    for(j=1;j<=size(L);j++)
4158    {
4159      e2=L[j];
4160      e3=e2;
4161      e3[size(e3)+1]=0;
4162      L2[size(L2)+1]=e3;
4163      e3=e2;
4164      e3[size(e3)+1]=1;
4165      L2[size(L2)+1]=e3;
4166    }
4167  }
4168  return(L2);
4169}
4170
4171// Auxiliary routine
4172// subsets: the list of subsets of (1,..n)
4173static proc subsets(int n)
4174{
4175  list L; list L1;
4176  int i; int j;
4177  L=zeroone(n);
4178  intvec e; intvec e1;
4179  for(i=1;i<=size(L);i++)
4180  {
4181    e=L[i];
4182    kill e1; intvec e1;
4183    for(j=1;j<=n;j++)
4184    {
4185      if(e[n+1-j]==1)
4186      {
4187        if(e1==intvec(0)){e1[1]=j;}
4188        else{e1[size(e1)+1]=j};
4189      }
4190    }
4191    L1[i]=e1;
4192  }
4193  return(L1);
4194}
4195
4196// Input a list A of locally closed sets in C-rep
4197// Output a list B of a simplified list of A
4198static proc SimplifyUnion(list A)
4199{
4200  int i; int j;
4201  list L=A;
4202  int n=size(L);
4203  if(n<2){return(A);}
4204  intvec w;
4205  for(i=1;i<=size(L);i++)
4206  {
4207    for(j=1;j<=size(L);j++)
4208    {
4209      if(i != j)
4210      {
4211        if(equalideals(L[i][2],L[j][1])==1)
4212        {
4213          L[i][2]=L[j][2];
4214          w[size(w)+1]=j;
4215        }
4216      }
4217    }
4218  }
4219  if(size(w)>0)
4220  {
4221    for(i=1; i<=size(w);i++)
4222    {
4223      j=w[size(w)+1-i];
4224      L=elimfromlist(L, j);
4225    }
4226  }
4227  ideal T=ideal(1);
4228  intvec v;
4229  for(i=1;i<=size(L);i++)
4230  {
4231    if(equalideals(L[i][2],ideal(1)))
4232    {
4233      v[size(v)+1]=i;
4234      T=intersect(T,L[i][1]);
4235    }
4236  }
4237  if(size(v)>0)
4238  {
4239    for(i=1; i<=size(v);i++)
4240    {
4241      j=v[size(v)+1-i];
4242      L=elimfromlist(L, j);
4243    }
4244  }
4245  if(equalideals(T,ideal(1))==0){L[size(L)+1]=list(std(T),ideal(1))};
4246  return(L);
4247}
4248
4249// input list A=[[p1,q1],...,[pn,qn]] :
4250//                    the list of segments of a constructible set S, where each [pi,qi] is given in C-representation
4251// output list [topA,C]
4252//       where topA is the closure of A
4253//                 C is the list of segments of the complement of A given in C-representation
4254static proc FirstLevel(list A)
4255{
4256  int n=size(A);
4257  list T=zeroone(n);
4258  ideal P; ideal Q;
4259  list Cb;  ideal Cc=1;
4260  int i; int j;
4261  intvec t;
4262  ideal topA=1;
4263  list C;
4264  for(i=1;i<=n;i++)
4265  {
4266    topA=intersect(topA,A[i][1]);
4267  }
4268  //topA=std(topA);
4269  for(i=2; i<=size(T);i++)
4270  {
4271    t=T[i];
4272    //"T_t"; t;
4273    P=0; Q=1;
4274    for(j=1;j<=n;j++)
4275    {
4276      if(t[n+1-j]==1)
4277      {
4278        P=P+A[j][2];
4279      }
4280      else
4281      {
4282        Q=intersect(Q,A[j][1]);
4283      }
4284    }
4285    Cb=Crep0(P,Q);
4286    //"T_Cb="; Cb;
4287    if(size(Cb)!=0)
4288    {
4289      if( Cb[1][1]<>1)
4290      {
4291        C[size(C)+1]=Cb;
4292      }
4293    }
4294  }
4295  if(size(C)>1){C=SimplifyUnion(C);}
4296  return(list(topA,C));
4297}
4298
4299// Input:
4300// Output:
4301static proc ConstoPrep(list L)
4302{
4303  list L1;
4304  int i; int j;
4305  list aux;
4306  for(i=1;i<=size(L);i++)
4307  {
4308    aux=Prep(L[i][2][1],L[i][2][2]);
4309    L1[size(L1)+1]=list(L[i][1],aux);
4310  }
4311  return(L1);
4312}
4313
4314
4315// Input:
4316//     list A =  [[P1,Q1], .. [Pn,Qn]]
4317//                  A constructible set as union of locally closed sets represented by pairs of ideals
4318// Output:
4319//     list L =[p1,p2,p3,...,pk]
4320//        where pi is the ideal of the closure of level i alternatively of  A or its complement
4321//        Note: the levels of A are [p1,p2], [p3,p4], [p5,p6],...
4322//                 the levels of C are [p2,p3],[p4,p5], ...
4323//                 expressed in C-representation
4324//    Assumed to be called in the ring Q[a]
4325proc ConsLevels(list A0)
4326"USAGE: ConsLevels(list L);
4327       L=[[P1,Q1],...,[Ps,Qs]] is a list of lists of of pairs of
4328       ideals represening the constructible set
4329       S=V(P1) \ V(Q1) u ... u V(Ps) \ V(Qs).
4330       To be called in a ring Q[a][x] or a ring Q[a]. But the
4331       ideals can contain only the parameters in Q[a].
4332RETURN: The list of ideals [a1,a2,...,at] representing the
4333       closures of the canonical levels of S and its
4334       complement C wrt to the closure of S. The
4335       canonical levels of S are represented by theirs
4336       Crep. So we have:
4337       Levels of S:  [a1,a2],[a3,a4],...
4338       Levels of C:  [a2,a3],[a4,a5],...
4339       S=V(a1) \ V(a2) u V(a3) \ V(a4) u ...
4340       C=V(a2 \ V(a3) u V(a4) \ V(a5) u ...
4341       The expression of S can be obtained from the
4342       output of ConsLevels by
4343       the call to Levels.
4344NOTE: The algorithm was described in
4345       J.M. Brunat, A. Montes. \"Computing the canonical
4346       representation of constructible sets.\"
4347       Math.  Comput. Sci. (2016) 19: 165-178.
4348KEYWORDS: constructible set; locally closed set; canonical form
4349EXAMPLE:  ConsLevels; shows an example"
4350{
4351  int te;
4352  def RR=basering;
4353  def Rx=ringlist(RR);
4354  if(size(Rx[1])==4)
4355  {
4356    te=1;
4357    def P=ring(Rx[1]);
4358    setring P;
4359    list A=imap(RR,A0);
4360  }
4361  // if(defined(@P)){te=1; setring(@P); list A=imap(RR,A0);}
4362  else {te=0; def A=A0;}
4363
4364  list L; list C;
4365  list B; list T; int i;
4366  for(i=1; i<=size(A);i++)
4367  {
4368    T=Crep0(A[i][1],A[i][2]);
4369    B[size(B)+1]=T;
4370  }
4371  list K;
4372  while(size(B)>0)
4373  {
4374    K=FirstLevel(B);
4375    //"T_K="; K;
4376    L[size(L)+1]=K[1];
4377    B=K[2];
4378   }
4379  L[size(L)+1]=ideal(1);
4380  if(te==1) {setring(RR); def LL=imap(P,L);}
4381  if(te==0){def LL=L;}
4382  return(LL);
4383}
4384example
4385{
4386"EXAMPLE:"; echo = 2;
4387  if(defined(R)){kill R;}
4388  ring R=0,(x,y,z),lp;
4389  short=0;
4390  ideal P1=x*(x^2+y^2+z^2-1);
4391  ideal Q1=z,x^2+y^2-1;
4392  ideal P2=y,x^2+z^2-1;
4393  ideal Q2=z*(z+1),y,x*(x+1);
4394
4395  list Cr1=Crep(P1,Q1);
4396  list Cr2=Crep(P2,Q2);
4397  list L=list(Cr1,Cr2);
4398  L;
4399
4400  ConsLevels(L);
4401}
4402
4403// Converts the output of ConsLevels, given by the set of closures of the Levels of the constructible S
4404//     to an expression where the Levels are apparent.
4405// Input: The ouput of ConsLevels of the form
4406//    [A1,A2,..,Ak], where the Ai's are the closures of the levels.
4407// Output: An expression of the form
4408//      L1=[[1,[A1,A2]],[3,[A3,A4]],..,[2l-1,[A_{2l-1},A_{2l}]]] the list of Levels of S
4409proc Levels(list L)
4410"USAGE: Levels(list L);
4411       The input list L must be the output of the call to the
4412       routine ConsLevels of a constructible set:
4413       L=[a1,a2,..,ak], where the a's are the closures
4414       of the levels, determined by ConsLevels.
4415       Levels selects the levels of the
4416       constructible set. To be called in a ring Q[a][x]
4417       or a ring Q[a]. But the ideals can contain
4418       only the parameters in Q[a].
4419RETURN: The levels of the constructible set:
4420       Lc=[ [1,[a1,a2]],[3,[a3,a4]],..,
4421           [2l-1,[a_{2l-1},a_{2l}]] ]
4422       the list of  levels of S
4423KEYWORDS: constructible sets; canonical form
4424EXAMPLE:  Levels shows an example"
4425{
4426  int n=size(L) div 2;
4427  int i;
4428  list L1; list L2;
4429  for(i=1; i<=n;i++)
4430  {
4431    L1[size(L1)+1]=list(2*i-1,list(L[2*i-1],L[2*i]));
4432  }
4433  return(L1);
4434}
4435example
4436{
4437"EXAMPLE:"; echo = 2;
4438  if(defined(R)){kill R;}
4439  ring R=0,(x,y,z),lp;
4440  short=0;
4441  ideal P1=(x^2+y^2+z^2-1);
4442  ideal Q1=z,x^2+y^2-1;
4443  ideal P2=y,x^2+z^2-1;
4444  ideal Q2=z*(z+1),y,x*(x+1);
4445  ideal P3=x;
4446  ideal Q3=5*z-4,5*y-3,x;
4447
4448  list Cr1=Crep(P1,Q1);
4449  list Cr2=Crep(P2,Q2);
4450  list Cr3=Crep(P3,Q3);
4451  list L=list(Cr1,Cr2,Cr3);
4452
4453  L;
4454
4455  def LL=ConsLevels(L);
4456  LL;
4457
4458  Levels(LL);
4459}
4460
4461//**************************** End ConsLevels ******************
4462
4463//******************** Begin locus and envelop ******************************
4464
4465// indepparameters
4466// Auxiliary routine to detect 'Special' components of the locus
4467// Input: ideal B
4468// Output:
4469//   1 if the ideal does not depend on the parameters
4470//   0 if they depend
4471static proc indepparameters(ideal B)
4472{
4473  def RR=basering;
4474  list Rx=ringlist(RR);
4475  def P=ring(Rx[1]);
4476  Rx[1]=0;
4477  def D=ring(Rx);
4478  def RP=D+P;
4479    // if(defined(@P)){kill @P; kill @RP; kill @R;}
4480   //  setglobalrings();
4481   ideal v=variables(B);
4482  setring RP;
4483  def BP=imap(RR,B);
4484  def vp=imap(RR,v);
4485  ideal varpar=variables(BP);
4486  int te;
4487  te=equalideals(vp,varpar);
4488  setring(RR);
4489  // kill @P; kill @RP; kill @R;
4490  if(te){return(1);}
4491  else{return(0);}
4492}
4493
4494// indepparameterspoly
4495// Auxiliary routine to detect 'Special' components of the locus
4496// Input: ideal B
4497// Output:
4498//   1 if the solutions of the ideal (or poly) does not depend on the parameters
4499//   0 if they depend
4500static proc indepparameterspoly(B)
4501{
4502  def RR=basering;
4503  list Rx=ringlist(RR);
4504  def P=ring(Rx[1]);
4505  Rx[1]=0;
4506  def D=ring(Rx);
4507  def RP=D+P;
4508    // if(defined(@P)){kill @P; kill @RP; kill @R;}
4509   //  setglobalrings();
4510   ideal v=variables(B);
4511  setring RP;
4512  def BP=imap(RR,B);
4513  def vp=imap(RR,v);
4514  ideal varpar=variables(BP);
4515  int te;
4516  te=equalideals(vp,varpar);
4517  setring(RR);
4518  // kill @P; kill @RP; kill @R;
4519  if(te){return(1);}
4520  else{return(0);}
4521}
4522
4523// dimP0: Auxiliary routine
4524// if the dimension in @P of an ideal in the parameters has dimension 0 then it returns 0
4525// else it retuns 1
4526static proc dimP0(ideal N)
4527{
4528  def RR=basering;
4529  def Rx=ringlist(RR);
4530  def P=ring(Rx[1]);
4531  setring P;
4532  // if(defined(@P)){ kill @P; kill @RP; kill @R;}
4533  // setglobalrings();
4534  // setring(@P);
4535  int te=1;
4536  def NP=imap(RR,N);
4537  attrib(NP,"IsSB",1);
4538  int d=dim(std(NP));
4539  //"T_d="; d;
4540  if(d==0){te=0;}
4541  setring(RR);
4542  return(te);
4543}
4544
4545//  DimPar
4546//  Auxilliary routine to NorSing determining the dimension of a parametric ideal
4547//  Does not use @P and define it directly because is assumes that
4548//                              variables and parameters have been inverted
4549 static proc DimPar(ideal E)
4550 {
4551   def RRH=basering;
4552   def RHx=ringlist(RRH);
4553   def P=ring(RHx[1]);
4554   setring(P);
4555   def E2=std(imap(RRH,E));
4556   attrib(E2,"IsSB",1);
4557   def d=dim(E2);
4558   setring RRH;
4559   return(d);
4560 }
4561
4562//  DimPar
4563//  Auxilliary routine to locus2 determining the dimension of a parametric ideal
4564//  it is identical to DimPar but adds infromation about the character of the component
4565static proc dimComp(ideal PA)
4566{
4567  def RR=basering;
4568  list Rx=ringlist(RR);
4569  int n=size(Rx[1][2]);
4570  def P=ring(Rx[1]);
4571  setring(P);
4572  list Lout;
4573  def CP=imap(RR,PA);
4574  attrib(CP,"IsSB",1);
4575  int d=dim(std(CP));
4576  if(d==n-1){Lout[1]=d;Lout[2]="Degenerate"; }
4577  else {Lout[1]=d; Lout[2]="Accumulation";}
4578  setring RR;
4579  return(Lout);
4580}
4581
4582// Takes a list of intvec and sorts it and eliminates repeated elements.
4583// Auxiliary routine
4584static proc sortpairs(L)
4585{
4586  def L1=sort(L);
4587  def L2=elimrepeated(L1[1]);
4588  return(L2);
4589}
4590
4591// Eliminates the pairs of L1 that are also in L2.
4592// Auxiliary routine
4593static proc minuselements(list L1,list L2)
4594{
4595  int i;
4596  list L3;
4597  for (i=1;i<=size(L1);i++)
4598  {
4599    if(not(memberpos(L1[i],L2)[1])){L3[size(L3)+1]=L1[i];}
4600  }
4601  return(L3);
4602}
4603
4604// NorSing
4605// Input:
4606//   ideal B: the basis of a component of the grobcov
4607//   ideal E: the top of the component (assumed to be of dimension > 0 (single equation)
4608//   ideal N: the holes of the component
4609// Output:
4610//   int d: the dimension of B on the variables (anti-image).
4611//     if d>0    then the component is 'Normal'
4612//     if d==0 then the component is 'Singular'
4613static proc NorSing(ideal B, ideal E, ideal N, list #)
4614  {
4615    int i; int j; int Fenv=0; int env; int dd;
4616    list DD=#;
4617    def RR=basering;
4618    int moverdim=npars(RR);
4619    ideal vmov;
4620    int version=0;
4621    int nv=nvars(RR);
4622    if(nv<4){version=1;}
4623    int d;
4624    poly F;
4625    for(i=1;i<=(size(DD) div 2);i++)
4626    {
4627      if(DD[2*i-1]=="vmov"){vmov=DD[2*i];}
4628      if(DD[2*i-1]=="movdim"){moverdim=DD[2*i];}
4629      if(DD[2*i-1]=="version"){version=DD[2*i];}
4630      if(DD[2*i-1]=="family"){F=DD[2*i];}
4631    }
4632    if(F!=0){Fenv=1;}
4633    list L0;
4634    if(dimP0(E)==0){L0=2,"Normal";} //  2 es fals pero ha de ser >0 encara que sigui 0
4635    else
4636    {
4637      if(version==0)
4638      {
4639          // Computing std(B+E,plex(x,y,x1,..xn)) one can detect if there is a first part
4640          // independent of parameters giving the variables with dimension 0
4641       dd=indepparameters(B);
4642       //"T_dd="; dd;
4643        if (dd==1){d=0; L0=d,string(B);}  // ,determineF(B,F,E)
4644        else{d=1; L0=2,"Normal";}
4645      }
4646      else
4647      {
4648        def RH=ringlist(RR);
4649         //"T_RH="; RH;
4650        def H=RH;
4651        H[1]=0;
4652        H[2]=RH[1][2]+RH[2];
4653        int n=size(H[2]);
4654        intvec ll;
4655        for(i=1;i<=n;i++)
4656        {
4657          ll[i]=1;
4658        }
4659        H[3][1][1]="lp";
4660        H[3][1][2]=ll;
4661        def RRH=ring(H);
4662        setring(RRH);
4663        ideal BH=imap(RR,B);
4664        ideal EH=imap(RR,E);
4665        ideal NH=imap(RR,N);
4666        if(Fenv==1){poly FH=imap(RR,F);}
4667        for(i=1;i<=size(EH);i++){BH[size(BH)+1]=EH[i];}
4668        BH=std(BH);  //  MOLT COSTOS!!!
4669        ideal G;
4670        ideal r; poly q;
4671        for(i=1;i<=size(BH);i++)
4672        {
4673          r=factorize(BH[i],1);
4674          q=1;
4675          for(j=1;j<=size(r);j++)
4676          {
4677            if((pdivi(r[j],NH)[1] != 0) or (equalideals(ideal(NH),ideal(1))))
4678            {
4679              q=q*r[j];
4680            }
4681          }
4682          if(q!=1){G[size(G)+1]=q;}
4683        }
4684        setring RR;
4685        def GG=imap(RRH,G);
4686        ideal GGG;
4687        if(defined(L0)){kill L0; list L0;}
4688        for(i=1;i<=size(GG);i++)
4689        {
4690          if(indepparameters(GG[i])){GGG[size(GGG)+1]=GG[i];}
4691        }
4692        GGG=std(GGG);
4693        ideal GLM;
4694        for(i=1;i<=size(GGG);i++)
4695        {
4696          GLM[i]=leadmonom(GGG[i]);
4697        }
4698        attrib(GLM,"IsSB",1);
4699        d=dim(std(GLM));
4700        string antiimi=string(GGG);
4701        L0=d,antiimi;
4702        if(d==0)  // d<dim(V(E) \ V(N))?
4703        {
4704           " ";string("Anti-image of Special component = ", GGG);
4705        }
4706        else
4707        {
4708          L0[2]="Normal";
4709        }
4710      }
4711    }
4712     //"T_L0="; L0;
4713    return(L0);
4714  }
4715
4716static proc determineF(ideal A,poly F,ideal E)
4717{
4718  int env; int i;
4719  def RR=basering;
4720  def RH=ringlist(RR);
4721  def H=RH;
4722  H[1]=0;
4723  H[2]=RH[1][2]+RH[2];
4724  int n=size(H[2]);
4725  intvec ll;
4726  for(i=1;i<=n;i++)
4727  {
4728    ll[i]=1;
4729  }
4730  H[3][1][1]="lp";
4731  H[3][1][2]=ll;
4732  def RRH=ring(H);
4733
4734        //" ";string("Anti-image of Special component = ", GGG);
4735
4736   setring(RRH);
4737   list LL;
4738   def AA=imap(RR,A);
4739   def FH=imap(RR,F);
4740   def EH=imap(RR,E);
4741   ideal M=std(AA+FH);
4742   def rh=reduce(EH,M,5);
4743   //"T_AA="; AA; "T_FH="; FH; "T_EH="; EH; "T_rh="; rh;
4744   if(rh==0){env=1;} else{env=0;}
4745   setring RR;
4746          //L0[3]=env;
4747    //"T_env="; env;
4748    return(env);
4749}
4750
4751
4752// locus0(G): Private routine used by locus (the public routine), that
4753//               builds the diferent components.
4754// input:     The output G of the grobcov (in generic representation, which is the default option)
4755//       Options: The algorithm allows the following options as pair of arguments:
4756//               "movdim", d  : by default movdim is 2 but it can be set to other values
4757//                  when locus is called by envelop then as default is uses d=dim @P
4758//               "version", v   :  There are two versions of the algorithm. ('version',1) is
4759//                  a full algorithm that always distinguishes correctly between 'Normal'
4760//                  and 'Special' components, whereas ('version',0) can decalre a component
4761//                  as 'Normal' being really 'Special', but is more effective. By default ('version',1)
4762//                  is used when the number of variables is less than 4 and 0 if not.
4763//                  The user can force to use one or other version, but it is not recommended.
4764//               "system", ideal F: if the initial systrem is passed as an argument. This is actually not used.
4765//               "comments", c: by default it is 0, but it can be set to 1.
4766//                 Usually locus problems have mover coordinates, variables and tracer coordinates.
4767//                 The mover coordinates are to be placed as the last variables, and by default,
4768//                 its number is dim @P, but as option it can be set to other values.
4769// output:
4770//         list, the canonical P-representation of the Normal and Non-Normal locus:
4771//              The Normal locus has two kind of components: Normal and Special.
4772//              The Non-normal locus has two kind of components: Accumulation and Degenerate.
4773//              This routine is complemented by locus that calls it in order to eliminate problems
4774//              with degenerate points of the mover.
4775//         The output components are given as
4776//              ((p1,(p11,..p1s_1),type_1,level_1),..,(pk,(pk1,..pks_k),type_k,level_k)
4777//         The components are given in canonical P-representation of the subset.
4778//              If all levels of a class of locus are 1, then the set is locally closed. Otherwise the level
4779//              gives the depth of the component.
4780static proc locus0(list GG, list #)
4781{
4782  int te=0;
4783  int t1=1; int t2=1; int i;
4784  def RR=basering;
4785  def Rx=ringlist(RR);
4786  def P=ring(Rx[1]);
4787  def RX=Rx;
4788  RX[1]=0;
4789  def D=ring(RX);
4790  def RP=D+P;
4791
4792  // if(defined(@P)==1){te=1; kill @P; kill @R; kill @RP; }
4793  // setglobalrings();
4794  //Options
4795  list DD=#;
4796  ideal vmov;
4797  int moverdim=size(ringlist(RR)[1][2]);
4798  int dimpar=size(Rx[1][2]);
4799  int dimvar=size(Rx[2]);
4800  int nv=nvars(RR);
4801  //if(moverdim>nv){moverdim=nv;}
4802  //for(i=1;i<=moverdim;i++)
4803  for(i=1;i<=nv;i++)
4804  {
4805    //string("T_moverdim=",moverdim,"T_nv=",nv,"T_var(",i,")=",var(i));
4806    //vmov[size(vmov)+1]=var(i+nv-moverdim);
4807    vmov[size(vmov)+1]=var(i);
4808  }
4809  //string("T_moverdim=",moverdim,"; dimvar=",dimvar,"; dimpar=",dimpar,"; vmov=",vmov);
4810  int version=0;
4811  //if(nv<4){version=1;}
4812  int comment=0;
4813  ideal Fm;
4814  poly F;
4815  for(i=1;i<=(size(DD) div 2);i++)
4816  {
4817    if(DD[2*i-1]=="vmov"){vmov=DD[2*i];}
4818    if(DD[2*i-1]=="version"){version=DD[2*i];}
4819    if(DD[2*i-1]=="system"){Fm=DD[2*i];}
4820    if(DD[2*i-1]=="comment"){comment=DD[2*i];}
4821    if(DD[2*i-1]=="family"){F=DD[2*i];}
4822  }
4823  list HHH;
4824  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)
4825    {return(HHH);}
4826  list G1; list G2;
4827  def G=GG;
4828  list Q1; list Q2;
4829  int d; int j; int k;
4830  t1=1;
4831  for(i=1;i<=size(G);i++)
4832  {
4833    attrib(G[i][1],"IsSB",1);
4834    d=dim(std(G[i][1]));
4835    if(d==0){G1[size(G1)+1]=G[i];}
4836    else
4837    {
4838      if(d>0){G2[size(G2)+1]=G[i];}
4839    }
4840  }
4841  if(size(G1)==0){t1=0;}  // normal point components
4842  if(size(G2)==0){t2=0;}  // non-normal point components
4843  //"T_G1="; G1; "T_G2="; G2;
4844  setring(RP);
4845  if(t1)
4846  {
4847    list G1RP=imap(RR,G1);
4848  }
4849  else {list G1RP;}
4850  list P1RP;
4851  ideal B;
4852  for(i=1;i<=size(G1RP);i++)
4853  {
4854    kill B;
4855     ideal B;
4856     for(k=1;k<=size(G1RP[i][3]);k++)
4857     {
4858       attrib(G1RP[i][3][k][1],"IsSB",1);
4859       G1RP[i][3][k][1]=std(G1RP[i][3][k][1]);
4860       for(j=1;j<=size(G1RP[i][2]);j++)
4861       {
4862         B[j]=reduce(G1RP[i][2][j],G1RP[i][3][k][1]);
4863       }
4864       B=std(B);
4865       P1RP[size(P1RP)+1]=list(G1RP[i][3][k][1],G1RP[i][3][k][2],B);
4866     }
4867  }  //In P1RP the basis has been reduced wrt the top
4868   setring(RR);
4869  ideal h;
4870  list P1;
4871  if(t1)
4872  {
4873    P1=imap(RP,P1RP);
4874    for(i=1;i<=size(P1);i++)
4875    {
4876      for(j=1;j<=size(P1[i][3]);j++)
4877      {
4878        h=factorize(P1[i][3][j],1);
4879        P1[i][3][j]=h[1];
4880        for(k=2;k<=size(h);k++)
4881        {
4882          P1[i][3][j]=P1[i][3][j]*h[k];
4883        }
4884      }
4885    }
4886  } //In P1 factors in the basis independent of the parameters have been obtained
4887  ideal BB; int dd; list NS;
4888  for(i=1;i<=size(P1);i++)
4889  {
4890     //"T_P1="; P1;
4891     NS=NorSing(P1[i][3],P1[i][1],P1[i][2][1],DD);
4892     //"T_NS="; NS;
4893     dd=NS[1];
4894     if(dd==0){P1[i][3]=NS;}  //"Special"; //dd==0
4895     else{P1[i][3]="Normal";}
4896  }
4897  list P2;
4898  for(i=1;i<=size(G2);i++)
4899  {
4900    for(k=1;k<=size(G2[i][3]);k++)
4901    {
4902      P2[size(P2)+1]=list(G2[i][3][k][1],G2[i][3][k][2]);
4903    }
4904  }
4905  list l;
4906  for(i=1;i<=size(P1);i++){Q1[i]=l; Q1[i][1]=P1[i];} P1=Q1;
4907  for(i=1;i<=size(P2);i++){Q2[i]=l; Q2[i][1]=P2[i];} P2=Q2;
4908
4909  // if(defined(@P)){te=1; kill @P; kill @RP; kill @R;}
4910  // setglobalrings();
4911
4912  setring(P);
4913  ideal J;
4914  if(t1==1)
4915  {
4916    def C1=imap(RR,P1);
4917    def L1=AddLocus(C1);
4918   }
4919  else{list C1; list L1; kill P1; list P1;}
4920  if(t2==1)
4921  {
4922    def C2=imap(RR,P2);
4923    def L2=AddLocus(C2);
4924  }
4925  else{list L2; list C2; kill P2; list P2;}
4926  for(i=1;i<=size(L2);i++)
4927  {
4928    J=std(L2[i][2]);
4929    d=dim(J);
4930    if(d+1==dimpar)
4931    {
4932      L2[i][4]=string("Degenerate",L2[i][4]);
4933    }
4934    else{L2[i][4]=string("Accumulation",L2[i][4]);}
4935  }
4936  list LN;
4937  if(t1==1)
4938  {
4939    for(i=1;i<=size(L1);i++){LN[size(LN)+1]=L1[i];}
4940  }
4941  if(t2==1)
4942  {
4943    for(i=1;i<=size(L2);i++){LN[size(LN)+1]=L2[i];}
4944  }
4945  int tLN=1;
4946  if(size(LN)==0){tLN=0;}
4947  setring(RR);
4948  if(tLN)
4949  {
4950   def L=imap(P,LN);
4951    for(i=1;i<=size(L);i++){if(size(L[i][2])==0){L[i][2]=ideal(1);}}
4952    list LL;
4953    for(i=1;i<=size(L);i++)
4954    {
4955      if(typeof(L[i][4])=="list") {L[i][4][1]="Special";}
4956      l[1]=L[i][2];
4957      l[2]=L[i][3];
4958      l[3]=L[i][4];
4959      l[4]=L[i][5];
4960      L[i]=l;
4961    }
4962  }
4963  else{list L;}
4964  // if(te==1){kill @P; kill @RP; kill @R;}
4965  return(L);
4966}
4967
4968// locus2(G): Private routine used by locus (the public routine), that
4969//                builds the diferent components.
4970// input:      The output G of the grobcov (in generic representation, which is the default option)
4971//                The ideal F defining the locus problem (G is the grobcov of F and has been
4972//                already determined by locus.
4973//       Options: The algorithm allows the following options as pair of arguments:
4974//                "movdim", d  : by default movdim is 2 but it can be set to other values
4975//                    when locus is called by envelop then as default is uses d=dim @P
4976//                "version", v   :  There are two versions of the algorithm. ('version',1) is
4977//                 a full algorithm that always distinguishes correctly between 'Normal'
4978//                 and 'Special' components, whereas ('version',0) can decalre a component
4979//                 as 'Normal' being really 'Special', but is more effective. By default ('version',1)
4980//                 is used when the number of variables is less than 4 and 0 if not.
4981//                 The user can force to use one or other version, but it is not recommended.
4982//                 "system", ideal F: if the initial systrem is passed as an argument. This is actually not used.
4983//                 "comments", c: by default it is 0, but it can be set to 1.
4984//                 Usually locus problems have mover coordinates, variables and tracer coordinates.
4985//                 The mover coordinates are to be placed as the last variables, and by default,
4986//                 its number is equal to the number of parameters of tracer variables, but as option
4987//                 it can be set to other values.
4988// output:
4989//         list, the canonical P-representation of the Normal and Non-Normal locus:
4990//              The Normal locus has two kind of components: Normal and Special.
4991//              The Non-normal locus has two kind of components: Accumulation and Degenerate.
4992//              This routine is compemented by locus that calls it in order to eliminate problems
4993//              with degenerate points of the mover.
4994//         The output components are given as
4995//              ((p1,(p11,..p1s_1),type_1,level_1),..,(pk,(pk1,..pks_k),type_k,level_k)
4996//         The components are given in canonical P-representation of the subset.
4997//              If all levels of a class of locus are 1, then the set is locally closed. Otherwise the level
4998//              gives the depth of the component.
4999static proc locus2(list G, ideal F, list #)
5000{
5001 int st=timer;
5002 list Snor; list Snonor;
5003 int d; int i; int j;
5004 def RR=basering;
5005 def Rx=ringlist(RR);
5006 def RP=ring(Rx[1]);
5007 int tax=1;
5008 list DD=#;
5009 list GG=G;
5010 int n=size(Rx[1][2]);
5011   for(i=1;i<=(size(DD) div 2);i++)
5012  {
5013//    if(DD[2*i-1]=="vmov"){vmov=DD[2*i];}
5014//    if(DD[2*i-1]=="version"){version=DD[2*i];}
5015//    if(DD[2*i-1]=="comment"){comment=DD[2*i];}
5016//    if(DD[2*i-1]=="grobcov"){GG=DD[2*i];}
5017    if(DD[2*i-1]=="anti-image"){tax=DD[2*i];}
5018  }
5019  //string("T_tax=",tax);
5020 for(i=1;i<=size(GG);i++)
5021 {
5022   attrib(GG[i][1],"IsSB",1);
5023   GG[i][1]=std(GG[i][1]);
5024   d=dim(GG[i][1]);
5025   if(d==0)
5026   {
5027     for(j=1;j<=size(GG[i][3]);j++)
5028     {
5029       Snor[size(Snor)+1]=GG[i][3][j];
5030     }
5031   }
5032   else
5033   {
5034     if(d>0)
5035     {
5036       for(j=1;j<=size(GG[i][3]);j++)
5037       {
5038         Snonor[size(Snonor)+1]=GG[i][3][j];
5039       }
5040     }
5041   }
5042 }
5043 //"T_Snor="; Snor;
5044 //"T_Snonor="; Snonor;
5045 int tnor=size(Snor); int tnonor=size(Snonor);
5046 setring RP;
5047 list SnorP;
5048 list SnonorP;
5049 if(tnor)
5050 {
5051   SnorP=imap(RR,Snor);
5052   st=timer;
5053   SnorP=LCUnionN(SnorP);
5054 }
5055 if(tnonor)
5056 {
5057   SnonorP=imap(RR,Snonor);
5058   SnonorP=LCUnionN(SnonorP);
5059 }
5060 //"T_SnorP after LCUnion="; SnorP;
5061 //"T_SnonorP  after LCUnion="; SnonorP;
5062
5063 setring RR;
5064 ideal C;  list N;  list BAC; list AI;
5065 list NSC; list DAC;
5066 list L;
5067 ideal B;
5068 int k;
5069 int j0; int k0; int te;
5070 poly kkk=1;
5071 ideal AI0;
5072 int dimP;
5073
5074 if(tnor)
5075 {
5076   Snor=imap(RP,SnorP);
5077   for(i=1;i<=size(Snor);i++)
5078   {
5079     C=Snor[i][1];
5080     N=Snor[i][2];
5081     dimP=DimPar(C);
5082     AI=NS(F,G,C,N);
5083     //"T_AI="; AI;
5084     AI0=AI[2];
5085     if(size(AI)==3){AI[2]="normal"; AI[3]=ideal(0);}
5086     else
5087     {
5088     if(AI[1]>=dimP)
5089     {
5090       AI[2]="Normal";
5091       if(tax>0){AI[3]=AI0;}
5092     }
5093     else{ if(AI[1]<n-1){AI[2]="Special"; AI[3]=AI0;} }
5094     }
5095     Snor[i][size(Snor[i])+1]=AI;
5096   }
5097   for(i=1;i<=size(Snor);i++)
5098   {
5099     L[size(L)+1]=Snor[i];
5100   }
5101  }
5102 if(tnonor)
5103 {
5104   Snonor=imap(RP,SnonorP);
5105   for(i=1;i<=size(Snonor);i++)
5106   {
5107     DAC=dimComp(Snonor[i][1]);
5108     Snonor[i][size(Snonor[i])+1]=DAC;
5109   }
5110   for(i=1;i<=size(Snonor);i++)
5111   {
5112     L[size(L)+1]=Snonor[i];
5113   }
5114 }
5115  return(L);
5116}
5117
5118// Auxilliary algorithm of locus2.
5119//           The algorithm searches the basis corresponding to C, in the grobcov.
5120//           It reduces the basis modulo the component.
5121//           The result is the reduced basis BR.
5122//           for each hole of the component
5123//              it searches the segment where the hole is included
5124//              and select form its basis the polynomials
5125//              only dependent on the variables.
5126//              These polynomials are non-null in an open set of
5127//              the component, and are included in the list NoNul of non-null factors
5128// input: F: the ideal of the locus problem
5129//           G the grobcov of F
5130//           C the top of a component of normal points
5131//           N the holes of the component
5132// output: (d,tax,a)
5133//           where d is the dimension of the anti-image
5134//           a is the anti-image of the component and
5135//           tax is the taxonomy \"Normal\" if d is equal to the dimension of C
5136//           and \"Special\" if it is smaller.
5137//           When a normal point component has degree greater than 9, then the
5138//           taxonomy is not determined, and (n,'normal', 0) is returned as third
5139//           element of the component. (n is the dimension of the space).
5140static proc NS(ideal F,list G, ideal C, list N)
5141{
5142  // Initializing and defining rings
5143  int i; int j; int k; int te; int j0;int k0; int m;
5144  def RR=basering;
5145  def Rx=ringlist(RR);
5146  def Lx=Rx;
5147  def P=ring(Rx[1]);               // ring Q[bx]
5148  Lx[1]=0;
5149  def D=ring(Lx);                   // ring Q[bu]
5150  def PR0=P+D;
5151  def PRx=ringlist(PR0);
5152  PRx[3][2][1]="lp";
5153  def PR=ring(PRx);               // ring Q[bx,bu]  in lex order
5154  int n=size(Rx[1][2]);
5155  def nv=nvars(RR);              // number of variables
5156  int nm;                               // number of mover variables
5157  ideal vmov;                        // mover variables   (bw)
5158  if(nv>=n){nm=n;}
5159  else{nm=nv;}
5160  for(i=1;i<=nm;i++)
5161  {
5162    vmov[size(vmov)+1]=var(i+nv-nm);
5163  }
5164  int ddeg; int dp;
5165  list LK;
5166  ideal bu;                               // ideal of all variables   (u)
5167  for(i=1;i<=nv;i++){bu[i]=var(i);}
5168  ideal mv;                            // ideal of mover varibles
5169  for(i=1;i<=nv;i++){mv[size(mv)+1]=var(i);}
5170
5171   // Searching the basis associated to C
5172   j=2; te=1;
5173   while((te) and (j<=size(G)))
5174   {
5175      k=1;
5176      while((te) and (k<=size(G[j][3])))
5177      {
5178        if (equalideals(C,G[j][3][k][1])){j0=j; k0=k; te=0;}
5179        k++;
5180      }
5181      j++;
5182   }
5183   if(te==1){"ERROR";}
5184   def B=G[j0][2];
5185
5186
5187   // Searching the elements in Q[v_m]  on basis differents from B that are nul there
5188   // and cannot become 0 on the antiimage of B. They are placed on NoNul
5189   list NoNul;
5190   ideal BNoNul;
5191   ideal covertop;           // basis of the segment where a hole of C is the top
5192   int te1;
5193   for(i=1;i<=size(N);i++)
5194   {
5195     j=2; te=1;
5196     while(te and j<=size(G))
5197     {
5198       if(j!=j0)
5199       {
5200         k=1;
5201         while(te and k<=size(G[j][3]))
5202         {
5203           covertop=G[j][3][k][1];
5204           if(equalideals(covertop,N[i]))
5205           {
5206             te=0; te1=1; BNoNul=G[j][2];
5207            }
5208           else
5209           {
5210             if(redPbasis(covertop,N[i]))
5211             {
5212               te=0; te1=1; m=1;
5213               while( te1 and m<=size(G[j][3][k][2]) )
5214               {
5215                 if(equalideals(G[j][3][k][2][m] ,N[i] )==1){te1=0;}
5216                 m++;
5217               }
5218             }
5219             if(te1==1){ BNoNul=G[j][2];}
5220           }
5221           k++;
5222         }
5223
5224         if((te==0) and (te1==1))
5225         {
5226          // Selecting the elements independent of the parameters,
5227          // They will be non null on the segment
5228           for(m=1;m<=size(BNoNul);m++)
5229           {
5230             if(indepparameterspoly(BNoNul[m]))
5231             {
5232                NoNul[size(NoNul)+1]=BNoNul[m];
5233             }
5234           }
5235         }
5236       }
5237       j++;
5238    }
5239  }
5240
5241   // Adding F to B
5242   for(i=1;i<=size(F);i++)
5243   {
5244     B[size(B)+1]=F[i];
5245   }
5246
5247  def E=NoNul;
5248  poly kkk=1;
5249  if(size(E)==0){E[1]=kkk;}
5250
5251  // Avoiding computations that are too expensive for obtaining
5252  //   the anti-image of normal point components
5253  setring(P);
5254  def CP=imap(RR,C);
5255  ddeg=deg(CP);
5256  setring(RR);
5257  // if(n+nv>10 or ddeg>=10){LK=n,ideal(0),"normal"; return(LK);}
5258  if(ddeg>=10){LK=n,ideal(0),"normal"; return(LK);}
5259
5260  // Reducing  basis B modulo C  in the ring PR      lex(x,u)
5261  setring(PR);
5262  def buPR=imap(RR,bu);
5263  def EE=imap(RR,E);
5264  ideal BR;
5265  def BB=imap(RR,B);
5266  def CC=imap(RR,C);
5267  attrib(CC,"IsSB",1);
5268  CC=std(CC);
5269  for(i=1;i<=size(BB);i++)
5270  {
5271    BR[i]=reduce(BB[i],CC);
5272  }
5273
5274  // Computing the GB(B) inthe ring PR     lex(x,u)
5275  BR=std(BR);
5276  ideal BRP;
5277
5278 // Eliminating the polynomials in B containing variables v_t
5279  for(i=1;i<=size(BR);i++)
5280  {
5281    if(subset(variables(BR[i]),buPR )){BRP[size(BRP)+1]=BR[i];}
5282  }
5283  BR=BRP;
5284
5285  // Factoring and eliminating the factors in N
5286  list H;
5287  ideal BP;
5288  poly f;
5289  int tj;
5290  //ideal vv=imap(RR,bu);
5291  for(i=1;i<=size(BR);i++)
5292  {
5293    f=1;
5294    H=factorize(BR[i]);
5295    if((subset(variables(H[1][2]),buPR)) and (size(H[1]))==2){BP[size(BP)+1]=H[1][2];}
5296    else
5297    {
5298      for(j=1;j<=size(H[1]);j++)
5299      {
5300        tj=subset(H[1][j],EE);
5301        if((subset(variables(H[1][j]),buPR)) and (tj==0)){f=f*H[1][j];}
5302      }
5303      if(leadcoef(f)!=f){BP[size(BP)+1]=f;}
5304   }
5305  }
5306
5307  // Determining the GB basis of B in Q[u]
5308  BP=std(BP);
5309  // Determining the dimension of the anti-image
5310  //   in the ring D
5311  setring D;
5312  def KK=imap(PR,BP);
5313  KK=std(KK);
5314  ideal KKM;
5315  ideal vmovM=imap(RR,vmov);
5316
5317  // selecting the element in Q[w]
5318  for(i=1;i<=size(KK);i++)
5319  {
5320    if(subset(variables(KK[i]),vmovM))
5321    {
5322      KKM[size(KKM)+1]=KK[i];
5323    }
5324  }
5325
5326  // Determining the dimensions
5327  list AIM=dimM(KKM,nv,nm);
5328  //int d2=AIM[1];
5329  def AAIM=AIM[2];
5330  setring(RR);
5331  //def BBR=imap(D,KK);
5332  def LKK=imap(D,AIM);
5333  //LKK=d2,string(BBR);
5334  return(LKK);
5335}
5336
5337// Auxilliary algorithm of locus2.
5338//           The algorithm searches the basis corresponding to C, in the grobcov.
5339//           It reduces the basis modulo the component.
5340//           The result is the reduced basis BR.
5341//           for each hole of the component
5342//              it searches the segment where the hole is included
5343//              and select form its basis the polynomials
5344//              only dependent on the variables.
5345//              These polynomials are non-null in an open set of
5346//              the component, and are included in the list NoNul of non-null factors
5347// input: F: the ideal of the locus problem
5348//           G the grobcov of F
5349//           C the top of a component of normal points
5350//           N the holes of the component
5351// output: (d,tax,a)
5352//           where d is the dimension of the anti-image
5353//           a is the anti-image of the component and
5354//           tax is the taxonomy \"Normal\" if d is equal to the dimension of C
5355//           and \"Special\" if it is smaller.
5356static proc NS5(ideal F,list G, ideal C, list N)
5357{
5358  // Initializing and defining rings
5359  int i; int j; int k; int te; int j0;int k0; int m;
5360  def RR=basering;
5361  def Rx=ringlist(RR);
5362  def Lx=Rx;
5363  def P=ring(Rx[1]);
5364  Lx[1]=0;
5365  def D=ring(Lx);
5366  def RP=D+P;
5367  def PR0=P+D;
5368  def PRx=ringlist(PR0);
5369  PRx[3][2][1]="lp";
5370  def PR=ring(PRx);
5371  int n=size(Rx[1][2]);                                     // dimension of the tracer space
5372  def nv=nvars(RR);                                        // number of variables
5373  ideal v; for(i=1;i<=nv;i++){v[i]=var(i);}        // variables
5374  int nm;                                                        // number of mover variables
5375  ideal vmov;                                                  // mover variables
5376  if(nv>=n){nm=n;}
5377  else{nm=nv;}
5378  for(i=1;i<=nm;i++)
5379  {
5380    vmov[size(vmov)+1]=var(i+nv-nm);
5381  }
5382
5383  // Searching the basis associated to C
5384   j=2; te=1;
5385   while((te) and (j<=size(G)))
5386   {
5387      k=1;
5388      while((te) and (k<=size(G[j][3])))
5389      {
5390        if (equalideals(C,G[j][3][k][1])){j0=j; k0=k; te=0;}
5391        k++;
5392      }
5393      j++;
5394   }
5395   if(te==1){"ERROR";}
5396   def B=G[j0][2];     // basis associated to C
5397   //"T_B="; B;
5398
5399  // Searching the elements in Q[vmov]  on bases differents from B that are nul there
5400  // and cannot become 0 on the antiimage of C. They are placed on NoNul
5401  list NoNul;          // elements in Q[vmov]  on bases differents from B
5402  ideal BNoNul;
5403  ideal covertop;   // basis of the segment whose top is a hole of our segment
5404  int te1;
5405  for(i=1;i<=size(N);i++)
5406  {
5407    j=2; te=1;
5408    while(te and j<=size(G))
5409    {
5410      if(j!=j0)
5411      {
5412        k=1;
5413        while(te and k<=size(G[j][3]))
5414        {
5415          covertop=G[j][3][k][1];
5416          if(equalideals(covertop,N[i]))
5417          {
5418            te=0; te1=1; BNoNul=G[j][2];
5419          }
5420          else
5421          {
5422            if(redPbasis(covertop,N[i]))
5423            {
5424              te=0; te1=1; m=1;
5425              while( te1 and m<=size(G[j][3][k][2]) )
5426              {
5427                if(equalideals(G[j][3][k][2][m] ,N[i] )==1){te1=0;}
5428                m++;
5429              }
5430            }
5431            if(te1==1){ BNoNul=G[j][2];}
5432          }
5433          k++;
5434        }
5435
5436        if((te==0) and (te1==1))
5437        {
5438          // Selecting the elements independent of the parameters,
5439          // They will be non null on the segment
5440          for(m=1;m<=size(BNoNul);m++)
5441          {
5442            if(indepparameterspoly(BNoNul[m]))
5443            {
5444               NoNul[size(NoNul)+1]=BNoNul[m];
5445            }
5446         }
5447       }
5448     }
5449     j++;
5450   }
5451 }
5452  def NN=NoNul;
5453  poly kkk=1;
5454  if(size(NN)==0){NN[1]=kkk;}
5455  //"T_NN="; NN;
5456
5457 // Union of F and B
5458 for(i=1;i<=size(F);i++)
5459 {
5460   B[size(B)+1]=F[i];
5461 }
5462 //"T_B+F="; B;
5463
5464  // Reducing  basis B modulo C  in the ring PR
5465  setring(PR);
5466  def vv=imap(RR,v);
5467  ideal BBR;
5468  def BB=imap(RR,B);
5469  def CC=imap(RR,C);
5470  attrib(CC,"IsSB",1);
5471  CC=std(CC);
5472  for(i=1;i<=size(BB);i++)
5473  {
5474    BBR[i]=reduce(BB[i],CC);
5475  }
5476  //"T_BBR="; BBR;
5477
5478  // Selecting the elements of the ideal in Q[v]
5479  // setring RP;
5480  ideal Bv;
5481  // def Bv=imap(PR,BBR);
5482  //ideal vvv=imap(RR,v);
5483  // Bv=std(Bv);
5484  ideal BR;
5485  for(i=1;i<=size(BBR);i++)
5486  {
5487    if(subset(variables(BBR[i]),vv)){BR[size(BR)+1]=BBR[i];}
5488  }
5489  //"T_BR="; BR;
5490  // setring PR;
5491  // def BR=imap(RP,BRv);
5492  def NNN=imap(RR,NN);
5493
5494  // Factoring and eliminating the factors in N
5495  list H;
5496  ideal BP;
5497  poly f;
5498  int tj;
5499  // ideal vv=imap(RR,v);
5500  for(i=1;i<=size(BR);i++)
5501  {
5502    f=1;
5503    H=factorize(BR[i]);
5504    if((subset(variables(H[1][2]),vv)) and (size(H[1]))==2){BP[size(BP)+1]=H[1][2];}
5505    else
5506    {
5507      for(j=1;j<=size(H[1]);j++)
5508      {
5509        tj=subset(H[1][j],NNN);
5510        if((subset(variables(H[1][j]),vv)) and (tj==0)){f=f*H[1][j];}
5511      }
5512      if(leadcoef(f)!=f){BP[size(BP)+1]=f;}
5513   }
5514  }
5515  //"T_BP="; BP;
5516
5517  //  Obtaining Am, the anti-image of C on vmov
5518  setring D;
5519  ideal A=imap(PR,BP);
5520  ideal vm=imap(RR,vmov);
5521  ideal Am;
5522  for(i=1;i<=size(A);i++)
5523  {
5524    if (subset(variables(A[i]),vm)){Am[size(Am)+1]=A[i];}
5525  }
5526  //"T_Am="; Am;
5527
5528
5529  list AIM=dimM(Am,nv,nm);
5530  setring(RR);
5531  def LAM=imap(D,AIM);
5532  return(LAM);
5533}
5534
5535static proc dimM(ideal KKM, int nv, int nm)
5536{
5537  def RR=basering;
5538  list L;
5539  int i;
5540  def Rx=ringlist(RR);
5541  for(i=1;i<=nm;i++)
5542  {
5543    L[i]=Rx[2][nv-nm+i];
5544  }
5545  Rx[2]=L;
5546  intvec iv;
5547  for(i=1;i<=nm;i++){iv[i]=1;}
5548  Rx[3][1][2]=iv;
5549   def DM=ring(Rx);
5550  setring(DM);
5551  ideal KKMD=imap(RR,KKM);
5552  attrib(KKMD,"IsSB",1);
5553  KKMD=std(KKMD);
5554  int d=dim(KKMD);
5555  setring(RR);
5556  def KAIM=imap(DM,KKMD);
5557  list LAIM=d,KAIM;
5558  return(LAIM);
5559}
5560
5561// Procedure using only standard GB in lex(x,a) order to obtain the
5562//    component of the locus.
5563//    It is not so fine as locus and cannot evaluate the taxonomy, but
5564//    it is much simpler and efficient.
5565// input: ideal S for determining the locus
5566// output: the irreducible components of the locus
5567//    Data must be given in Q[a][x]
5568proc stdlocus(ideal F)
5569"USAGE: stdlocus(ideal F)
5570       The input ideal must be the set equations defining the locus.
5571       Calling sequence: locus(F);
5572       The input ring must be a parametrical ideal in Q[x][u],
5573       (x=tracer variables, u=remaining variables).
5574       (Inverts the concept of parameters and variables of the ring).
5575       Special routine for determining the locus of points of  a geometrical construction.
5576       Given a parametric ideal F representing the system determining the locus of points (x)
5577       which verify certain properties, the call to stdlocus(F)
5578       determines the different irreducible components of the locus.
5579       This is a simple routine, using only standard Groebner basis computation,
5580       elimination and prime decomposition instead of using grobcov.
5581       It does not determine the taxonomy, nor the holes of the components
5582RETURN:The output is a list of the tops of the components [C_1, .. , C_n] of the locus.
5583       Each component is given its top ideal p_i.
5584NOTE: The input must be the locus system.
5585KEYWORDS: geometrical locus; locus
5586EXAMPLE: stdlocus; shows an example"
5587{
5588  int i; int te;
5589  def RR=basering;
5590  list Rx=ringlist(RR);
5591  int n=npars(RR);  // size(Rx[1][2]);
5592  int nv=nvars(RR);
5593  ideal vpar;
5594  ideal vvar;
5595  //"T_n="; n;
5596   //"T_nv="; nv;
5597  for(i=1;i<=n;i++){vpar[size(vpar)+1]=par(i);}
5598  for(i=1;i<=nv;i++){vvar[size(vvar)+1]=var(i);}
5599  //string("T_vpar = ", vpar," vvar = ",vvar);
5600  def P=ring(Rx[1]);
5601  Rx[1]=0;
5602  def D=ring(Rx);
5603  def RP=D+P;
5604  list Lx=ringlist(RP);
5605  setring(RP);
5606  def FF=imap(RR,F);
5607  def vvpar=imap(RR,vpar);
5608  //string("T_vvpar = ",vvpar);
5609  ideal B=std(FF);
5610  //"T_B="; B;
5611  ideal Bel;
5612  //"T_vvpar="; vvpar;
5613  for(i=1;i<=size(B);i++)
5614  {
5615    if(subset(variables(B[i]),vvpar)) {Bel[size(Bel)+1]=B[i];}
5616  }
5617  //"T_Bel="; Bel;
5618  list H;
5619  list FH;
5620  H=minAssGTZ(Bel);
5621  int t1;
5622  if(size(H)==0){t1=1;}
5623  setring RR;
5624  list empt;
5625  if(t1==1){return(empt);}
5626  else
5627  {
5628    def HH=imap(RP,H);
5629    return(HH);
5630  }
5631}
5632example
5633{
5634  "EXAMPLE:"; echo = 2;
5635  if(defined(R)){kill R;}
5636  ring R=(0,x,y),(x1,y1),dp;
5637  short=0;
5638
5639  // Concoid
5640  ideal S96=x1 ^2+y1 ^2-4,(x-2)*x1 -x*y1 +2*x,(x-x1 )^2+(y-y1 )^2-1;
5641
5642  stdlocus(S96);
5643}
5644
5645//  locus(F):  Special routine for determining the locus of points
5646//                 of  geometrical constructions.
5647//  input:      The ideal of the locus equations
5648//  output:
5649//          The output components are given as
5650//               ((p1,(p11,..p1s_1),tax_1),..,(pk,(pk1,..pks_k),tax_k)
5651//               Elements 1 and 2 represent the P-canonical form of the component.
5652//               The third element tax is:
5653//                 for normal point components, tax=(d,taxonomy,anti-image)
5654//                    being d=dimension of the anti-image on the mover varaibles,
5655//                           taxonomy='Normal'  or  'Special', and
5656//                           anti-image=ideal of the anti-image over the mover variables
5657//                                which are taken to be the last n variables.
5658//                 for non-normal point components, tax =(d,taxonomy)
5659//                    being d=dimension of the component  and
5660//                           taxonomy='Accumulation' or 'Degenerate'.
5661//          The components are given in canonical P-representation of the subset.         l
5662//          The normal locus has two kind of components: Normal and Special.
5663//            Normal component:
5664//            - each point in the component has 0-dimensional anti-image.
5665//            - the anti-image in the mover coordinates is equal to the dimension of the component
5666//            Special component:
5667//            - each point in the component has 0-dimensional anti-image.
5668//            - the anti-image in the mover coordinates is smaller than the dimension of the component
5669//          The non-normal locus has two kind of components: Accumulation and Degenerate.
5670//           Accumulation points:
5671//             - each point in the component has anti-image of dimension greater than 0.
5672//             - the component has dimension less than n-1.
5673//           Degenerate components:
5674//             - each point in the component has anti-image of dimension greater than 0.
5675//             - the component has dimension n-1.
5676//           When a normal point component has degree greater than 9, then the
5677//           taxonomy is not determined, and (n,'normal', 0) is returned as third
5678//           element of the component. (n is the dimension of the space).
5679
5680proc locus(ideal F, list #)
5681"USAGE:  locus(ideal F[,options])
5682        Special routine for determining the locus of points of
5683        a geometrical construction.
5684INPUT:  The input ideal must be the set equations
5685        defining the locus. Calling sequence:
5686        locus(F[,options]);
5687        The input ring must be a parametrical ideal
5688        in Q[x1,..,xn][u1,..,um],
5689        (x=tracer variables, u=remaining auxiliary variables).
5690        The number of tracer variables is n=dim(space).
5691        The n last u-variables are considered as mover variables.
5692        (Inverts the concept of parameters and variables of
5693        the ring).
5694OPTIONS:An option is a pair of arguments: string, integer.
5695        To modify the default options, pairs of arguments
5696        -option name, value- of valid options must be added to
5697        the call.The algorithm allows the following options as
5698        pair of arguments:
5699        \"grobcov\", list(the previous computed grobcov(F)).
5700        It is to be used when we modify externally the grobcov,
5701        for example to obtain the real grobcov.
5702        \"anti-image\",0  if the anti-image is not to be
5703        shown for \"Normal\" components.
5704        \"comments\", c: by default it is 0, but it can be set
5705        to 1.
5706RETURN: The output is a list of the components:
5707        ((p1,(p11,..p1s_1),tax_1),..,(pk,(pk1,..pks_k),tax_k)
5708        Elements 1 and 2 of a component represent the
5709        P-canonical form of the component.
5710        The third element tax is:
5711          for normal point components,
5712            tax=(d,taxonomy,anti-image) being
5713             d=dimension of the anti-image on the mover varaibles,
5714             taxonomy=\"Normal\"  or  \"Special\" and
5715             anti-image=ideal of the anti-image over the mover
5716               variables which are taken to be the n last u-variables.
5717          for non-normal point components,
5718            tax =(d,taxonomy) being
5719             d=dimension of the component  and
5720             taxonomy=\"Accumulation\" or \"Degenerate\".
5721        The components are given in canonical P-representation.
5722        The normal locus has two kind of components:
5723          Normal and Special.
5724          Normal component:
5725           - each point in the component has 0-dimensional
5726              anti-image.
5727           - the anti-image in the mover coordinates is equal
5728              to the dimension of the component
5729          Special component:
5730           - each point in the component has 0-dimensional
5731              anti-image.
5732           - the anti-image in the mover coordinates is smaller
5733              than the dimension of the component
5734        The non-normal locus has two kind of components:
5735          Accumulation and Degenerate.
5736          Accumulation component:
5737           - each point in the component has anti-image of
5738              dimension greater than 0.
5739           - the component has dimension less than n-1.
5740         Degenerate components:
5741           - each point in the component has anti-image
5742              of dimension greater than 0.
5743           - the component has dimension n-1.
5744       When a normal point component has degree greater than 9,
5745         then the taxonomy is not determined, and (n,'normal', 0)
5746         is returned as third element of the component. (n is the
5747         dimension of the space).
5748
5749       Given a parametric ideal F representing the system F
5750       determining the locus of points (x) which verify certain
5751       properties, the call to locus(F) determines the different
5752       classes of locus components, following the taxonomy
5753       defined in the book:
5754       A. Montes. \"The Groebner Cover\" (Discussing Parametric
5755       Polynomial Systems) not yet published
5756       A previous paper gives particular definitions
5757       for loci in 2d.
5758       M. Abanades, F. Botana, A. Montes, T. Recio,
5759       \"An Algebraic Taxonomy for Locus Computation
5760       in Dynamic Geometry\",
5761       Computer-Aided Design 56 (2014) 22-33.
5762NOTE: The input must be the locus system.
5763KEYWORDS: geometrical locus; locus; dynamic geometry
5764EXAMPLE: locus; shows an example"
5765{
5766  int tes=0; int i;  int m; int mm; int n;
5767  def RR=basering;
5768  list GG;
5769  //Options
5770  list DD=#;
5771  ideal vmov;
5772  int moverdim=size(ringlist(RR)[1][2]);
5773  int nv=nvars(RR);
5774  if(moverdim>nv){moverdim=nv;}
5775  for(i=1;i<=moverdim;i++){vmov[size(vmov)+1]=var(i+nv-moverdim);}
5776  // for(i=1;i<=nv;i++){vmov[size(vmov)+1]=var(i);}
5777  int version=2;
5778  // if(nv<4){version=2;}
5779  int comment=0;
5780  int tax=1;
5781  ideal Fm;
5782  for(i=1;i<=(size(DD) div 2);i++)
5783  {
5784    if(DD[2*i-1]=="vmov"){vmov=DD[2*i];}
5785    if(DD[2*i-1]=="version"){version=DD[2*i];}
5786    if(DD[2*i-1]=="comment"){comment=DD[2*i];}
5787    if(DD[2*i-1]=="grobcov"){GG=DD[2*i];}
5788    if(DD[2*i-1]=="anti-image"){tax=DD[2*i];}
5789  }
5790  if(size(GG)==0){GG=grobcov(F);}
5791  int j; int k; int te;
5792  def B0=GG[1][2];
5793  def H0=GG[1][3][1][1];
5794  list nGP;
5795  if (equalideals(B0,ideal(1)) )
5796  {
5797    if(version==2){return(locus2(GG,F,DD));}
5798    else{return(locus0(GG,DD));}
5799  }
5800  else
5801  {
5802    n=nvars(R);
5803    ideal vB;
5804    ideal N;
5805    for(i=1;i<=size(B0);i++)
5806    {
5807      if(subset(variables(B0[i]),vmov)){N[size(N)+1]=B0[i];}
5808    }
5809    attrib(N,"IsSB",1);
5810    N=std(N);
5811   if((size(N))>=2)
5812    {
5813       //def dN=dim(N);
5814       te=indepparameters(N);
5815       if(te)
5816       {
5817         string("locus detected that the mover must avoid points (",N,") in order to obtain the correct locus");" ";
5818         //eliminates segments of GG where N is contained in the basis
5819         nGP[1]=GG[1];
5820         nGP[1][1]=ideal(1);
5821         nGP[1][2]=ideal(1);
5822         def GP=GG;
5823         ideal BP;
5824         ideal fBP;
5825         for(j=2;j<=size(GP);j++)
5826         {
5827           te=1; k=1;
5828           BP=GP[j][2];
5829          // eliminating multiple factors in the polynomials of BP
5830           for(mm=1;mm<=size(BP);mm++)
5831           {
5832             fBP=factorize(BP[mm],1);
5833             BP[mm]=1;
5834             for(m=1;m<=size(fBP);m++)
5835             {
5836               BP[mm]=BP[mm]*fBP[m];
5837             }
5838           }
5839           // end eliminating multiple factors
5840           while((te==1) and (k<=size(N)))
5841           {
5842             if(pdivi(N[k],BP)[1]!=0){te=0;}
5843             k++;
5844           }
5845           if(te==0){nGP[size(nGP)+1]=GP[j];}
5846         }
5847       }
5848    }
5849    else
5850    {
5851      nGP=GG;
5852      " ";string("Unavoidable ",moverdim,"-dimensional locus");
5853      //string("Try option 'vmov',ideal(of mover variables) to avoid some point of the mover");
5854      //" ";"Elements of the basis of the generic segment in mover variables=";  N;" ";
5855      list L; return(L);
5856    }
5857  }
5858  if(comment>0){"Input for locus2 GB="; nGP; "input for locus  F="; F;}
5859  if(version==2)
5860  {
5861    //"T_nGP="; nGP;
5862    def LL=locus2(nGP,F,DD);
5863  }
5864  else{def LL=locus0(nGP,DD);}
5865  // kill @RP; kill @P; kill @R;
5866  return(LL);
5867}
5868example
5869{
5870  "EXAMPLE:"; echo = 2;
5871  if(defined(R)){kill R;}
5872  ring R=(0,x,y),(x1,y1),dp;
5873  short=0;
5874
5875  // Concoid
5876  ideal S96=x1 ^2+y1 ^2-4,(x-2)*x1 -x*y1 +2*x,(x-x1 )^2+(y-y1 )^2-1;
5877
5878  locus(S96);
5879}
5880
5881//  locusdg(G):  Special routine for determining the locus of points
5882//                 of  geometrical constructions in Dynamic Geometry.
5883//                 It is to be applied to the output of locus and selects
5884//                 as 'Relevant' the 'Normal' and the 'Accumulation'
5885//                 components.
5886//  input:      The output of locus(S);
5887//  output:
5888//          list, the canonical P-representation of the 'Relevant' components of the locus.
5889//          The output components are given as
5890//               ((p1,(p11,..p1s_1),type_1,level_1),..,(pk,(pk1,..pks_k),type_k,level_k)
5891//          The components are given in canonical P-representation of the subset.
5892//               If all levels of a class of locus are 1, then the set is locally closed. Otherwise the level
5893//               gives the depth of the component of the constructible set.
5894proc locusdg(list L)
5895"USAGE: locusdg(list L)
5896       Calling sequence:
5897       locusdg(locus(S)).
5898RETURN: The output is the list of the \"Relevant\" components of the
5899       locus in Dynamic Geometry [C1,..,C:m], where
5900       C_i= [p_i,[p_i1,..p_is_i], \"Relevant\", level_i]
5901       The \"Relevant\" components are \"Normal\" and
5902       \"Accumulation\" components of the locus. (See help
5903       for locus).
5904KEYWORDS: geometrical locus; locus; dynamic geometry
5905EXAMPLE: locusdg; shows an example"
5906{
5907  list LL;
5908  int i;
5909  for(i=1;i<=size(L);i++)
5910  {
5911    if(typeof(L[i][3][2])=="string")
5912    {
5913      if((L[i][3][2]=="Normal") or (L[i][3][2]=="Accumulation")){L[i][3][2]="Relevant"; LL[size(LL)+1]=L[i];}
5914    }
5915  }
5916  return(LL);
5917}
5918example
5919{
5920  "EXAMPLE:"; echo = 2;
5921  if(defined(R)){kill R;};
5922  ring R=(0,a,b),(x,y),dp;
5923  short=0;
5924  // Concoid
5925  ideal S96=x^2+y^2-4,(b-2)*x-a*y+2*a,(a-x)^2+(b-y)^2-1;
5926
5927  def L96=locus(S96);
5928  L96;
5929
5930  locusdg(L96);
5931}
5932
5933// locusto: Transforms the output of locus, locusdg, envelop
5934//             into a string that can be reed from different computational systems.
5935// input:
5936//     list L: The output of locus or locusdg or envelop.
5937// output:
5938//     string s: Converts the input into a string readable by other programs
5939proc locusto(list L)
5940"USAGE: locusto(list L);
5941       The argument must be the output of locus or locusdg or
5942       envelop. It transforms the output into a string in standard
5943       form readable in other languages, not only Singular
5944       (Geogebra).
5945RETURN: The locus in string standard form
5946NOTE: It can only be called after computing either
5947        - locus(F)                -> locusto( locus(F) )
5948        - locusdg(locus(F))  -> locusto( locusdg(locus(F)) )
5949        - envelop(F,C)         -> locusto( envelop(F,C) )
5950KEYWORDS: geometrical locus; locus; envelop
5951EXAMPLE:  locusto; shows an example"
5952{
5953  int i; int j; int k;
5954  string s="["; string sf="]"; string st=s+sf;
5955  if(size(L)==0){return(st);}
5956  ideal p;
5957  ideal q;
5958  for(i=1;i<=size(L);i++)
5959  {
5960    s=string(s,"[[");
5961    for (j=1;j<=size(L[i][1]);j++)
5962    {
5963      s=string(s,L[i][1][j],",");
5964    }
5965    s[size(s)]="]";
5966    s=string(s,",[");
5967    for(j=1;j<=size(L[i][2]);j++)
5968    {
5969      s=string(s,"[");
5970      for(k=1;k<=size(L[i][2][j]);k++)
5971      {
5972        s=string(s,L[i][2][j][k],",");
5973      }
5974      s[size(s)]="]";
5975      s=string(s,",");
5976    }
5977    s[size(s)]="]";
5978    s=string(s,"]");
5979    if(size(L[i])>=3)
5980    {
5981      s=string(s,",[");
5982      if(typeof(L[i][3])=="string")
5983      {
5984        s=string(s,string(L[i][3]),"]]");
5985      }
5986      else
5987      {
5988        for(k=1;k<=size(L[i][3]);k++)
5989        {
5990          s=string(s,"[",L[i][3][k],"],");
5991        }
5992        s[size(s)]="]";
5993        s=string(s,"]");
5994      }
5995    }
5996    if(size(L[i])>=4)
5997    {
5998      s[size(s)]=",";
5999      s=string(s,string(L[i][4]),"],");
6000    }
6001    s[size(s)]="]";
6002    s=string(s,",");
6003  }
6004  s[size(s)]="]";
6005  return(s);
6006}
6007example
6008{
6009  "EXAMPLE:"; echo = 2;
6010  if(defined(R)){kill R;}
6011  ring R=(0,x,y),(x1,y1),dp;
6012  short=0;
6013  ideal S=x1^2+y1^2-4,(y-2)*x1-x*y1+2*x,(x-x1)^2+(y-y1)^2-1;
6014  def L=locus(S);
6015  locusto(L);
6016  locusto(locusdg(L));
6017}
6018
6019// envelop
6020// Input:
6021//   poly F: the polynomial defining the family of hypersurfaces in ring R=0,(x_1,..,x_n),(u_1,..,u_m),lp;
6022//   ideal C=g1,..,g_{n-1}:  the set of constraints;
6023//   options.
6024// Output: the components of the envolvent;
6025proc envelop(poly F, ideal C, list #)
6026"USAGE: envelop(poly F,ideal C[,options]);
6027       poly F must represent the family of hyper-surfaces for
6028       which on want to compute its envelop. ideal C must be
6029       the ideal of restrictions on the variables defining the
6030       family, and should contain less polynomials than the
6031       number of variables. (x_1,..,x_n) are the variables of
6032       the hyper-surfaces of F, that are considered as
6033       parameters of the parametric ring. (u_1,..,u_m) are
6034       the parameteres of the hyper-surfaces, that are
6035       considered as variables of the parametric ring.
6036       Calling sequence:
6037       ring R=(0,x_1,..,x_n),(u_1,..,u_m),lp;
6038       poly F=F(x_1,..,x_n,u_1,..,u_m);
6039       ideal C=g_1(u_1,..u_m),..,g_s(u_1,..u_m);
6040       envelop(F,C[,options]);   where s<m.
6041RETURN: The output is a list of the components [C_1, .. , C_n]
6042       of the locus. Each component is given by
6043       Ci=[pi,[pi1,..pi_s_i],tax] where
6044       pi,[pi1,..pi_s_i] is the canonical P-representation of
6045       the component.
6046       Concerning tax: (see help for locus)
6047       For normal-point components is
6048         tax=[d,taxonomy,anti-image], being
6049         d=dimension of the anti-image
6050         taxonomy=\"Normal\" or \"Special\"
6051         anti-image=values of the mover corresponding
6052         to the component
6053       For non-normal-point components is
6054         tax=[d,taxonomy]
6055         d=dimension of the component
6056         taxonomy=\"Accumulation\" or \"Degenerate\".
6057OPTIONS: An option is a pair of arguments: string, integer.
6058       To modify the default options,
6059       pairs of arguments -option name, value- of valid options
6060       must be added to the call. The algorithm allows the
6061       following option as pair of arguments:
6062       \"comments\", c: by default it is 0, but it can be set to 1.
6063       \"anti-image\", a: by default a=1 and the anti-image is
6064       shown also for \"Normal\" components.
6065       For a=0, it is not shown.
6066NOTE: grobcov and locus are called internally.
6067       The basering R, must be of the form Q[x][u]
6068       (x=parameters, u=variables).
6069       This routine uses the generalized definition of envelop
6070       introduced in the book
6071       A. Montes. \"The Groebner Cover\" (Discussing Parametric
6072       Polynomial Systems) not yet published.
6073KEYWORDS: geometrical locus; locus; envelop
6074EXAMPLE:  envelop; shows an example"
6075{
6076  def RR=basering;
6077  int tes=0; int i;   int j;  int k; int m;
6078  int d;
6079  int dp;
6080  ideal BBB;
6081  //Options
6082  list DD=#;
6083
6084  list Rx=ringlist(RR);
6085  ideal vmov;
6086  int moverdim=size(Rx[1][2]);
6087  int nv=nvars(RR);
6088  if(moverdim>nv){moverdim=nv;}
6089  for(i=1;i<=moverdim;i++){vmov[size(vmov)+1]=var(i+nv-moverdim);}
6090  //for(i=1;i<=nv;i++)  {vmov[size(vmov)+1]=var(i);}
6091  int version=2;
6092  int comment=0;
6093  ideal Fm;
6094  int tax=1;
6095
6096// Old options:
6097//   ideal vmov;
6098//   int nv=nvars(R);
6099//   for(i=1;i<=nv;i++){vmov[size(vmov)+1]=var(i);}
6100//   int numpars=size(ringlist(R)[1][2]);
6101//   int version=0;
6102//   if(nv<4){version=1;}
6103//  int comment=0;
6104  int familyinfo;
6105//  ideal Fm;
6106  for(i=1;i<=(size(DD) div 2);i++)
6107  {
6108//     if(DD[2*i-1]=="vmov"){vmov=DD[2*i];}
6109//     if(DD[2*i-1]=="version"){version=DD[2*i];}
6110//     if(DD[2*i-1]=="comment"){comment=DD[2*i];}
6111//     if(DD[2*i-1]=="familyinfo"){familyinfo=DD[2*i];}
6112    if(DD[2*i-1]=="anti-image"){tax=DD[2*i];}
6113    if(DD[2*i-1]=="vmov"){vmov=DD[2*i];}
6114    if(DD[2*i-1]=="version"){version=2;DD[2*i]=2;}
6115    if(DD[2*i-1]=="comment"){comment=DD[2*i];}
6116    if(DD[2*i-1]=="familyinfo"){familyinfo=0;DD[2*i]=0;}
6117//    if(DD[2*i-1]=="anti-image"){tax=DD[2*i];}
6118  };
6119  // DD=list("vmov",vmov,"version",version,"comment",comment,"anti-image",tax);
6120  //"T_DD="; DD;
6121  int ng=size(C);
6122  ideal S=F;
6123  //"T_C="; C;
6124  for(i=1;i<=size(C);i++){S[size(S)+1]=C[i];}
6125  //"T_S="; S;
6126  int s=nv-ng;
6127  if(s>0)
6128  {
6129    matrix M[ng+1][ng+1];
6130    def cc=comb(nv,ng+1);
6131    //string("nv=",nv," ng=",ng," s=",s);
6132    //"T_cc="; cc;
6133    poly J;
6134    for(k=1;k<=size(cc);k++)
6135    {
6136      for(j=1;j<=ng+1;j++)
6137      {
6138        M[1,j]=diff(F,var(cc[k][j]));
6139      }
6140      for(i=1;i<=ng;i++)
6141      {
6142        for(j=1;j<=ng+1;j++)
6143        {
6144          M[i+1,j]=diff(C[i],var(cc[k][j]));
6145        }
6146      }
6147      J=det(M);
6148      S[size(S)+1]=J;
6149    }
6150 }
6151 if(comment>0){"System S before grobcov ="; S;}
6152  //def G=grobcov(S,DD);
6153  list HHH;
6154  def L=locus(S,DD);
6155  list GL;
6156  ideal fam; ideal env;
6157
6158  def P=ring(Rx[1]);
6159  Rx[1]=0;
6160  def D=ring(Rx);
6161  def RP=P+D;
6162  list LL;
6163  list NormalComp;
6164  ideal Gi;
6165  ideal BBBB;
6166  poly B0;
6167  return(L);
6168// From here up, this is no more used.
6169//   if(familyinfo==1)
6170//   {
6171//     for(i=1;i<=size(L);i++)
6172//     {
6173//       if(typeof(L[i][3])=="string")
6174//       {
6175//         if(L[i][3]=="Normal")
6176//         {
6177//           NormalComp[size(NormalComp)+1]=L[i][1];
6178//           Gi=S;
6179//           Gi[size(Gi)+1]=L[i][1][1];
6180//           //"T_grobcov(Gi)="; grobcov(Gi);
6181//           kill HHH; list HHH;
6182//           //"T_L[i]="; L[i];
6183//           //d=DimPar(L[i][1]);
6184//           if(defined(SL)){kill SL;}
6185//           def SL=C;
6186//           SL[size(SL)+1]=F;
6187//           for(j=1;j<=size(L[i][1]);j++)
6188//           {
6189//             SL[size(SL)+1]=L[i][1][j];
6190//           }
6191//           setring RP;
6192//           if(defined(BBBB)){kill BBBB;}
6193//           ideal BBBB;
6194//           if(defined(BB)){kill BB;}
6195//           def BB=imap(R,SL);
6196//           if(defined(B0)){kill B0;}
6197//           poly B0;
6198//           if(defined(LLL)){kill LLL;}
6199//           def LLL=imap(R,L);
6200//           //"T_BB="; BB;
6201//           BB=std(BB);
6202//            for(j=1;j<=size(BB);j++)
6203//            {
6204//              B0=reduce(BB[j],LLL[i][1]);
6205//              if(not(B0==0)){BBBB[size(BBBB)+1]=B0;}
6206//            }
6207//           setring RR;
6208//           BBB=imap(RP,BBBB);
6209//            L[i][5]=BBB;
6210//         }
6211//       }
6212//     }
6213//     LL[1]=L;
6214//     LL[2]=NormalComp;
6215//     list LLL; list LLLL;
6216//     int t;
6217//     for(k=1;k<=size(LL[2]);k++)
6218//     {
6219//       for(i=1;i<=size(G);i++)
6220//       {
6221//         j=1; t=0;
6222//         while(t==0 and j<=size(G[i][3]))
6223//         {
6224//           //"T_LL[2][k]="; LL[2][k];
6225//           //"T_G[i][3][j][1]="; G[i][3][j][1];
6226//           if(equalideals(LL[2][k],G[i][3][j][1]))
6227//           {
6228//             LLL[size(LLL)+1]=list(k,i,j);
6229//             t=1;
6230//           }
6231//           j++;
6232//         }
6233//       }
6234//     }
6235//     LL[3]=LLL;
6236//
6237//     for(k=1;k<=size(LLL);k++)
6238//     {
6239//       for(m=k+1;m<=size(LLL);m++)
6240//       {
6241//         for(i=1;i<=size(G[LLL[k][2]][3][LLL[k][3]][2]);i++)
6242//         {
6243//           for(j=1;j<=size(G[LLL[m][2]][3][LLL[m][3]][2]);j++)
6244//           {
6245//             //string("T_(G[",LLL[k][2],"][3][",LLL[k][3],"][2][",i,"])=");  G[LLL[k][2]][3][LLL[k][3]][2][i];
6246//             //string("T_(G[",LLL[m][2],"][3][",LLL[m][3],"][2][",j,"])=");  G[LLL[m][2]][3][LLL[m][3]][2][j];
6247//             if(equalideals( G[LLL[k][2]][3][LLL[k][3]][2][i] ,G[LLL[m][2]][3][LLL[m][3]][2][j]))
6248//             {
6249//               //"T_GGG="; LL[2][LLL[k][1]]; LL[2][LLL[m][1]]; G[LLL[k][2]][3][LLL[k][3]][2][i];
6250//               LLLL[size(LLLL)+1]=list(LL[2][LLL[k][1]],LL[2][LLL[m][1]], G[LLL[k][2]][3][LLL[k][3]][2][i]);
6251//             }
6252//           }
6253//         }
6254//       }
6255//     }
6256//     LL[3]=LLLL;
6257//   }
6258//   else{LL=L;}
6259//   return(LL);
6260}
6261example
6262{
6263  "EXAMPLE:"; echo = 2;
6264  // Steiner Deltoid
6265  // 1. Consider the circle x1^2+y1^2-1=0, and a mover point M(x1,y1) on it.
6266  // 2. Consider the triangle A(0,1), B(-1,0), C(1,0).
6267  // 3. Consider lines passing through M perpendicular to two sides of ABC triangle.
6268  // 4. Obtain the envelop of the lines above.
6269  if(defined(R)){kill R;}
6270  ring R=(0,x,y),(x1,y1,x2,y2),lp;
6271  short=0;
6272  ideal C=(x1)^2+(y1)^2-1,
6273               x2+y2-1,
6274               x2-y2-x1+y1;
6275  matrix M[3][3]=x,y,1,x2,y2,1,x1,0,1;
6276  poly F=det(M);
6277  // Curves Family F
6278  F;
6279  // Conditions C=
6280  C;
6281  envelop(F,C);
6282}
6283
6284proc AssocTanToEnv(poly F,ideal C, ideal E,list #)
6285"USAGE: AssocTanToEnv(poly F,ideal C,ideal E);
6286       poly F must be the family of hyper-surfaces whose
6287       envelope is analyzed. It must be defined in the ring
6288       R=Q[x_1.,,x_n][u_1,..,u_m],
6289       ideal C must be the ideal of restrictions
6290       in the variables u1,..um for defining the family.
6291       C must contain less  polynomials than m.
6292       ideal E must be a component of
6293       envelop(F,C), previously computed.
6294       (x_1,..,x_n) are the variables of the hypersurfaces
6295       of F, that are considered as parameters of the
6296       parametric ring. (u_1,..,u_m) are the parameteres
6297       of the hyper-surfaces, that are considered as variables
6298       of the parametric ring. Having computed an envelop
6299       component E of a family of hyper-surfaces F,
6300       with constraints C, it returns the parameter values
6301       of the associated tangent hyper-surface of the
6302       family passing at one point of the envelop component E.
6303       Calling sequence:  (s<m)
6304       ring R=(0,x_1,..,x_n),(u_1,..,u_m),lp;
6305       poly F=F(x_1,..,x_n,u_1,..,u_m);
6306       ideal C=g_1(u_1,..u_m),..,g_s(u_1,..u_m);
6307       poly E(x_1,..,x_n);
6308       AssocTanToEnv(F,C,E,[,options]);
6309RETURN: list [lpp,basis,segment]. The basis determines
6310       the associated tangent hyper-surface at a point of
6311       the envelop component E. The segment is given in Prep.
6312       See book
6313       A. Montes. \"The Groebner Cover\": (Discussing Parametric
6314       Polynomial Systems).
6315NOTE:  grobcov is called internally.
6316KEYWORDS: geometrical locus; locus; envelop; associated tangent
6317EXAMPLE:  AssocTanToEnv; shows an example"
6318{
6319  // def RR=basering;
6320  int tes=0; int i;   int j;  int k; int m;
6321  int d;
6322  int dp;
6323  ideal EE=E;
6324  int moreinfo=1;
6325  ideal BBB;
6326  //Options
6327  list DD=#;
6328  ideal vmov;
6329  int nv=nvars(R);
6330  for(i=1;i<=nv;i++){vmov[size(vmov)+1]=var(i);}
6331  int numpars=size(ringlist(R)[1][2]);
6332  int version=0;
6333  if(nv<4){version=1;}
6334  int comment=0;
6335  int familyinfo;
6336  ideal Fm;
6337  for(i=1;i<=(size(DD) div 2);i++)
6338  {
6339    if(DD[2*i-1]=="vmov"){vmov=DD[2*i];}
6340    if(DD[2*i-1]=="version"){version=DD[2*i];}
6341    if(DD[2*i-1]=="comment"){comment=DD[2*i];}
6342    if(DD[2*i-1]=="familyinfo"){familyinfo=DD[2*i];}
6343    if(DD[2*i-1]=="moreinfo"){moreinfo=DD[2*i];}
6344  };
6345  DD=list("vmov",vmov,"version",version,"comment",comment);
6346  int ng=size(C);
6347  ideal S=F;
6348  for(i=1;i<=size(C);i++){S[size(S)+1]=C[i];}
6349  int s=nv-ng;
6350  if(s>0)
6351  {
6352    matrix M[ng+1][ng+1];
6353    def cc=comb(nv,ng+1);
6354    poly J;
6355    for(k=1;k<=size(cc);k++)
6356    {
6357      for(j=1;j<=ng+1;j++)
6358      {
6359        M[1,j]=diff(F,var(cc[k][j]));
6360      }
6361      for(i=1;i<=ng;i++)
6362      {
6363        for(j=1;j<=ng+1;j++)
6364        {
6365          M[i+1,j]=diff(C[i],var(cc[k][j]));
6366        }
6367      }
6368      J=det(M);
6369      S[size(S)+1]=J;
6370    }
6371 }
6372 for(i=1;i<=size(EE);i++)
6373 {
6374   S[size(S)+1]=EE[i];
6375 }
6376 //if(comment>0){"System S before grobcov ="; S;}
6377  def G=grobcov(S,DD);
6378  //"T_G=";G;
6379  list GG;
6380  for(i=2;i<=size(G);i++)
6381  {
6382    GG[size(GG)+1]=G[i];
6383  }
6384  G=GG;
6385  //"T_G=";G;
6386  if(moreinfo>0){return(G);}
6387  else
6388  {
6389    int t=0;
6390    ideal H;
6391    i=1;
6392    while(t==0 and i<=size(G))
6393    {
6394      //string("T_G[",i,"][3][1][1][1]="); G[i][3][1][1][1];
6395      //string("T_EE="); EE;
6396      if(G[i][3][1][1][1]==EE)
6397      {
6398         t=1;
6399         H=G[i][2];
6400      }
6401      i++;
6402    }
6403    return(H);
6404  }
6405  return(G);
6406}
6407example
6408{
6409  "EXAMPLE:"; echo = 2;
6410  if(defined(R)){kill R;}
6411  ring R=(0,y0,x,y),(t),dp;
6412  short=0;
6413  poly F=(x-5*t)^2+y^2-3^2*t^2;
6414  F;
6415  ideal C;
6416  C;
6417  def Env=envelop(F,C);
6418  Env;
6419  // E is a component of the envelop:
6420  ideal E=Env[1][1];
6421  E;
6422  def A=AssocTanToEnv(F,C,E);
6423  A;
6424  // The basis of the parameter values of the associated
6425  // tangent component is
6426  A[1][2][1];
6427  // Thus t=(5/12)*y0 and the associated tangent component at (x0,y0) is
6428  subst(F,t,(5/12)*y0);
6429
6430// EXAMPLE
6431  if(defined(R)){kill R;}
6432  ring R=(0,x,y,z),(x1,y1,z1),dp;
6433  short=0;
6434  poly F=(x-x1)^2+(y-y1)^2+(z-z1)^2-1;
6435  ideal C=(x1)^2+(y1)^2-1;
6436  short=0;
6437  def Env=envelop(F,C); Env;
6438  def E=Env[1][1];
6439  AssocTanToEnv(F,C,E);
6440  def E1=Env[2][1];
6441  AssocTanToEnv(F,C,E1);
6442}
6443
6444proc FamElemsAtEnvCompPoints(poly F,ideal C, ideal E)
6445"USAGE: FamElemsAtEnvCompPoints(poly F,ideal C,ideal E);
6446       poly F must be the family of hyper-surfaces whose
6447       envelope is analyzed. It must be defined in the ring
6448       R=Q[x_1.,,x_n][u_1,..,u_m],
6449       ideal C must be the ideal of restrictions on the
6450       variables u1,..um.
6451       Must contain less polynomials than m.
6452       ideal E must be a component of
6453       envelop(F,C), previously computed.
6454       After computing the envelop of a family of
6455       hyper-surfaces F, with constraints C,
6456       Consider a component with top E. The call to
6457       FamElemsAtEnvCompPoints(F,C,E)
6458       returns the parameter values of the
6459       set of all hyper-surfaces of the family passing at
6460       one point of the envelop component E.
6461       Calling sequence:
6462       ring R=(0,x_1,..,x_n),(u_1,..,u_m),lp;
6463       poly F=F(x_1,..,x_n,u_1,..,u_m);
6464       ideal C=g_1(u_1,..u_m),..,g_s(u_1,..u_m);
6465       poly E(x_1,..,x_n);
6466       FamElemsAtEnvCompPoints(F,C,E[,options]);
6467RETURN: list [lpp,basis,segment]. The basis determines
6468       the parameter values of the of hyper-surfaces that
6469       pass at a fixed point of the envelop component E.
6470       The lpp determines the dimension of the set.
6471       The segment is the component and is given in Prep.
6472       Fixing the values of (x_1,..,x_n) inside E, the basis
6473       allows to detemine the values of the parameters
6474       (u_1,..u_m), of the hyper-surfaces passing at a point
6475       of E. See the book
6476       A. Montes. \"The Groebner Cover\" (Discussing
6477       Parametric Polynomial Systems).
6478NOTE: grobcov is called internally.
6479       The basering R, must be of the form Q[a][x]
6480       (a=parameters, x=variables).
6481KEYWORDS: geometrical locus; locus; envelop; associated tangent
6482EXAMPLE:  FamElemsAtEnvCompPoints; shows an example"
6483{
6484  int i;
6485  ideal S=C;
6486  S[size(S)+1]=F;
6487  for(i=1;i<=size(E);i++){S[size(S)+1]=E[i];}
6488  def G=grobcov(S);
6489  list GG;
6490  for(i=2; i<=size(G); i++)
6491  {
6492    GG[size(GG)+1]=G[i];
6493  }
6494  return(GG);
6495}
6496example
6497{
6498  "EXAMPLE:"; echo = 2;
6499  if(defined(R)){kill R;}
6500  ring R=(0,y0,x,y),(t),dp;
6501  short=0;
6502  poly F=(x-5*t)^2+y^2-3^2*t^2;
6503  F;
6504  ideal C;
6505  C;
6506
6507  def Env=envelop(F,C);
6508  Env;
6509
6510  // E is a component of the envelop:
6511  ideal E=Env[1][1];
6512  E;
6513  def A=AssocTanToEnv(F,C,E);
6514  A;
6515  // The basis of the parameter values of the associated
6516  //    tangent component is
6517  A[1][2][1];
6518  // Thus t=(5/12)*y0, and  the assocoated tangent family
6519  //    element at (x0,y0) is
6520  subst(F,t,(5/12)*y0);
6521
6522  FamElemsAtEnvCompPoints(F,C,E);
6523  // Thus (12*t^2-5*y0)^2=0 and the unique circle of the
6524  //   family passing at (x0,y0) in E is the associated
6525  //   tangent circle:
6526  subst(F,t,(5/12)*y0);
6527}
6528
6529// discrim
6530proc discrim(poly F0, poly x0)
6531"USAGE: discrim(f,x);
6532       poly f: the polynomial in Q[a][x] or Q[x] of degree 2 in x
6533       poly x: can be a variable or a parameter of the ring.
6534RETURN: the factorized discriminant of f wrt x for discussing
6535        its sign
6536KEYWORDS: second degree; solve
6537EXAMPLE:  discrim; shows an example"
6538{
6539  def RR=basering;
6540  def Rx=ringlist(RR);
6541  def P=ring(Rx[1]);
6542  Rx[1]=0;
6543  def D=ring(Rx);
6544  def RP=D+P;
6545  int i;
6546  int te;
6547  int d;  int dd;
6548  if(size(ringlist(RR)[1])>0)
6549  {
6550    te=1;
6551    // setglobalrings();
6552    setring RP;
6553    poly F=imap(RR,F0);
6554    poly X=imap(RR,x0);
6555  }
6556  else
6557  {poly F=F0; poly X=x0;}
6558  matrix M=coef(F,X);
6559  d=deg(M[1,1]);
6560  if(d>2){"Degree is higher than 2. No discriminant"; setring RR; return();}
6561    poly dis=(M[2,2])^2-4*M[2,1]*M[2,3];
6562    def disp=factorize(dis,0);
6563    if(te==0){return(disp);}
6564    else
6565    {
6566      setring RR;
6567      def disp0=imap(RP,disp);
6568      return(disp0);
6569    }
6570}
6571example
6572{
6573  "EXAMPLE:"; echo = 2;
6574  if(defined(R)){kill R;}
6575  ring R=(0,a,b,c),(x,y),dp;
6576  short=0;
6577  poly f=a*x^2*y+b*x*y+c*y;
6578  discrim(f,x);
6579}
6580
6581// AddLocus: auxilliary routine for locus0 that computes the components of the constructible:
6582// Input:  the list of locally closed sets to be added, each with its type as third argument
6583//     L=[ [LC[11],..,LC[1k_1],.., [LC[r1],..,LC[rk_r] ] where
6584//            LC[1]=[p1,[p11,..,p1k],typ]
6585// Output:  the list of components of the constructible union of L, with the type of the corresponding top
6586//               and the level of the constructible
6587//     L4= [[v1,p1,[p11,..,p1l],typ_1,level]_1 ,.. [vs,ps,[ps1,..,psl],typ_s,level_s]
6588static proc AddLocus(list L)
6589{
6590  list L1; int i; int j;  list L2; list L3;
6591  list l1; list l2;
6592  intvec v;
6593  for(i=1; i<=size(L); i++)
6594  {
6595    for(j=1;j<=size(L[i]);j++)
6596    {
6597      l1[1]=L[i][j][1];
6598      l1[2]=L[i][j][2];
6599      l2[1]=l1[1];
6600      if(size(L[i][j])>2){l2[3]=L[i][j][3];}
6601      v[1]=i; v[2]=j;
6602      l2[2]=v;
6603      L1[size(L1)+1]=l1;
6604      L2[size(L2)+1]=l2;
6605    }
6606  }
6607  L3=LocusConsLevels(L1);
6608  list L4; int level;
6609  ideal p1; ideal pp1; int t; int k; int k0; string typ; list l4;
6610  for(i=1;i<=size(L3);i++)
6611  {
6612    level=L3[i][1];
6613    for(j=1;j<=size(L3[i][2]);j++)
6614    {
6615      p1=L3[i][2][j][1];
6616      t=1; k=1;
6617      while((t==1) and (k<=size(L2)))
6618      {
6619        pp1=L2[k][1];
6620        if(equalideals(p1,pp1)){t=0; k0=k;}
6621        k++;
6622      }
6623      if(t==0)
6624      {
6625        v=L2[k0][2];
6626        l4[1]=v; l4[2]=p1; l4[3]=L3[i][2][j][2];  l4[5]=level;
6627        if(size(L2[k0])>2){l4[4]=L2[k0][3];}
6628        L4[size(L4)+1]=l4;
6629      }
6630      else{"ERROR p1 NOT FOUND";}
6631    }
6632  }
6633  return(L4);
6634}
6635
6636// Input L: list of components in P-rep to be added
6637//         [  [[p_1,[p_11,..,p_1,r1]],..[p_k,[p_k1,..,p_kr_k]]  ]
6638// Output:
6639//          list of lists of levels of the different locally closed sets of
6640//          the canonical P-rep of the constructible.
6641//          [  [level_1,[ [Comp_11,..Comp_1r_1] ] ], .. ,
6642//             [level_s,[ [Comp_s1,..Comp_sr_1] ]
6643//          ]
6644//          where level_i=i,   Comp_ij=[ p_i,[p_i1,..,p_it_i] ] is a prime component.
6645// LocusConsLevels: given a set of components of locally closed sets in P-representation, it builds the
6646//       canonical P-representation of the corresponding constructible set of its union,
6647//       including levels it they are.
6648static proc LocusConsLevels(list L)
6649{
6650  list Lc; list Sc;
6651  int i;
6652  for(i=1;i<=size(L);i++)
6653  {
6654    Sc=PtoCrep0(list(L[i]));
6655    Lc[size(Lc)+1]=Sc;
6656  }
6657  list S=ConsLevels(Lc);
6658  S=Levels(S);
6659  list Sout;
6660  list Lev;
6661  for(i=1;i<=size(S);i++)
6662  {
6663    Lev=list(S[i][1],Prep(S[i][2][1],S[i][2][2]));
6664    Sout[size(Sout)+1]=Lev;
6665  }
6666  return(Sout);
6667}
6668
6669// used in NS
6670// returns 0 if E does not reduce modulo N
6671// returns 1 if it reduces
6672static proc redPbasis(ideal E, ideal N)
6673{
6674  int i;
6675  def RR=basering;
6676  def Rx=ringlist(RR);
6677  def Lx=Rx;
6678  def P=ring(Rx[1]);
6679  setring P;
6680  def EP=imap(RR,E);
6681  def NP=imap(RR,N);
6682  NP=std(NP);
6683  list L;
6684  int red=1;
6685  i=1;
6686  while(red and (i<=size(EP)))
6687  {
6688    if(reduce(EP[i],NP,5)!=0){red=0;}
6689    i++;
6690  }
6691  setring RR;
6692  return(red);
6693}
6694
6695
6696//******************** End locus and envelop ******************************
6697
6698//********************* Begin WLemma **********************
6699
6700// input ideal F in @R
6701//          ideal a in @R but only depending on parameters
6702//          F is a generating ideal in V(a);
6703// output:  ideal b in @R but depending only on parameters
6704//              ideal G=GBasis(F) in V(a) \ V(b)
6705proc WLemma(ideal F,ideal a, list #)
6706"USAGE: WLemma(F,A[,options]);
6707       The first argument ideal F in Q[x_1,..,x_n][u_1,..,u_m];
6708       The second argument ideal A in Q[x_1,..,x_n].
6709       Calling sequence:
6710       ring R=(0,x_1,..,x_n),(u_1,..,u_m),lp;
6711       ideal  F=f_1(x_1,..,x_n,u_1,..,u_m),..,
6712           f_s(x_1,..,x_n,u_1,..,u_m);
6713       ideal A=g_1(u_1,..u_m),..,g_s(u_1,..u_m);
6714       list # : Options
6715       Calling sequence:
6716       WLemma(F,A[,options]);
6717
6718       Given the ideal F  and ideal A
6719       it returns the list (lpp,B,S)  were B is the
6720       reduced Groebner basis of the specialized F over
6721       the segment S, subset of V(A) with top A,
6722       determined by Wibmer's Lemma.
6723       S is determined in P-representation
6724       (or optionally in C-representation). The basis is
6725       given by I-regular functions.
6726OPTIONS: either (\"rep\", 0) or (\"rep\",1) the representation of
6727       the resulting segment, by default is
6728       0 =P-representation, (default) but can be set to
6729       1=C-representation.
6730RETURN: list of [lpp,B,S] =
6731       [leading power product, basis,segment],
6732       being B the reduced Groebner Basis given by
6733       I-regular functions in full representation, of
6734       the specialized ideal F on the segment S,
6735       subset of V(A) with top A.
6736       given in P- or C-representation.
6737       It is the result of Wibmer's Lemma. See
6738       A. Montes , M. Wibmer, \"Groebner Bases for
6739       Polynomial Systems with parameters\".
6740       JSC 45 (2010) 1391-1425.)
6741       or the book
6742       A. Montes. \"The Groebner Cover\" (Discussing
6743       Parametric Polynomial Systems).
6744
6745NOTE: The basering R, must be of the form Q[a][x]
6746      (a=parameters, x=variables).
6747KEYWORDS: Wibmer's Lemma
6748EXAMPLE:  WLemma; shows an example"
6749{
6750  list L=#;
6751  int i; int j;
6752  def RR=basering;
6753  def Rx=ringlist(RR);
6754  def P=ring(Rx[1]);
6755  Rx[1]=0;
6756  def D=ring(Rx);
6757  def RP=D+P;
6758  setring(RP);
6759  ideal FF=imap(RR,F);
6760  FF=std(FF);
6761  ideal AA=imap(RR,a);
6762  AA=std(AA);
6763  ideal FFa;
6764  poly r;
6765  for(i=1; i<=size(FF);i++)
6766  {
6767    r=reduce(FF[i],AA);
6768    if(r!=0){FFa[size(FFa)+1]=r;}
6769  }
6770  setring RR;
6771  ideal Fa=imap(RP,FFa);
6772  ideal AAA=imap(RP,AA);
6773  ideal lppFa;
6774  ideal lcFa;
6775  for(i=1;i<=size(Fa);i++)
6776  {
6777    lppFa[size(lppFa)+1]=leadmonom(Fa[i]);
6778    lcFa[size(lcFa)+1]=leadcoef(Fa[i]);
6779  }
6780  setring RP;
6781  ideal lccr=imap(RR,lppFa);
6782  lccr=std(lccr);
6783  setring RR;
6784  ideal lcc=imap(RP,lccr);
6785  list J; list Jx;
6786  ideal Jci;
6787  ideal Jxi;
6788  list B;
6789  for(i=1;i<=size(lcc);i++)
6790  {
6791    kill Jci; ideal Jci; kill Jxi; ideal Jxi;
6792    for(j=1;j<=size(Fa);j++)
6793    {
6794      if(lppFa[j]==lcc[i])
6795      {
6796        Jci[size(Jci)+1]=lcFa[j];
6797        Jxi[size(Jxi)+1]=Fa[j];
6798      }
6799    }
6800    J[size(J)+1]=Jci;
6801    B[size(B)+1]=Jxi;
6802  }
6803  setring P;
6804  list Jp=imap(RR,J);
6805  ideal JL=product(Jp);
6806  setring(RR);
6807  def JLA=imap(P,JL);
6808  list PR;
6809  if (size(L)>0)
6810  {
6811    if((L[1]=="rep") and (L[2]==1))
6812    {
6813      PR=Crep(AAA, JLA);
6814    }
6815    else
6816    {PR=Prep(AAA, JLA);}
6817  }
6818  else{PR=Prep(AAA, JLA);}
6819  return(list(lcc,B,PR));
6820}
6821example
6822{
6823  "EXAMPLE:"; echo = 2;
6824  if(defined(R)){kill R;}
6825  ring R=(0,a,b,c,d,e,f),(x,y),lp;
6826  ideal F=a*x^2+b*x*y+c*y^2,d*x^2+e*x*y+f*y^2;
6827  ideal A=a*e-b*d;
6828  WLemma(F,A);
6829  WLemma(F,A,"rep",1);
6830}
6831
6832//********************* End WLemma ************************
6833
6834// Not used
6835static proc redbasis(ideal B, ideal C)
6836{
6837  int i;
6838  def RR=basering;
6839  def Rx=ringlist(RR);
6840  def Lx=Rx;
6841  def P=ring(Rx[1]);
6842  Lx[1]=0;
6843  def D=ring(Lx);
6844  def RP=D+P;
6845  setring RP;
6846  ideal BB=imap(RR,B);
6847  ideal CC=imap(RR,C);
6848  attrib(CC,"IsSB",1);
6849  CC=std(CC);
6850  for(i=1;i<=size(BB);i++)
6851  {
6852    BB[i]=reduce(BB[i],CC);
6853  }
6854  setring(RR);
6855  def BBB=imap(RP,BB);
6856  return(BBB);
6857}
6858
6859
6860// not used
6861// Input: ideals E, N
6862// Output: the ideal N without the polynomials in E
6863//   Works in any kind of ideal
6864static proc idminusid(ideal E,ideal N)
6865{
6866  int i; int j;
6867  ideal h;
6868  int te=1;
6869  for(i=1; i<=size(N);i++)
6870  {
6871    te=1;
6872    for(j=1;j<=size(E);j++)
6873    {
6874      if(N[i]==E[j]){te=0;}
6875    }
6876    if(te==1){h[size(h)+1]=N[i];}
6877  }
6878  return(h);
6879}
6880
6881// not used
6882// eliminar els factors de cada polinomi de F que estiguin a N\ E
6883static proc simpB(ideal F,ideal E,ideal N)
6884{
6885  ideal FF;
6886  poly ff;
6887  int i; int j;
6888  ideal J=idminusid(E,N);
6889  //"T_J="; J;
6890  for(i=1;i<=size(F);i++)
6891  {
6892    for(j=1;j<=size(J);j++)
6893    {
6894      ff=elimfacsinP(F[i],J[j]);
6895    }
6896    FF[size(FF)+1]=ff;
6897  }
6898  return(FF);
6899}
6900
6901// used in simpB that is not used
6902static proc elimfacsinP(poly f,poly g)
6903{
6904  def RR=basering;
6905  def Rx=ringlist(RR);
6906  int i; int j;
6907  int n=size(Rx[1][2]);
6908  def Lx=Rx;
6909  Lx[1]=0;
6910  def D=ring(Lx);
6911  def P=ring(Rx[1]);
6912  def RP=D+P;
6913  setring P;
6914  ideal vp;
6915  for(i=1;i<=n;i++)
6916  {
6917    vp[size(vp)+1]=var(i);
6918  }
6919  setring RP;
6920  def gg=imap(RR,g);
6921  ideal vpr=imap(P,vp);
6922  poly ff=imap(RR,f);
6923  def L=factorize(ff);
6924  def L1=L[1];
6925  poly p=1;
6926  for(i=1;i<=size(L1);i++)
6927  {
6928    if(L1[i]==gg){;}
6929    else{p=p*L1[i];}
6930  }
6931  setring RR;
6932  def pp=imap(RP,p);
6933  return(pp);
6934}
6935
6936//****************************** Begin ADGT *************************
6937
6938// used in ADGT
6939// Given G=grobcov(F,"rep",1) to have the GC in C-representation,
6940// CompLev determines the levels of the constructible subset of the parameter space
6941//   for which there exist solutions of F
6942// To be called in Q[a][x]
6943static proc CompLev(list G)
6944{
6945  int i;
6946  list S;
6947  def RR=basering;
6948  def Rx=ringlist(RR);
6949  def P=ring(Rx[1]);
6950  setring(RR);
6951  for(i=1;i<=size(G);i++)     // select the segments with solutions
6952  {
6953    if(not(G[i][1][1][1]==1))
6954    {
6955      S[size(S)+1]=G[i][3];
6956    }
6957  }
6958  if(size(S)==0)
6959  {
6960    list L;
6961    L[1]=1;
6962  }
6963  else
6964  {
6965    setring P;
6966    def SP=imap(RR,S);
6967    list LP=ConsLevels(SP);   // construct the levels of the constructible
6968    setring RR;
6969    def L=imap(P,LP);
6970  }
6971  return(L);
6972}
6973
6974// Auxiliary rutine for intersecting ideal only in the parameters a
6975// when the ideals are defined in Q[a][x]
6976proc intersectpar(list S)
6977"USAGE: interectpar(list of ideals S)
6978    list S=ideal I1,...,ideal Ik;
6979RETURN: The intersection of the ideals I1 ...  Ik  in Q[x,a]
6980NOTE: The routine is called in Q[a][x],
6981    The ideals I1,..,Ik can be ideals depending only on [a] or on [x,a]
6982EXAMPLE: intersectpar shows an example"
6983{
6984  def RR=basering;
6985  def Rx=ringlist(RR);
6986  def P=ring(Rx[1]);
6987  Rx[1]=0;
6988  def D=ring(Rx);
6989  def RP=D+P;
6990  setring(RP);
6991  def SP=imap(RR,S);
6992  def EP=intersect(SP[1..size(SP)]);
6993  setring RR;
6994  def E=imap(RP,EP);
6995  return(E);
6996}
6997example
6998{
6999"EXAMPLE:"; echo = 2;
7000if(defined(R)){kill R;}
7001ring R=(0,x,y,z),(x1,y1,z1),lp;
7002ideal I1=x+y*z*x1;
7003ideal I2=x-y*z*y1;
7004ideal I3=x+y+z*z1;
7005list S=I1,I2,I3;
7006S;
7007intersectpar(S);
7008}
7009
7010proc ADGT(ideal H,ideal T,ideal H1,ideal T1,list #)
7011"USAGE: ADGT(ideal H, ideal T, ideal H1,ideal T1[,options]);
7012      H: ideal in Q[a][x] hypothesis
7013      T: ideal in Q[a][x] thesis
7014      H1: ideal in Q[a][x] negative hypothesis, only dependent on [a]
7015      T1: ideal in Q[a][x] negative thesis
7016           of the Proposition (H and not H1) => (T and not T1)
7017RETURN: The list  [[1,S1],[2,S2],..],
7018       S1, S2, .. represent the set of parameter values
7019       that must be verified as supplementary
7020       conditions for the Proposition to become a Theorem.
7021       They are given by default in Prep.
7022       If the proposition is generally true,
7023       (the proposition is already a theorem), then
7024       the generic segment of the internal grobcov
7025       called is also returned to provide information
7026       about the values of the variables determined
7027       for every value of the parameters.
7028       If the propsition is false for every values of the
7029       parameters, then the emply list is returned.
7030OPTIONS: An option is a pair of arguments: string,
7031       integer. To modify the default options, pairs
7032       of arguments -option name, value- of valid options
7033       must be added to the call.
7034       Option \"rep\",0-1: The default is (\"rep\",0)
7035       and then the segments are given in canonical
7036       P-representation.
7037       Option (\"rep\",1) represents the segments
7038       in canonical C-representation,
7039       Option \"gseg\",0-1: The default is \"gseg\",1
7040       and then when the proposition is generally true,
7041       ADGT outputs a second element which is the
7042       \"generic segment\" to provide supplementary information.
7043       With option \"gseg\",0 this is avoided.
7044NOTE:  The basering R, must be of the form Q[a][x],
7045       (a=parameters, x=variables), and
7046       should be defined previously. The ideals
7047       must be defined on R.
7048KEYWORDS: Automatic Deduction; Automatic Demonstration; Geometric Theorems
7049EXAMPLE:  ADGT shows an example"
7050{
7051  int i; int j;
7052  def RR=basering;
7053  def Rx=ringlist(RR);
7054  def P=ring(Rx[1]);
7055  Rx[1]=0;
7056  def D=ring(Rx);
7057  def RP=D+P;
7058  setring RR;
7059  list Lopt=#;
7060  int start=timer;
7061  // options
7062  int rep=0;
7063  int gseg=1;
7064  for(i=1;i<=size(Lopt) div 2;i++)
7065  {
7066    if(Lopt[2*i-1]=="rep"){rep=Lopt[2*i];}
7067    else{if(Lopt[2*i-1]=="gseg"){gseg=Lopt[2*i];}}
7068  }
7069  // begin proc
7070  if(equalideals(T1,ideal(1))) //nonnullT==0)
7071  {
7072    def F=H;
7073    for(i=1;i<=size(T);i++)
7074    {
7075      F[size(F)+1]=T[i];
7076    }
7077    list G2;
7078    if(not(equalideals(H1,ideal(1))))  //nonnullH==1)
7079    {
7080      G2=grobcov(F,"nonnull",H1,"rep",1);
7081    }
7082    else
7083    {
7084      G2=grobcov(F,"rep",1);
7085    }
7086  }
7087  else
7088  {
7089    def F=H;
7090    for(i=1;i<=size(T1);i++)
7091    {
7092      F[size(F)+1]=T1[i];
7093    }
7094    list G3=grobcov(F,"rep",1);
7095    def L0=CompLev(G3);
7096    setring P;
7097    def LP=imap(RR,L0);
7098    def H1P=imap(RR,H1);
7099    if(not(equalideals(H1P,ideal(1))))  //nonnullH==1)
7100    {
7101      i=1;
7102      while(i<=size(LP))
7103      {
7104        if(i mod 2==1)
7105        {
7106          LP[i]=intersect(LP[i],H1P);
7107        }
7108        i++;
7109      }
7110    }
7111    setring RR;
7112    L0=imap(P,LP);
7113    F=H;
7114    for(i=1;i<=size(T);i++)
7115    {
7116      F[size(F)+1]=T[i];
7117    }
7118    def G2=grobcov(F,"nonnull",L0[1],"rep",1);
7119    list G1;
7120    int m=size(L0);
7121    int r=m div 2;
7122    if(m mod 2==0){r=r-1;}
7123     for(i=1;i<=r;i++)
7124    {
7125      G1=grobcov(F,"null",L0[2*i],"nonnull",L0[2*i+1],"rep",1);
7126      for(j=1;j<=size(G1);j++)
7127      {
7128        if(not(equalideals(G1[j][1],ideal(1))))
7129        {
7130          G2[size(G2)+1]=G1[j];
7131        }
7132      }
7133    }
7134  }
7135  if(size(G2)==0)
7136  {
7137    list L;
7138    // L[1]=1;
7139  }
7140  else
7141  {
7142    list L=Levels(CompLev(G2));
7143    if(rep==0 and size(L)>0)
7144    {
7145      setring P;
7146      def LFP=imap(RR,L);
7147      // list LFP1=LFP;
7148      for(i=1;i<=size(LFP);i++)
7149      {
7150        LFP[i][2]=Prep(LFP[i][2][1],LFP[i][2][2]);
7151      }
7152      setring RR;
7153      L=imap(P,LFP);
7154    }
7155    if(equalideals(G2[1][3][1][1],0) and not(equalideals(G2[1][1],ideal(1))))
7156    {
7157      list GL=G2[1];
7158      list LL=GL[3];
7159      if(rep==0)
7160      {
7161        setring P;
7162        def LLP=imap(RR,LL);
7163        LLP=Prep(LLP[1],LLP[2]);
7164        setring RR;
7165        LL=imap(P,LLP);
7166        GL[3]=LL;
7167      }
7168      if(gseg==1)
7169      {
7170        L[size(L)+1]=list("Generic segment",GL);
7171      }
7172    }
7173  }
7174  return(L);
7175}
7176example
7177{
7178"EXAMPLE:"; echo = 2;
7179// Determine the supplementary conditions
7180// for the non-degenerate  triangle A(-1,0), B(1,0), C(x,y)
7181// to have an ortic non-degenerate isosceles triangle
7182
7183if(defined(R)){kill R;}
7184ring R=(0,x,y),(x2,y2,x1,y1),lp;
7185// Hypothesis H
7186ideal H=-y*x1+(x-1)*y1+y,
7187             (x-1)*(x1+1)+y*y1,
7188             -y*x2+(x+1)*y2-y,
7189             (x+1)*(x2-1)+y*y2;
7190// Thesis T
7191ideal T=(x1-x)^2+y1^2-(x2-x)^2-y2^2;
7192// Negative Hypothesis H1
7193ideal H1=y;
7194 // Negative Thesis T1
7195ideal T1=x*(y1-y2)-y*(x1-x2)+x1*y2-x2*y1;
7196// Complementary conditions for the
7197// Proposition (H and not H1) => (T and not T1)
7198// to be true
7199
7200ADGT(H,T,H1,T1);
7201//********************************************
7202
7203// Example of automatic demonstrations of a theorem
7204// The Nine Points Circle Theorem:
7205
7206if(defined(R1)){kill R1;}
7207ring R1=(0,x,y),(x1,y1,x2,y2,yh,a,b,r),dp;
7208short=0;
7209//Hypothesis H
7210ideal H=y*x1+y1-x*y1-y,
7211            (x-1)*(x1+1)+y*y1,
7212            -y*x2+y2+x*y2-y,
7213            (x+1)*(x2-1)+y*y2,
7214            (x1-a)^2+(y1-b)^2-r^2,
7215            (x2-a)^2+(y2-b)^2-r^2,
7216            (x-a)^2+b^2-r^2,
7217            -yh+x*y1-x1*yh+y1;
7218// Thesis T
7219ideal T=yh+x*y2-x2*yh-y2,
7220            (x-1-2*a)^2+(yh-2*b)^2-4*r^2,
7221            (x+1-2*a)^2+(yh-2*b)^2-4*r^2,
7222            4*(x-a)^2+(y+yh-2*b)^2-4*r^2,
7223            (x-1-2*a)^2+(y-2*b)^2-4*r^2,
7224            (x+1-2*a)^2+(y-2*b)^2-4*r^2,
7225            4*(x-a)^2+(yh+y-2*b)^2-4*r^2;
7226ADGT(H,T,y,1);
7227// Thus the theorem is true.
7228}
7229//****************************** End ADGT *************************
7230
7231//   Obsolete routine. No more used after the actual release.
7232//   setglobalrings();  Generates the global rings @R, @P and @RP that are respectively the rings Q[a][x], Q[a], Q[x,a].
7233//             It is called inside each of the fundamental routines of the library: grobcov, cgsdr, locus, locusdg and
7234//             killed before the output.
7235//             In the actual version, after the call of setglobalrings on Q[a][x], the public names of the defined ideals
7236//             generated by setglobalrings are Grobcov::@R, Grobcov::@P,  Grobcov::@RP.
7237//
7238//   proc setglobalrings()
7239//   "USAGE:   setglobalrings();
7240//             No arguments.
7241//             Can be called when a parametric ideal Q[a][x] is in use. (a=parameters, x=variables).
7242//   RETURN: After its call the rings Grobcov::@R=Q[a][x], Grobcov::@P=Q[a],  Grobcov::@RP=Q[x,a] are defined as
7243//             global variables. (a=parameters, x=variables).
7244//   NOTE: It is called internally by many basic routines of the library grobcov, cgsdr, extendGC, pdivi, pnormalf, locus,
7245//             locusdg, envelop, WLemma, and killed before the output. The user does not need to call it.
7246//             The basering R, must be of the form Q[a][x], (a=parameters, x=variables), and should be defined previously.
7247//   KEYWORDS: ring; rings
7248//   EXAMPLE:  setglobalrings; shows an example"
7249//   {
7250//     if (defined(@P))
7251//     {
7252//       kill @P; kill @R; kill @RP;
7253//     }
7254//     def RRR=basering;
7255//     def @R=basering;  // must be of the form Q[a][x], (a=parameters, x=variables)
7256//     def Rx=ringlist(RRR);
7257//     def @P=ring(Rx[1]);
7258//     list Lx;
7259//     Lx[1]=0;
7260//     Lx[2]=Rx[2]+Rx[1][2];
7261//     Lx[3]=Rx[1][3];
7262//     Lx[4]=Rx[1][4];
7263//     Rx[1]=0;
7264//     def D=ring(Rx);
7265//     def @RP=D+@P;
7266//     export(@R);      // global ring Q[a][x]
7267//     export(@P);      // global ring Q[a]
7268//     export(@RP);     // global ring Q[x,a] with product order
7269//     setring(RRR);
7270//   };
7271//   example
7272//   {
7273//     "EXAMPLE:"; echo = 2;
7274//     if(defined(R)){kill R;}
7275//     ring R=(0,a,b),(x,y,z),dp;
7276//     setglobalrings();
7277//
7278//     R;
7279//
7280//     Grobcov::@R;
7281//
7282//     Grobcov::@P;
7283//
7284//     Grobcov::@RP;
7285//
7286//     ringlist(Grobcov::@R);
7287//
7288//     ringlist(Grobcov::@P);
7289//
7290//    ringlist(Grobcov::@RP);
7291//   }
7292;
Note: See TracBrowser for help on using the repository browser.