source: git/Singular/LIB/deflation.lib @ 61fbaf

spielwiese
Last change on this file since 61fbaf was 20f2239, checked in by Hans Schoenemann <hannes@…>, 4 years ago
spelling p7
  • Property mode set to 100644
File size: 27.5 KB
Line 
1//////////////////////////////////////////////////////////////////////////////
2version="version deflation.lib 4.1.2.0 Feb_2019 "; // $Id$
3category="Numerical Analysis";
4info="
5LIBRARY:  deflation.lib  Various deflation methods
6AUTHOR:  Adrian Koch (kocha at rhrk.uni-kl.de)
7
8REFERENCES:
9 - Jonathan Hauenstein, Bernard Mourrain, Agnes Szanto; Certifying isolated singular
10     points and their multiplicity structure
11 - Jonathan Hauenstein, Charles Wampler; Isosingular Sets and Deflation; published in
12     Foundations of Computational Mathematics, Volume 13, Issue 3, 2013, on pages 371-403
13 - Anton Leykin, Jan Verschelde, Ailing Zhao; Newtons method with deflation for isolated
14     singularities of polynomial systems; published in Theoretical Computer Science,
15     Volume 359, 2006, on pages 111-122
16
17PROCEDURES:
18 deflateHMS(F,ro,co,[..]);  deflation algorithm by Hauenstein, Mourrain, and Szanto
19 deflateHW1(F,ro,co);       isosingular deflation: uses determinants - by Hauenstein and Wampler
20 deflateHW2(F,rk,[..]);     isosingular deflation: strong, intrinsic - by Hauenstein and Wampler
21 deflateLVZ(F,rk,[..]);     deflation algorithm by Leykin, Verschelde, and Zhao
22
23KEYWORDS: deflation
24";
25
26
27LIB "linalg.lib";
28LIB "primdec.lib";
29
30//////////////////////////////////////////////////////////////////////////////////////////
31//////////////////////////////////////////////////////////////////////////////////////////
32//////////////////////////////////////   Method C   //////////////////////////////////////
33//////////////////////////////////////////////////////////////////////////////////////////
34//////////////////////////////////////////////////////////////////////////////////////////
35
36static proc getLambda(matrix A, matrix B)
37{
38   //computes the composite matrix whose columns we use to augment the original
39   //polynomial system
40
41   matrix C=-adjoint(A)*B;
42   int c=ncols(C);
43   matrix L=transpose(C);
44   L=concat(L,diag(1,c));
45   return(transpose(L));
46}
47
48static proc process_choice_for_i(int a, int c)
49{
50   //a contains the choice, c is the maximum element of the set i = 1,...,c
51   //if a is -1, returns random value between 1 and c
52   //if a is  0, returns c
53   //if a  >  c, returns c
54   //if 1< a <c, returns a
55
56
57   if(a == -1)
58   {
59      return(random(1,c));
60   }
61
62   if(a == 0)
63   {
64      return(c);
65   }
66
67   if(a <= c)
68   {
69      if(a >= 1)
70      {
71         return(a);
72      }
73   }
74
75   if(a > c)
76   {
77      return(c);
78   }
79
80   ERROR("Input (to control the choice of which element of i to use) invalid." +
81   " Must be an integer >= -1");
82}
83
84static proc append_var_list(int nv, list RL, list VN)
85{
86   //nv the number of new variables, RL the ringlist, VN the new variable names and,
87   //possibly, the no brackets option
88
89   int nb;
90   if(VN[1] == "no parentheses")
91   {
92      nb=1;
93      VN=delete(VN,1);
94   }
95
96   int i;
97   list vl;
98
99   if(size(VN) < nv)
100   {
101      string st=VN[1];
102
103      if(nb == 0)
104      {
105         for(i=1; i<=nv; i++)
106         {
107            vl=vl+list(st+"("+string(i)+")");
108         }
109      }
110      if(nb == 1)
111      {
112         for(i=1; i<=nv; i++)
113         {
114            vl=vl+list(st+string(i));
115         }
116      }
117   }
118
119
120   if(size(VN) >= nv)
121   {
122      for(i=1; i<=nv; i++)
123      {
124         vl=vl+list(VN[i]);
125      }
126   }
127
128   RL[2]=RL[2]+vl;
129   return(RL);
130}
131
132static proc remove_constants(ideal H);
133{
134   //remove constants and scalar multiples from H
135   H=1,H;
136   H=simplify(H,2+4+8);
137   H=H[2..size(H)];
138   return(H);
139}
140
141static proc exhaust_options(ideal F, int a, matrix la, matrix J)
142{
143   int i;
144   int c=ncols(la);
145   matrix N[nrows(la)][1];
146   ideal H;
147   int sF=size(F);
148   for(i=1; i<=c; i++)
149   {
150      if(i == a)
151      {
152         //we already checked that one
153         i++;
154         continue;
155      }
156      N=submat(la,1..nrows(la),i);
157      H=ideal(J*N);
158      H=remove_constants(H);
159      F=F,H;
160      F=simplify(F,14);
161      if(size(F) > sF){ return(F); }
162   }
163   print("Deflation unsuccessful: return value is the (possibly simplified) original system.");
164   return(F);
165}
166
167proc deflateHMS(ideal F, intvec ro, intvec co, list #)
168"USAGE:   deflateHMS(F, ro, co [, m [, S ]]);
169         ideal F: system of polynomial equations
170         intvecs ro and co: contain the row (respectively column) indices of a full
171           rank submatrix of the Jacobian of F at the point at which you want to deflate F
172           (if the rank is 0, make ro and co equal to the intvec containing only 0)
173         integer m: parameter influencing a choice made in the algorithm
174         string (or list of strings) S: parameter(s) influencing the output
175RETURN:  ring: a ring containing the ideal AUGF, representing the augmented system
176REMARK:  This deflation method augments the given polynomial system to a system which is
177         defined in the original ring. However, if the rank is 0, we add additional
178         variables representing the entries of a random column vector L of length nv,
179         where nv is the number of variables of the original polynomial ring. The system F
180         is then augmented by the entries of J*L, where J is the Jacobian of F.
181         We use these additional variables, instead of just choosing some random numbers,
182         so that the user would have full control over the type of random numbers: one
183         can just substitute the variables later on.
184         For more information about this deflation method see
185         section 3 of Jonathan Hauenstein, Bernard Mourrain, Agnes Szanto; Certifying
186            isolated singular points and their multiplicity structure.
187         We use the integer c as defined in that paper. During the algorithm, we have to
188         choose a subset of {1,...,c}, which is then used to generate the augmentation
189         of F. In this implementation, we only use subsets containing exactly one element.
190         The choice can be controlled by the optional argument m.
191
192NOTE:    The optional argument m controls which element of {1,...,c} will be chosen during
193         the procedure:
194           if m is -1, the procedure chooses a random value between 1 and c
195           if m is  0, the procedure chooses c
196           if m  >  c, the procedure chooses c
197           if 1< m <c, the procedure chooses m
198         If no optional argument is given, the procedure chooses a random value.
199         if the given m leads the procedure to adding only polynomials which are 0 or
200         scalar multiples of the polynomials in the original system, the procedure
201         automatically goes through 1,...,c until something useful is added (or returns
202         the original system and prints a message if the deflation was unsuccessful).
203
204         With the optional argument S you can influence the names that will be given to
205         the additional variables.
206         If S is of type string, say \"L\", then the variable names will be L(1),...,L(nv).
207         If S is a list of strings, it should be of the following form:
208         [\"no parentheses\",] s_1 [,...,s_n]. If the list consists of two
209         elements \"no parentheses\" and \"L\", the variables are named as
210         above, but without the parentheses. If the list contains enough strings, that is
211         if you specify strings s_1,...,s_nv, then exactly these strings will be used as
212         the names of the variables. (If you specify less than nv names, only s_1 is used.
213         If you specify more than nv, only s_1,...,s_nv are used.)
214
215         The procedure does not check for naming conflicts prior to defining the
216         extended ring, so please make sure that there are none.
217
218         You should only specify an S if you have also specified an m.
219         If no S is given, the added variables are named L(1),...,L(nv).
220EXAMPLE: example deflateHMS; shows an example
221"
222{
223   int chi=-1;
224   if(size(#) > 0)
225   {
226      chi=#[1];
227   }
228   if(size(#) <= 1)
229   {
230      list VN="L";
231   }
232   if(size(#) == 2)
233   {
234      list VN=#[2];
235   }
236   if(size(#) > 2)
237   {
238      list VN=delete(#,1);
239   }
240
241   F=simplify(F,2+4+8);
242   matrix J=jacob(F);
243
244   int nv=nvars(basering);
245   def br=basering;
246   list RL=ringlist(br);
247
248   if( ro[1]*co[1] == 0 )
249   {
250      //ie if the rank is 0
251      //then we need a random vector
252      //so we construct a ring with additional variables, such that the random values
253      //can be chosen later on and substituted for these variables
254
255      RL=append_var_list(nv,RL,VN);
256      def bigR=ring(RL);
257      setring bigR;
258
259
260      matrix N[nv][1];
261      int i;
262      for(i=1; i<=nv; i++)
263      {
264         N[i,1]=var(nv+i);
265      }
266
267      matrix J=imap(br,J);
268      J=J*N;
269      ideal AUGF=imap(br,F);
270      AUGF=AUGF,ideal(J);
271      //int CHNG=nv;
272      export(AUGF);
273      //export(CHNG);
274      return(bigR);
275   }
276   else
277   {
278      intvec cc=complementary_ro_co_vecs(co,ncols(J));
279      matrix A=submat(J,ro,co);
280      matrix B=submat(J,ro,cc);
281      matrix la=getLambda(A,B);
282      int i=process_choice_for_i(chi,ncols(la));
283      matrix N[nrows(la)][1]=submat(la,1..nrows(la),i);
284
285      ideal H=ideal(J*N);
286      H=remove_constants(H);
287      int sF=size(F);
288      F=F,H;
289      F=simplify(F,14);
290      //gets rid of zero generators and copies of earlier listed generators
291      //and polys which are scalar multiples of earlier listed polys
292
293      if(size(F) == sF)
294      {
295         //we did not add a polynomial which is not 0 and not a scalar multiple
296         //of an earlier listed polynomial
297         F=exhaust_options(F,i,la,J);
298      }
299      def outR=ring(RL);
300      setring outR;
301      ideal AUGF=imap(br,F);
302      //int CHNG=0;
303      export(AUGF);
304      //export(CHNG);
305      return(outR);
306   }
307}
308example
309{ "EXAMPLE:"; echo=2;
310  ring ojika3=0,(x,y,z),dp;
311  ideal F=x+y+z-1, 2x3+5y2-10z+5z3+5, 2x+2y+z2-1;
312  intvec ro=1,2;
313  intvec co=1,3;
314  def R1=deflateHMS(F,ro,co);
315  R1;
316  setring R1;
317  AUGF;
318
319  ring cbms1=0,(x,y,z),dp;
320  ideal F=x3-yz, y3-xz, z3-xy;
321  ro=0;
322  co=0;
323  int m=-1;
324  def R2=deflateHMS(F,ro,co,m,"L");
325  R2;
326  setring R2;
327  AUGF;
328}
329
330//////////////////////////////////////////////////////////////////////////////////////////
331//////////////////////////////////////////////////////////////////////////////////////////
332//////////////////////////////////////   Method B   //////////////////////////////////////
333//////////////////////////////////////////////////////////////////////////////////////////
334//////////////////////////////////////////////////////////////////////////////////////////
335
336static proc complementary_ro_co_vecs(intvec v, int m)
337{
338   intvec c;
339   intvec b;
340   int j;
341   b[m]=0;
342   int i;
343   for(i=1; i<=size(v); i++)
344   {
345      b[v[i]]=1;
346   }
347   for(i=1; i<=m; i++)
348   {
349      if(b[i] == 0)
350      {
351         j++;
352         c[j]=i;
353      }
354   }
355   return(c);
356}
357
358static proc certain_submats(matrix M, intvec ro, intvec co)
359{
360   //ro and co the row ,respectively column, indices of the matrix we want to have as
361   //part of the returned submatrices
362
363   list S;
364   intvec rn, cn;//the row and column indices used to obtain the next submatrix
365   intvec rc=complementary_ro_co_vecs(ro,nrows(M));
366   intvec cc=complementary_ro_co_vecs(co,ncols(M));
367   int sr=size(ro)+1;
368   int sc=size(co)+1;
369   int i,j;
370   for(i=1; i<=size(rc); i++)
371   {
372      rn=ro;
373      rn[sr]=rc[i];
374      for(j=1; j<=size(cc); j++)
375      {
376         cn=co;
377         cn[sc]=cc[j];
378         S = S + list(submat(M,rn,cn));
379      }
380   }
381   return(S);
382}
383
384static proc det_augment(ideal F, intvec ro, intvec co)
385{
386   //returns the polynomials with which we want to augment F
387   //namely the determinants of all r+1 x r+1 submatrices of the Jacobian of F
388   //containing the r x r submatrix specified by ro and co
389   matrix J=jacob(F);
390
391   if(ro[1]*co[1] == 0)
392   {
393      //meaning the rank is 0
394      //then return the 1x1 minors, that is the entries of J
395      return(ideal(J));
396   }
397
398   list S=certain_submats(J,ro,co);
399
400   ideal A=det(S[1]);
401   int i;
402   for(i=2; i<=size(S); i++)
403   {
404      A=A,det(S[i]);
405   }
406   return(A);
407}
408
409proc deflateHW1(ideal F, intvec ro, intvec co)
410"USAGE:   deflateHW1(F, ro, co);
411         ideal F: system of polynomial equations
412         intvecs ro and co: contain the row (respectively column) indices of a full
413           rank submatrix of the Jacobian of F at the point at which you want to deflate F
414           (if the rank is 0, make ro and co equal to the intvec containing only 0)
415RETURN:  ideal: an augmented polynomial system
416ASSUME:  ro and co have the same number of elements, say rk.
417REMARK:  This deflation method adds to F the determinants of the (rk+1) x (rk+1)
418         submatrices of the Jacobian of F containing the rows and columns specified in
419         ro and co
420EXAMPLE: example deflateHW1; shows an example
421"
422{
423   //does one iteration of deflation, then returns the augmented system
424   //ro and co the row, respectively column, indices of the matrix we want to have as
425   //part of the submatrices we use to augment F
426
427   ideal A=det_augment(F,ro,co);
428   F=F,A;
429   F=simplify(F,2+4+8);//erases the zeroes, copies, scalar multiples
430   return(F);
431}
432example
433{ "EXAMPLE:"; echo=2;
434  ring ojika3=0,(x,y,z),dp;
435  ideal F=x+y+z-1, 2x3+5y2-10z+5z3+5, 2x+2y+z2-1;
436  intvec ro=1,2;//number of elements is rk=2
437  intvec co=1,3;
438  ideal AUGF=deflateHW1(F,ro,co);//considers 3x3 submatrices of the Jacobian J of F,
439  //that is J itself
440
441  AUGF;
442
443  //the only polynomial we added is the determinant of J
444  det(jacob(F));
445}
446
447//////////////////////////////////////////////////////////////////////////////////////////
448/////////////////////////////   strong intrinsic deflation   /////////////////////////////
449//////////////////////////////////////////////////////////////////////////////////////////
450
451static proc makeB(int N, int d)
452{
453   //fills an NxN matrix with newly added variables
454   //column by column, from left to right, each column from top to bottom
455
456   matrix B[N][N];
457   int i,j;
458   for(j=1; j<=N; j++)
459   {
460      for(i=1; i<=N; i++)
461      {
462         B[i,j]=var(N+(N-d)*d+(j-1)*N+i);
463      }
464   }
465   return(B);
466}
467
468static proc makeIX(int N, int d)
469{
470   //constructs the composite matrix which has the identity matrix on top and
471   //Xi on the bottom. Xi is filled with the newly added variables; column by column,
472   //from left to right, each column from top to bottom
473
474   matrix I=diag(1,d);
475   matrix X[N-d][d];
476   int i,j;
477   for(j=1; j<=d; j++)
478   {
479      for(i=1; i<=N-d; i++)
480      {
481         X[i,j]=var(N+(j-1)*(N-d)+i);
482      }
483   }
484   I=concat(I,transpose(X));
485   I=transpose(I);
486   return(I);
487}
488
489proc deflateHW2(ideal F, int rk, list #)
490"USAGE:   deflateHW2(F, rk [, SXi, SB]);
491         ideal F: system of polynomial equations
492         int rk: the rank of the Jacobian of F at the point at which you want to deflate
493         strings (or lists of strings) SXi, SB: parameters influencing the output
494
495RETURN:  ring: a ring containing the ideal AUGF, representing the augmented system
496
497REMARK:  This deflation method augments the given polynomial system to a system which is
498         defined in the original ring if rk = 0.
499         If rk > 0, the augmented system is defined in an extended ring and a random
500         matrix B is used in the computations. More precisely:
501         - rk*(nv-rk) new variables are added to the original ring
502         - the random matrix B has dimensions nv*nv
503
504NOTE:    If rk = 0: the returned ring R is the same as the basering.
505         If rk > 0: the returned ring R is the basering plus additional variables.
506         More precisely, we add rk*(nv-rk) + nv*nv variables, where nv is the number of
507         variables in the basering. They have the following purpose:
508         - the first rk*(nv-rk) correspond to the new variables of the extended ring
509           ( lets say that these variables are called Xi_1,...,Xi_(rk*(nv-rk)) )
510         - the last nv*nv variables correspond to the entries of the random matrix B
511         This way, you have more options: you can substitute the variables corresponding
512         to the entries of B by random numbers you generated yourself.
513
514         With the optional arguments you can influence the names that will be given to the
515         additional variables. If you give any optional arguments, you should give exactly
516         two of them. The first controls the names of the Xi_j, the second the names
517         of the entries of B.
518         If an optional argument is of type string, say \"X\", then the variable names
519         controlled by this argument will be X(1),...,X(# of variables).
520         If an optional argument is given as a list of strings, it should be of the
521         following form: [\"no parentheses\",] s_1 [,...,s_n]. If the list consists of two
522         elements \"no parentheses\" and \"X\", the variables are named as
523         above, but without the parentheses. If the list contains enough strings, that is
524         if you specify strings s_1,...,s_n with n=rk*(nv-rk) or n=nv*nv (depending on
525         which of the variable names are being controlled), then exactly these strings
526         will be used as the names of the variables. (If you specify less than n names,
527         only s_1 is used. If you specify more than n, only s_1,...,s_n are used.)
528
529         The procedure does not check for naming conflicts prior to defining the
530         extended ring, so please make sure that there are none.
531
532         If no optional arguments are given, the new variables are named X(1),...,X(rk+1),
533         the entries of B are named B(1),...,B(nv*(rk+1)).
534
535         As for the order in which B is filled with variables:
536         - B is filled with variables column by column, from left to right, filling the
537           columns from top to bottom
538
539EXAMPLE: example deflateHW2; shows an example
540"
541{
542   list vnb="B";
543   list vnxi="X";
544   if(size(#) > 0)
545   {
546      if(size(#) > 2)
547      {
548         ERROR("Too many optional arguments (there should be exactly two, if any).");
549      }
550      if(size(#) == 1)
551      {
552         ERROR("Too few optional arguments (there should be exactly two, if any).");
553      }
554
555      if(typeof(#[1]) != typeof(#[2]))
556      {
557         //ERROR("The optional arguments must be of the same type.");
558      }
559
560      vnb=#[2];
561      vnxi=#[1];
562   }
563
564   matrix J=jacob(F);
565   int N=ncols(J);//number of variables
566   int d=N-rk;
567
568   int nv=nvars(basering);
569   def br=basering;
570   list RL=ringlist(br);
571
572   if( rk > 0 )
573   {
574      RL=append_var_list((N-d)*d,RL,vnxi);
575      RL=append_var_list(N*N,RL,vnb);
576
577      def bigR=ring(RL);
578      setring bigR;
579
580      matrix J=imap(br,J);
581      matrix B=makeB(N,d);
582      matrix IX=makeIX(N,d);
583      J=J*B*IX;
584
585      ideal AUGF=imap(br,F);
586      AUGF=AUGF,ideal(J);
587      AUGF=simplify(AUGF,2+4+8);//remove zeroes, copies, scalar multiples
588      export(AUGF);
589      return(bigR);
590   }
591
592   if( rk == 0 )
593   {
594      def outR=ring(RL);
595      setring outR;
596
597      matrix J=imap(br,J);
598      ideal AUGF=imap(br,F);
599      AUGF=AUGF,ideal(J);
600      AUGF=simplify(AUGF,2+4+8);
601      export(AUGF);
602      return(outR);
603   }
604}
605example
606{ "EXAMPLE:"; echo=2;
607  ring ojika3=0,(x,y,z),dp;
608  ideal F=x+y+z-1, 2x3+5y2-10z+5z3+5, 2x+2y+z2-1;
609  int rk=2;
610  list L="X",list("no parentheses", "B");
611  def R=deflateHW2(F,rk,L);
612  R;
613  setring R;
614  AUGF;
615}
616
617//////////////////////////////////////////////////////////////////////////////////////////
618//////////////////////////////////////////////////////////////////////////////////////////
619//////////////////////////////////////   Method A   //////////////////////////////////////
620//////////////////////////////////////////////////////////////////////////////////////////
621//////////////////////////////////////////////////////////////////////////////////////////
622
623proc deflateLVZ(ideal F, int rk, list #)
624"USAGE:   deflateLVZ(F, rk [, Sl, SB, Sh]);
625         ideal F: system of polynomial equations
626         int rk: the rank of the Jacobian of F at the point at which you want to deflate
627         strings (or lists of strings) Sl, SB, Sh: parameters influencing the output
628
629RETURN:  ring: a ring containing the ideal AUGF, representing the augmented system
630
631REMARK:  This deflation method augments the given polynomial system to a system defined
632         in an extended polynomial ring (new variables: lambda_i), and uses two random
633         elements in its computations: a matrix B and a (column) vector h.
634         More precisely:
635         - the original polynomial ring is extended by rk+1 variables
636         - the random matrix B has dimensions nv x rk+1, where nv is the number of
637           variables in the original ring
638         - the random vector h has length rk+1
639
640NOTE:    The returned ring R is the same as the basering plus additional variables.
641         More precisely, we add (nv+2)*(rk+1) variables, where nv is the number of
642         variables in the basering. They have the following purpose:
643         - the first rk+1 correspond to the variables lambda_i of the extended ring
644         - the next nv*(rk+1) variables correspond to the entries of the random matrix B
645         - the last rk+1 variables correspond to the entries of the random vector h
646         This way, the user has more options: he can substitute the variables
647         corresponding to the random elements by random numbers he generated himself.
648
649         With the optional arguments you can influence the names that will be given to the
650         additional variables. If you give any optional arguments, you should give exactly
651         three of them. The first controls the names of the lambda_i, the second the names
652         of the entries of B, and the third controls the names given to the entries of h.
653         If an optional argument is of type string, say \"X\", then the variable names
654         controlled by this argument will be X(1),...,X(# of variables).
655         If an optional argument is given as a list of strings, it should be of the
656         following form: [\"no parentheses\",] s_1 [,...,s_n]. If the list consists of two
657         elements \"no parentheses\" and \"X\", the variables are named as
658         above, but without the parentheses. If the list contains enough strings, that is
659         if you specify strings s_1,...,s_n with n=rk+1 or n=nv*(rk+1) (depending on which
660         of the variable names are being controlled), then exactly these strings will be
661         used as the names of the variables. (If you specify less than n names, only s_1
662         is used. If you specify more than n, only s_1,...,s_n are used.)
663
664         The procedure does not check for naming conflicts prior to defining the
665         extended ring, so please make sure that there are none.
666
667         If no optional arguments are given, the new variables are named l(1),...,l(rk+1),
668         the entries of B are named B(1),...,B(nv*(rk+1)), and the entries of h are named
669         h(1),...,h(rk+1).
670
671         As for the order in which B and h are filled with variables:
672         - B is filled with variables column by column, from left to right, filling the
673           columns from top to bottom
674         - the column vector h is filled from top to bottom
675
676EXAMPLE: example deflateLVZ; shows an example
677"
678{
679   if(size(#) != 3)
680   {
681      if(size(#) != 0)
682      {
683         ERROR("If any optional arguments are given, there have to be exactly three of them.");
684      }
685      list Vl="l";
686      list VB="B";
687      list Vh="h";
688   }
689
690   if(size(#) == 3)
691   {
692      list Vl=#[1];
693      list VB=#[2];
694      list Vh=#[3];
695   }
696
697
698
699   matrix J=jacob(F);
700
701   def br=basering;
702   list RL=ringlist(basering);
703   int nv=nvars(basering);
704   RL=append_var_list(rk+1,RL,Vl);
705   RL=append_var_list( nv*(rk+1) ,RL,VB);
706   RL=append_var_list(rk+1,RL,Vh);
707
708   def outr=ring(RL);
709   setring outr;
710   matrix J=imap(br,J);
711   ideal F=imap(br,F);
712
713   matrix B[nv][rk+1];
714   int ii,jj;
715   for(jj=1; jj<=rk+1; jj++)
716   {
717      for(ii=1; ii<=nv; ii++)
718      {
719         B[ii,jj]=var( nv+rk+1 + (jj - 1)*(rk+1) + ii );
720      }
721   }
722
723   matrix la[rk+1][1];
724   for(ii=1; ii<=rk+1; ii++)
725   {
726      la[ii,1]=var( nv + ii );
727   }
728
729   matrix h[rk+1][1];
730   for(ii=1; ii<=rk+1; ii++)
731   {
732      h[ii,1]=var( nv+rk+1 + nv*(rk+1) + ii );
733   }
734
735   matrix C=J*B;
736   ideal G=ideal(C*la);
737   matrix H=transpose(la)*h;
738   kill h;
739   poly h=H[1,1]-1;
740
741   ideal AUGF=F,G,h;
742   export(AUGF);
743   return(outr);
744}
745example
746{ "EXAMPLE:"; echo=2;
747  ring ojika3=0,(x,y,z),dp;
748  ideal F=x+y+z-1, 2x3+5y2-10z+5z3+5, 2x+2y+z2-1;
749  int rk=2;
750  list L="l",list("no parentheses", "B"), list("ha","he","ho");
751  def R=deflateLVZ(F,rk,L);
752  R;
753  setring R;
754  AUGF;
755}
756
757
758//////////////////////////////////////////////////////////////////////////////////////////
759//////////////////////////////////////////////////////////////////////////////////////////
760//////////////////////////////////////   Examples   //////////////////////////////////////
761//////////////////////////////////////////////////////////////////////////////////////////
762//////////////////////////////////////////////////////////////////////////////////////////
763//These are some benchmark-examples. You can find most of them in the literature listed
764//under references.
765//Every examples listed consists of a polynomial system of equations and one ore two
766//points at which we want to deflate the system. The examples which are given
767//exactly can be handled with Singular (that is, symbolically). However, the purpose of
768//the procedures in this library is to use information which was computed numerically
769//- such as the (numerical) rank of the Jacobian of the polynomial system at a certain
770//point -
771//and then do symbolical manipulations of the polynomial system in order to deflate it.
772//For the Cyclic-9 problem, for example, you will probably want to compute the necessary
773//information numerically.
774/*
775
776ring cbms1=0,(x,y,z),dp;
777list p=0,0,0;
778ideal F=x3-yz, y3-xz, z3-xy;
779
780
781ring cbms2=0,(x,y,z),dp;
782list p=0,0,0;
783ideal F=x3-3x2y+3xy2-y3-z2, z3-3z2x+3zx2-x3-y2, y3-3y2z+3yz2-z3-x2;
784
785
786ring mth191=0,(x,y,z),dp;
787list p=0,1,0;
788ideal F=x3+y2+z2-1, x2+y3+z2-1, x2+y2+z3-1;
789
790
791ring decker2=0,(x,y),dp;
792list p=0,0;
793ideal F=x+y3, x2y-y4;
794
795
796ring ojika2=0,(x,y,z),dp;
797list p=0,0,1;
798list q=1,0,0;
799ideal F=x2+y+z-1, x+y2+z-1, x+y+z2-1;
800
801
802ring ojika3=0,(x,y,z),dp;
803list p=0,0,1;
804list q=poly(-5)/2,poly(5)/2,1;
805ideal F=x+y+z-1, 2x3+5y2-10z+5z3+5, 2x+2y+z2-1;
806
807
808ring caprasse=(0,a),(x,y,z,w),dp;
809minpoly=a2+3;
810list p=2,-a,2,a;
811ideal F=-x3z + 4xy2z + 4x2yw + 2y3w + 4x2 - 10y2 + 4xz - 10yw + 2,
812-xz3 + 4yz2w + 4xzw2 + 2yw3 + 4xz + 4z2 - 10yw - 10w2 + 2,
813y2z + 2xyw - 2x - z, 2yzw + xw2 - x - 2z;
814
815
816ring KSS=0,x(1..5),dp;
817int i; ideal F; poly f;
818poly g=sum(maxideal(1));
819for(i=1; i<=5; i++)
820{
821   f=var(i)^2 + g - 2*var(i) - 4;
822   F=F,f;
823}
824F=simplify(F,2);
825list p=1,1,1,1,1;
826
827
828
829ring C9=(0,I),(x0,x1,x2,x3,x4,x5,x6,x7,x8),dp;
830ideal F=x0 + x1 + x2 + x3 + x4 + x5 + x6 + x7 + x8,
831
832  x0*x1 + x1*x2 + x2*x3 + x3*x4 + x4*x5 + x5*x6 + x6*x7 + x7*x8 + x8*x0,
833
834  x0*x1*x2 + x1*x2*x3 + x2*x3*x4 + x3*x4*x5 + x4*x5*x6 + x5*x6*x7
835+ x6*x7*x8 + x7*x8*x0 + x8*x0*x1,
836
837  x0*x1*x2*x3 + x1*x2*x3*x4 + x2*x3*x4*x5 + x3*x4*x5*x6 + x4*x5*x6*x7
838+ x5*x6*x7*x8 + x6*x7*x8*x0 + x7*x8*x0*x1 + x8*x0*x1*x2,
839
840  x0*x1*x2*x3*x4 + x1*x2*x3*x4*x5 + x2*x3*x4*x5*x6 + x3*x4*x5*x6*x7
841+ x4*x5*x6*x7*x8 + x5*x6*x7*x8*x0 + x6*x7*x8*x0*x1 + x7*x8*x0*x1*x2
842+ x8*x0*x1*x2*x3,
843
844  x0*x1*x2*x3*x4*x5 + x1*x2*x3*x4*x5*x6 + x2*x3*x4*x5*x6*x7 + x3*x4*x5*x6*x7*x8
845+ x4*x5*x6*x7*x8*x0 + x5*x6*x7*x8*x0*x1 + x6*x7*x8*x0*x1*x2 + x7*x8*x0*x1*x2*x3
846+ x8*x0*x1*x2*x3*x4,
847
848  x0*x1*x2*x3*x4*x5*x6 + x1*x2*x3*x4*x5*x6*x7 + x2*x3*x4*x5*x6*x7*x8
849+ x3*x4*x5*x6*x7*x8*x0 + x4*x5*x6*x7*x8*x0*x1 + x5*x6*x7*x8*x0*x1*x2
850+ x6*x7*x8*x0*x1*x2*x3 + x7*x8*x0*x1*x2*x3*x4 + x8*x0*x1*x2*x3*x4*x5,
851
852  x0*x1*x2*x3*x4*x5*x6*x7 + x1*x2*x3*x4*x5*x6*x7*x8 + x2*x3*x4*x5*x6*x7*x8*x0
853+ x3*x4*x5*x6*x7*x8*x0*x1 + x4*x5*x6*x7*x8*x0*x1*x2 + x5*x6*x7*x8*x0*x1*x2*x3
854+ x6*x7*x8*x0*x1*x2*x3*x4 + x7*x8*x0*x1*x2*x3*x4*x5 + x8*x0*x1*x2*x3*x4*x5*x6,
855
856  x0*x1*x2*x3*x4*x5*x6*x7*x8 - 1;
857poly z0= poly(-9396926) - 3520201*I; z0=z0/10000000;
858poly z1=poly(-24601472) - 8954204*I; z1=z1/10000000;
859poly z2= poly(-3589306) - 1306401*I; z2=z2/10000000;
860list p=z0,z1,z2,z0,-z2,-z1,z0,-z2,-z1;
861
862
863ring DZ1=0,(x,y,z,w),dp;
864list p=0,0,0,0;
865ideal F=x4-yzw, y4-xzw, z4-xyw, w4-xyz;
866
867
868ring DZ2=0,(x,y,z),dp;
869list p=0,0,-1;
870ideal F=x4, x2y+y4, z+z2-7x3-8x2;
871
872*/
Note: See TracBrowser for help on using the repository browser.