Annotation of OpenXM_contrib2/asir2000/engine/Fgfs.c, Revision 1.12
1.12 ! noro 1: /* $OpenXM: OpenXM_contrib2/asir2000/engine/Fgfs.c,v 1.11 2002/11/22 08:44:57 noro Exp $ */
1.1 noro 2:
3: #include "ca.h"
4:
1.3 noro 5: void cont_pp_mv_sf(VL vl,VL rvl,P p,P *c,P *pp);
6: void gcdsf_main(VL vl,P *pa,int m,P *r);
7: void ugcdsf(P *pa,int m,P *r);
1.10 noro 8: void head_monomial(VL vl,V v,P p,P *coef,P *term);
1.4 noro 9: void sqfrsfmain(VL vl,P f,DCP *dcp);
10: void pthrootsf(P f,Q m,P *r);
11: void partial_sqfrsf(VL vl,V v,P f,P *r,DCP *dcp);
12: void gcdsf(VL vl,P *pa,int k,P *r);
1.5 noro 13: void mfctrsfmain(VL vl, P f, DCP *dcp);
1.7 noro 14: void next_evaluation_point(int *mev,int n);
1.12 ! noro 15: void estimatelc_sf(VL vl,VL rvl,P c,DCP dc,int *mev,P *lcp);
! 16: void mfctrsf_hensel(VL vl,VL rvl,P f,P pp0,P u0,P v0,P lcu,P lcv,int *mev,P *up);
1.7 noro 17: void substvp_sf(VL vl,VL rvl,P f,int *mev,P *r);
18: void shift_sf(VL vl, VL rvl, P f, int *mev, int sgn, P *r);
1.12 ! noro 19: void adjust_coef_sf(VL vl,VL rvl,P lcu,P u0,int *mev,P *r);
1.8 noro 20: void extended_gcd_modyk(P u0,P v0,V x,V y,int dy,P *cu,P *cv);
1.7 noro 21: void poly_to_gfsn_poly(VL vl,P f,V v,P *r);
22: void gfsn_poly_to_poly(VL vl,P f,V v,P *r);
1.8 noro 23: void poly_to_gfsn_poly_main(P f,V v,P *r);
24: void gfsn_poly_to_poly_main(P f,V v,P *r);
25: void gfsn_univariate_to_sfbm(P f,int dy,BM *r);
26: void sfbm_to_gfsn_univariate(BM f,V x,V y,P *r);
1.4 noro 27:
28: void lex_lc(P f,P *c)
29: {
30: if ( !f || NUM(f) )
31: *c = f;
32: else
33: lex_lc(COEF(DC(f)),c);
34: }
35:
36: DCP append_dc(DCP dc,DCP dct)
37: {
38: DCP dcs;
39:
40: if ( !dc )
41: return dct;
42: else {
43: for ( dcs = dc; NEXT(dcs); dcs = NEXT(dcs) );
44: NEXT (dcs) = dct;
45: return dc;
46: }
47: }
48:
49: void sqfrsf(VL vl, P f, DCP *dcp)
50: {
51: DCP dc,dct;
52: Obj obj;
53: P t,s,c;
54: VL tvl,nvl;
55:
56: simp_ff((Obj)f,&obj); f = (P)obj;
57: lex_lc(f,&c); divsp(vl,f,c,&t); f = t;
58: monomialfctr(vl,f,&t,&dc); f = t;
59: clctv(vl,f,&tvl); vl = tvl;
60: if ( !vl )
61: ;
62: else if ( !NEXT(vl) ) {
63: sfusqfr(f,&dct);
64: dc = append_dc(dc,NEXT(dct));
65: } else {
66: t = f;
67: for ( tvl = vl; tvl; tvl = NEXT(tvl) ) {
68: reordvar(vl,tvl->v,&nvl);
69: cont_pp_mv_sf(vl,NEXT(nvl),t,&c,&s); t = s;
70: sqfrsf(vl,c,&dct);
71: dc = append_dc(dc,NEXT(dct));
72: }
73: sqfrsfmain(vl,t,&dct);
74: dc = append_dc(dc,dct);
75: }
76: NEWDC(dct); DEG(dct) = ONE; COEF(dct) = (P)c; NEXT(dct) = dc;
77: *dcp = dct;
78: }
79:
80: void sqfrsfmain(VL vl,P f,DCP *dcp)
81: {
82: VL tvl;
83: DCP dc,dct,dcs;
84: P t,s;
85: Q m,m1;
86: V v;
87:
88: clctv(vl,f,&tvl); vl = tvl;
89: dc = 0;
90: t = f;
91: for ( tvl = vl; tvl; tvl = NEXT(tvl) ) {
92: v = tvl->v;
93: partial_sqfrsf(vl,v,t,&s,&dct); t = s;
94: dc = append_dc(dc,dct);
95: }
96: if ( !NUM(t) ) {
97: STOQ(characteristic_sf(),m);
98: pthrootsf(t,m,&s);
99: sqfrsfmain(vl,s,&dct);
100: for ( dcs = dct; dcs; dcs = NEXT(dcs) ) {
101: mulq(DEG(dcs),m,&m1); DEG(dcs) = m1;
102: }
103: dc = append_dc(dc,dct);
104: }
105: *dcp = dc;
106: }
107:
108: void pthrootsf(P f,Q m,P *r)
109: {
110: DCP dc,dc0,dct;
111: N qn,rn;
112:
113: if ( NUM(f) )
114: pthrootgfs(f,r);
115: else {
116: dc = DC(f);
117: dc0 = 0;
118: for ( dc0 = 0; dc; dc = NEXT(dc) ) {
119: NEXTDC(dc0,dct);
120: pthrootsf(COEF(dc),m,&COEF(dct));
121: if ( DEG(dc) ) {
122: divn(NM(DEG(dc)),NM(m),&qn,&rn);
123: if ( rn )
124: error("pthrootsf : cannot happen");
125: NTOQ(qn,1,DEG(dct));
126: } else
127: DEG(dct) = 0;
128: }
129: NEXT(dct) = 0;
130: MKP(VR(f),dc0,*r);
131: }
132: }
133:
134: void partial_sqfrsf(VL vl,V v,P f,P *r,DCP *dcp)
135: {
136: P ps[2];
137: DCP dc0,dc;
138: int m;
139: P t,flat,flat1,g,df,q;
140:
141: diffp(vl,f,v,&df);
142: if ( !df ) {
143: *dcp = 0;
144: *r = f;
145: return;
146: }
147: ps[0] = f; ps[1] = df;
148: gcdsf(vl,ps,2,&g);
149: divsp(vl,f,g,&flat);
150: m = 0;
151: t = f;
152: dc0 = 0;
153: while ( !NUM(flat) ) {
154: while ( divtp(vl,t,flat,&q) ) {
155: t = q; m++;
156: }
157: ps[0] = t; ps[1] = flat;
158: gcdsf(vl,ps,2,&flat1);
159: divsp(vl,flat,flat1,&g);
160: flat = flat1;
161: NEXTDC(dc0,dc);
162: COEF(dc) = g;
163: STOQ(m,DEG(dc));
164: }
165: NEXT(dc) = 0;
166: *dcp = dc0;
167: *r = t;
168: }
1.1 noro 169:
170: void gcdsf(VL vl,P *pa,int k,P *r)
171: {
1.3 noro 172: P *ps,*pl,*pm;
173: P **cp;
1.1 noro 174: int *cn;
175: DCP *ml;
176: Obj obj;
177: int i,j,l,m;
178: P mg,mgsf,t;
179: VL avl,nvl,tvl,svl;
180:
181: ps = (P *)ALLOCA(k*sizeof(P));
182: for ( i = 0, m = 0; i < k; i++ ) {
183: simp_ff((Obj)pa[i],&obj);
184: if ( obj )
1.3 noro 185: ps[m++] = (P)obj;
1.1 noro 186: }
187: if ( !m ) {
188: *r = 0;
189: return;
190: }
191: if ( m == 1 ) {
1.3 noro 192: *r = ps[0];
1.1 noro 193: return;
194: }
195: pl = (P *)ALLOCA(m*sizeof(P));
196: ml = (DCP *)ALLOCA(m*sizeof(DCP));
197: for ( i = 0; i < m; i++ )
198: monomialfctr(vl,ps[i],&pl[i],&ml[i]);
1.3 noro 199: gcdmonomial(vl,ml,m,&mg); simp_ff((Obj)mg,&obj); mgsf = (P)obj;
1.1 noro 200: for ( i = 0, nvl = vl, avl = 0; nvl && i < m; i++ ) {
201: clctv(vl,pl[i],&tvl);
202: intersectv(nvl,tvl,&svl); nvl = svl;
203: mergev(vl,avl,tvl,&svl); avl = svl;
204: }
205: if ( !nvl ) {
206: *r = mgsf;
207: return;
208: }
209: if ( !NEXT(avl) ) {
210: ugcdsf(pl,m,&t);
211: mulp(vl,mgsf,t,r);
212: return;
213: }
214: for ( tvl = nvl, i = 0; tvl; tvl = NEXT(tvl), i++ );
215: for ( tvl = avl, j = 0; tvl; tvl = NEXT(tvl), j++ );
216: if ( i == j ) {
217: /* all the pl[i]'s have the same variables */
218: gcdsf_main(avl,pl,m,&t);
219: } else {
220: cp = (P **)ALLOCA(m*sizeof(P *));
221: cn = (int *)ALLOCA(m*sizeof(int));
222: for ( i = 0; i < m; i++ ) {
223: cp[i] = (P *)ALLOCA(lengthp(pl[i])*sizeof(P));
224: cn[i] = pcoef(vl,nvl,pl[i],cp[i]);
225: }
226: for ( i = j = 0; i < m; i++ )
227: j += cn[i];
228: pm = (P *)ALLOCA(j*sizeof(P));
229: for ( i = l = 0; i < m; i++ )
230: for ( j = 0; j < cn[i]; j++ )
231: pm[l++] = cp[i][j];
232: gcdsf(vl,pm,l,&t);
233: }
234: mulp(vl,mgsf,t,r);
235: }
236:
237: /* univariate gcd */
238:
239: void ugcdsf(P *pa,int m,P *r)
240: {
1.3 noro 241: P *ps;
1.1 noro 242: int i;
243: UM w1,w2,w3,w;
244: int d;
245: V v;
246:
247: if ( m == 1 ) {
248: *r = pa[0];
249: return;
250: }
1.3 noro 251: for ( i = 0; i < m; i++ )
252: if ( NUM(pa[i]) ) {
253: itogfs(1,r);
254: return;
255: }
1.1 noro 256: ps = (P *)ALLOCA(m*sizeof(P));
257: sort_by_deg(m,pa,ps);
1.3 noro 258: v = VR(ps[m-1]);
259: d = getdeg(v,ps[m-1]);
1.1 noro 260: w1 = W_UMALLOC(d);
261: w2 = W_UMALLOC(d);
262: w3 = W_UMALLOC(d);
263: ptosfum(ps[0],w1);
264: for ( i = 1; i < m; i++ ) {
265: ptosfum(ps[i],w2);
266: gcdsfum(w1,w2,w3);
267: w = w1; w1 = w3; w3 = w;
268: if ( !DEG(w1) ) {
1.3 noro 269: itogfs(1,r);
1.1 noro 270: return;
271: }
272: }
273: sfumtop(v,w1,r);
274: }
275:
1.4 noro 276: /* deg(HT(p),v), where p is considered as distributed poly over F[v] */
277: int gethdeg(VL vl,V v,P p)
278: {
279: DCP dc;
280: Q dmax;
281: P cmax;
282:
283: if ( !p )
284: return -1;
285: else if ( NUM(p) )
286: return 0;
287: else if ( VR(p) != v )
288: /* HT(p) = HT(lc(p))*x^D */
289: return gethdeg(vl,v,COEF(DC(p)));
290: else {
291: /* VR(p) = v */
292: dc = DC(p); dmax = DEG(dc); cmax = COEF(dc);
293: for ( dc = NEXT(dc); dc; dc = NEXT(dc) )
294: if ( compp(vl,COEF(dc),cmax) > 0 ) {
295: dmax = DEG(dc); cmax = COEF(dc);
296: }
297: return QTOS(dmax);
298: }
299: }
1.1 noro 300:
301: /* all the pa[i]'s have the same variables (=vl) */
302:
303: void gcdsf_main(VL vl,P *pa,int m,P *r)
304: {
1.3 noro 305: int nv,i,i0,imin,d,d0,d1,d2,dmin,index;
306: V v,v0,vmin;
1.2 noro 307: VL tvl,nvl,rvl,nvl0,rvl0;
1.3 noro 308: P *pc, *ps, *ph,*lps;
309: P x,t,cont,hg,g,hm,mod,s;
310: P hge,ge,ce,he,u,cof1e,mode,mod1,adj,cof1,coadj,q;
311: GFS sf;
1.2 noro 312:
1.1 noro 313: for ( nv = 0, tvl = vl; tvl; tvl = NEXT(tvl), nv++);
314: if ( nv == 1 ) {
315: ugcdsf(pa,m,r);
316: return;
317: }
1.4 noro 318: /* find v s.t. min(deg(pa[i],v)+gethdeg(pa[i],v)) is minimal */
1.1 noro 319: tvl = vl;
320: do {
321: v = tvl->v;
322: i = 0;
323: do {
1.4 noro 324: d = getdeg(v,pa[i])+gethdeg(vl,v,pa[i]);
1.1 noro 325: if ( i == 0 || (d < d0) ) {
326: d0 = d; i0 = i; v0 = v;
327: }
328: } while ( ++i < m );
329: if ( tvl == vl || (d0 < dmin) ) {
330: dmin = d0; imin = i0; vmin = v0;
331: }
332: } while ( tvl = NEXT(tvl) );
333:
334: /* reorder variables so that vmin is the last variable */
335: for ( nvl0 = 0, rvl0 = 0, tvl = vl; tvl; tvl = NEXT(tvl) )
336: if ( tvl->v != vmin ) {
337: NEXTVL(nvl0,nvl); nvl->v = tvl->v;
338: NEXTVL(rvl0,rvl); rvl->v = tvl->v;
339: }
340: /* rvl = remaining variables */
1.3 noro 341: NEXT(rvl) = 0; rvl = rvl0;
1.1 noro 342: /* nvl = ...,vmin */
1.3 noro 343: NEXTVL(nvl0,nvl); nvl->v = vmin; NEXT(nvl) = 0; nvl = nvl0;
1.2 noro 344: MKV(vmin,x);
1.1 noro 345:
346: /* for content and primitive part */
347: pc = (P *)ALLOCA(m*sizeof(P));
348: ps = (P *)ALLOCA(m*sizeof(P));
349: ph = (P *)ALLOCA(m*sizeof(P));
350: /* separate the contents */
351: for ( i = 0; i < m; i++ ) {
1.3 noro 352: reorderp(nvl,vl,pa[i],&t);
1.1 noro 353: cont_pp_mv_sf(nvl,rvl,t,&pc[i],&ps[i]);
1.10 noro 354: head_monomial(nvl,vmin,ps[i],&ph[i],&t);
1.1 noro 355: }
356: ugcdsf(pc,m,&cont);
357: ugcdsf(ph,m,&hg);
358:
359: /* for hg*pp (used in check phase) */
360: lps = (P *)ALLOCA(m*sizeof(P));
361: for ( i = 0; i < m; i++ )
362: mulp(nvl,hg,ps[i],&lps[i]);
363:
364: while ( 1 ) {
365: g = 0;
1.3 noro 366: cof1 = 0;
1.1 noro 367: hm = 0;
1.3 noro 368: itogfs(1,&mod);
1.1 noro 369: index = 0;
1.3 noro 370: for ( index = 0; getdeg(vmin,mod) <= d+1; index++ ) {
1.1 noro 371: /* evaluation pt */
1.3 noro 372: indextogfs(index,&s);
1.1 noro 373: substp(nvl,hg,vmin,s,&hge);
374: if ( !hge )
375: continue;
376: for ( i = 0; i < m; i++ )
377: substp(nvl,ps[i],vmin,s,&ph[i]);
378: /* ge = GCD(ps[0]|x=s,...,ps[m-1]|x=s) */
379: gcdsf(nvl,ph,m,&ge);
1.10 noro 380: head_monomial(nvl,vmin,ge,&ce,&he);
1.3 noro 381: if ( NUM(he) ) {
1.1 noro 382: *r = cont;
383: return;
384: }
1.3 noro 385: divgfs((GFS)hge,(GFS)ce,&sf); t = (P)sf;
386: mulp(nvl,t,ge,&u); ge = u;
1.1 noro 387: divsp(nvl,ph[imin],ge,&t); mulp(nvl,hge,t,&cof1e);
1.2 noro 388: /* hm=0 : reset; he==hm : lucky */
1.3 noro 389: if ( !hm || !compp(nvl,he,hm) ) {
1.2 noro 390: substp(nvl,mod,vmin,s,&mode); divsp(nvl,mod,mode,&mod1);
391: /* adj = mod/(mod|x=s)*(ge-g|x=s) */
392: substp(nvl,g,vmin,s,&t);
393: subp(nvl,ge,t,&u); mulp(nvl,mod1,u,&adj);
394: /* coadj = mod/(mod|vmin=s)*(cof1e-cof1e|vmin=s) */
395: substp(nvl,cof1,vmin,s,&t);
1.3 noro 396: subp(nvl,cof1e,t,&u); mulp(nvl,mod1,u,&coadj);
1.2 noro 397: if ( !adj ) {
398: /* adj == gcd ? */
399: for ( i = 0; i < m; i++ )
1.3 noro 400: if ( !divtp(nvl,lps[i],g,&t) )
1.2 noro 401: break;
402: if ( i == m ) {
1.3 noro 403: cont_pp_mv_sf(nvl,rvl,g,&t,&u);
1.2 noro 404: mulp(nvl,cont,u,&t);
1.3 noro 405: reorderp(vl,nvl,t,r);
1.2 noro 406: return;
407: }
408: } else if ( !coadj ) {
1.3 noro 409: /* ps[imin]/coadj == gcd ? */
410: if ( divtp(nvl,lps[imin],cof1,&q) ) {
1.2 noro 411: for ( i = 0; i < m; i++ )
412: if ( !divtp(nvl,lps[i],q,&t) )
413: break;
414: if ( i == m ) {
415: cont_pp_mv_sf(nvl,rvl,q,&t,&u);
416: mulp(nvl,cont,u,&t);
1.3 noro 417: reorderp(vl,nvl,t,r);
1.2 noro 418: return;
419: }
420: }
421: }
422: addp(nvl,g,adj,&t); g = t;
423: addp(nvl,cof1,coadj,&t); cof1 = t;
424: subp(nvl,x,s,&t); mulp(nvl,mod,t,&u); mod = u;
425: hm = he;
426: } else {
427: d1 = homdeg(hm); d2 = homdeg(he);
428: if ( d1 < d2 ) /* we use current hm */
429: continue;
430: else if ( d1 > d2 ) {
431: /* use he */
432: g = ge;
433: cof1 = cof1e;
434: hm = he;
435: subp(nvl,x,s,&mod);
436: } else {
437: /* d1==d2, but hm!=he => both are unlucky */
438: g = 0;
439: cof1 = 0;
1.3 noro 440: itogfs(1,&mod);
1.2 noro 441: }
1.1 noro 442: }
443: }
444: }
445: }
446:
1.10 noro 447: void head_monomial(VL vl,V v,P p,P *coef,P *term)
1.1 noro 448: {
449: P t,s,u;
450: DCP dc;
451: GFS one;
452:
1.3 noro 453: itogfs(1,&one);
454: t = (P)one;
1.1 noro 455: while ( 1 ) {
456: if ( NUM(p) || VR(p) == v ) {
457: *coef = p;
458: *term = t;
459: return;
460: } else {
1.3 noro 461: NEWDC(dc);
462: COEF(dc) = (P)one; DEG(dc) = DEG(DC(p));
1.1 noro 463: MKP(VR(p),dc,s);
464: mulp(vl,t,s,&u); t = u;
465: p = COEF(DC(p));
466: }
467: }
468: }
469:
470: void cont_pp_mv_sf(VL vl,VL rvl,P p,P *c,P *pp)
471: {
472: DP dp;
473: MP t;
474: int i,m;
475: P *ps;
476:
477: ptod(vl,rvl,p,&dp);
478: for ( t = BDY(dp), m = 0; t; t = NEXT(t), m++ );
479: ps = (P *)ALLOCA(m*sizeof(P));
1.3 noro 480: for ( t = BDY(dp), i = 0; t; t = NEXT(t), i++ )
1.1 noro 481: ps[i] = C(t);
1.10 noro 482: gcdsf(vl,ps,m,c);
1.3 noro 483: divsp(vl,p,*c,pp);
1.5 noro 484: }
485:
486: void mfctrsf(VL vl, P f, DCP *dcp)
487: {
488: DCP dc0,dc,dct,dcs,dcr;
489: Obj obj;
490:
491: simp_ff((Obj)f,&obj); f = (P)obj;
492: sqfrsf(vl,f,&dct);
493: dc = dc0 = dct; dct = NEXT(dct); NEXT(dc) = 0;
494: for ( ; dct; dct = NEXT(dct) ) {
495: mfctrsfmain(vl,COEF(dct),&dcs);
496: for ( dcr = dcs; dcr; dcr = NEXT(dcr) )
497: DEG(dcr) = DEG(dct);
498: for ( ; NEXT(dc); dc = NEXT(dc) );
499: NEXT(dc) = dcs;
500: }
501: *dcp = dc0;
502: }
503:
504: /* f : sqfr, non const */
505:
506: void mfctrsfmain(VL vl, P f, DCP *dcp)
507: {
1.6 noro 508: VL tvl,nvl,rvl;
1.7 noro 509: DCP dc,dc0,dc1,dc2,dct,lcfdc,dcs;
510: int imin,inext,i,j,n,k,np;
1.5 noro 511: int *da;
512: V vx,vy;
513: V *va;
1.7 noro 514: P *l,*tl;
1.5 noro 515: P gcd,g,df,dfmin;
516: P pa[2];
1.10 noro 517: P f0,pp0,spp0,c,c0,x,y,u,v,lcf,lcu,lcv,u0,v0,t,s;
1.12 ! noro 518: P ype,yme,fin;
1.6 noro 519: GFS ev,evy;
520: P *fp0;
521: int *mev,*win;
1.5 noro 522:
523: clctv(vl,f,&tvl); vl = tvl;
524: if ( !vl )
525: error("mfctrsfmain : cannot happen");
526: if ( !NEXT(vl) ) {
527: /* univariate */
528: ufctrsf(f,&dc);
529: /* remove lc */
530: *dcp = NEXT(dc);
531: return;
532: }
533: for ( n = 0, tvl = vl; tvl; tvl = NEXT(tvl), n++ );
534: va = (V *)ALLOCA(n*sizeof(int));
535: da = (int *)ALLOCA(n*sizeof(int));
536: /* find v s.t. diff(f,v) is nonzero and deg(f,v) is minimal */
537: imin = -1;
538: for ( i = 0, tvl = vl; i < n; tvl = NEXT(tvl), i++ ) {
539: va[i] = tvl->v;
540: da[i] = getdeg(va[i],f);
541: diffp(vl,f,va[i],&df);
542: if ( !df )
543: continue;
544: if ( imin < 0 || da[i] < da[imin] ) {
545: dfmin = df;
546: imin = i;
547: }
548: }
549: /* find v1 neq v s.t. deg(f,v) is minimal */
550: inext = -1;
551: for ( i = 0; i < n; i++ ) {
552: if ( i == imin )
553: continue;
554: if ( inext < 0 || da[i] < da[inext] )
555: inext = i;
556: }
557: pa[0] = f;
558: pa[1] = dfmin;
1.11 noro 559: gcdsf(vl,pa,2,&gcd);
1.5 noro 560: if ( !NUM(gcd) ) {
561: /* f = gcd * f/gcd */
562: mfctrsfmain(vl,gcd,&dc1);
563: divsp(vl,f,gcd,&g);
564: mfctrsfmain(vl,g,&dc2);
565: for ( dct = dc1; NEXT(dct); dct = NEXT(dct) );
566: NEXT(dct) = dc2;
567: *dcp = dc1;
568: return;
569: }
570: /* create vl s.t. vl[0] = va[imin], vl[1] = va[inext] */
571: nvl = 0;
572: NEXTVL(nvl,tvl); tvl->v = va[imin];
573: NEXTVL(nvl,tvl); tvl->v = va[inext];
574: for ( i = 0; i < n; i++ ) {
575: if ( i == imin || i == inext )
576: continue;
577: NEXTVL(nvl,tvl); tvl->v = va[i];
578: }
579: NEXT(tvl) = 0;
580:
1.12 ! noro 581: fin = f;
1.10 noro 582: reorderp(nvl,vl,f,&g); f = g;
1.5 noro 583: vx = nvl->v;
584: vy = NEXT(nvl)->v;
1.6 noro 585: MKV(vx,x);
586: MKV(vy,y);
587: /* remaining variables */
588: rvl = NEXT(NEXT(nvl));
589: if ( !rvl ) {
1.5 noro 590: /* bivariate */
1.10 noro 591: sfbfctr(f,vx,vy,getdeg(vx,f),&dc1);
1.5 noro 592: for ( dc0 = 0; dc1; dc1 = NEXT(dc1) ) {
593: NEXTDC(dc0,dc);
594: DEG(dc) = ONE;
595: reorderp(vl,nvl,COEF(dc1),&COEF(dc));
596: }
597: NEXT(dc) = 0;
598: *dcp = dc0;
599: return;
600: }
1.6 noro 601: /* n >= 3; nvl = (vx,vy,X) */
602: /* find good evaluation pt for X */
603: mev = (int *)CALLOC(n-2,sizeof(int));
604: while ( 1 ) {
1.10 noro 605: /* lcf(mev)=0 => invalid */
606: substvp_sf(nvl,rvl,COEF(DC(f)),mev,&t);
607: if ( t ) {
608: substvp_sf(nvl,rvl,f,mev,&f0);
609: pa[0] = f0;
610: diffp(nvl,f0,vx,&pa[1]);
611: if ( pa[1] ) {
612: gcdsf(nvl,pa,2,&gcd);
1.6 noro 613: /* XXX maybe we have to accept the case where gcd is a poly of y */
1.10 noro 614: if ( NUM(gcd) )
615: break;
616: }
1.6 noro 617: }
1.7 noro 618: /* XXX if generated indices exceed q of GF(q) => error in indextogfs */
619: next_evaluation_point(mev,n-2);
1.6 noro 620: }
1.10 noro 621: /* f0 = f(x,y,mev) */
622: /* separate content; f0 may have the content wrt x */
623: cont_pp_sfp(nvl,f0,&c0,&pp0);
1.6 noro 624:
1.7 noro 625: /* factorize pp0; pp0 = pp0(x,y+evy) = prod dc */
626: sfbfctr_shift(pp0,vx,vy,getdeg(vx,pp0),&evy,&spp0,&dc); pp0 = spp0;
1.6 noro 627:
628: if ( !NEXT(dc) ) {
629: /* f is irreducible */
1.12 ! noro 630: NEWDC(dc); DEG(dc) = ONE; COEF(dc) = fin; NEXT(dc) = 0;
1.6 noro 631: *dcp = dc;
632: return;
633: }
1.7 noro 634: /* ype = y+evy, yme = y-evy */
635: addp(nvl,y,(P)evy,&ype); subp(nvl,y,(P)evy,&yme);
636:
1.6 noro 637: /* shift c0; c0 <- c0(y+evy) */
1.7 noro 638: substp(nvl,c0,vy,ype,&s); c0 = s;
639:
640: /* shift f; f <- f(y+evy) */
641: substp(nvl,f,vy,ype,&s); f = s;
642:
643: /* now f(x,0,mev) = c0 * prod dc */
1.6 noro 644:
645: /* factorize lc_x(f) */
646: lcf = COEF(DC(f));
1.7 noro 647: mfctrsf(nvl,lcf,&dct);
648: /* skip the first element (= a number) */
1.12 ! noro 649: lcfdc = NEXT(dct);
1.6 noro 650:
651: /* np = number of bivariate factors */
652: for ( np = 0, dct = dc; dct; dct = NEXT(dct), np++ );
653: fp0 = (P *)ALLOCA((np+1)*sizeof(P));
654: for ( i = 0, dct = dc; i < np; dct = NEXT(dct), i++ )
655: fp0[i] = COEF(dct);
656: fp0[np] = 0;
1.7 noro 657: l = tl = (P *)ALLOCA((np+1)*sizeof(P));
1.6 noro 658: win = W_ALLOC(np+1);
1.7 noro 659:
1.6 noro 660: for ( k = 1, win[0] = 1, --np; ; ) {
661: itogfs(1,&u0);
662: /* u0 = product of selected factors */
663: for ( i = 0; i < k; i++ ) {
664: mulp(nvl,u0,fp0[win[i]],&t); u0 = t;
665: }
666: /* we have to consider the content */
1.10 noro 667: /* f0 = c0*u0*v0 */
1.12 ! noro 668: mulp(nvl,LC(u0),c0,&c); estimatelc_sf(nvl,rvl,c,lcfdc,mev,&lcu);
1.6 noro 669: divsp(nvl,pp0,u0,&v0);
1.12 ! noro 670: mulp(nvl,LC(v0),c0,&c); estimatelc_sf(nvl,rvl,c,lcfdc,mev,&lcv);
! 671: mfctrsf_hensel(nvl,rvl,f,pp0,u0,v0,lcu,lcv,mev,&u);
1.7 noro 672: if ( u ) {
673: /* save the factor */
674: reorderp(vl,nvl,u,&t);
1.12 ! noro 675: /* y -> y-evy */
! 676: substp(vl,t,vy,yme,tl++);
1.7 noro 677:
678: /* update f,pp0 */
679: divsp(nvl,f,u,&t); f = t;
680: divsp(nvl,pp0,u0,&t); pp0 = t;
681: /* update win, fp0 */
682: for ( i = 0; i < k-1; i++ )
683: for ( j = win[i]+1; j < win[i+1]; j++ )
684: fp0[j-i-1] = fp0[j];
685: for ( j = win[k-1]+1; j <= np; j++ )
686: fp0[j-k] = fp0[j];
687: if ( ( np -= k ) < k ) break;
688: if ( np-win[0]+1 < k )
689: if ( ++k <= np ) {
690: for ( i = 0; i < k; i++ )
691: win[i] = i + 1;
692: continue;
693: } else
694: break;
695: else
696: for ( i = 1; i < k; i++ )
697: win[i] = win[0] + i;
698: } else {
699: if ( ncombi(1,np,k,win) == 0 )
700: if ( k == np ) break;
701: else
702: for ( i = 0, ++k; i < k; i++ )
703: win[i] = i + 1;
704: }
1.6 noro 705: }
1.10 noro 706: reorderp(vl,nvl,f,&t);
1.12 ! noro 707: /* y -> y-evy */
! 708: substp(vl,t,vy,yme,tl++);
1.10 noro 709: *tl = 0;
710: for ( dc0 = 0, i = 0; l[i]; i++ ) {
711: NEXTDC(dc0,dc); DEG(dc) = ONE; COEF(dc) = l[i];
712: }
713: NEXT(dc) = 0; *dcp = dc0;
1.6 noro 714: }
715:
1.7 noro 716: void next_evaluation_point(int *e,int n)
717: {
718: int i,t,j;
719:
720: for ( i = n-1; i >= 0; i-- )
721: if ( e[i] ) break;
722: if ( i < 0 ) e[n-1] = 1;
723: else if ( i == 0 ) {
724: t = e[0]; e[0] = 0; e[n-1] = t+1;
725: } else {
726: e[i-1]++; t = e[i];
727: for ( j = i; j < n-1; j++ )
728: e[j] = 0;
729: e[n-1] = t-1;
730: }
731: }
732:
733: /*
734: * dc : f1^E1*...*fk^Ek
1.12 ! noro 735: * find e1,...,ek s.t. fi(mev)^ei | c
1.7 noro 736: * and return f1^e1*...*fk^ek
737: * vl = (vx,vy,rvl)
738: */
739:
1.12 ! noro 740: void estimatelc_sf(VL vl,VL rvl,P c,DCP dc,int *mev,P *lcp)
1.7 noro 741: {
742: DCP dct;
743: P r,c1,c2,t,s,f;
744: int i,d;
745: Q q;
746:
747: for ( dct = dc, r = (P)ONE; dct; dct = NEXT(dct) ) {
748: if ( NUM(COEF(dct)) )
749: continue;
750: /* constant part */
1.12 ! noro 751: substvp_sf(vl,rvl,COEF(dct),mev,&f);
1.7 noro 752: d = QTOS(DEG(dct));
753: for ( i = 0, c1 = c; i < d; i++ )
754: if ( !divtp(vl,c1,f,&c2) )
755: break;
756: else
757: c1 = c2;
758: if ( i ) {
759: STOQ(i,q);
760: pwrp(vl,COEF(dct),q,&s); mulp(vl,r,s,&t); r = t;
761: }
762: }
763: *lcp = r;
764: }
765:
766: void substvp_sf(VL vl,VL rvl,P f,int *mev,P *r)
767: {
768: int i;
769: VL tvl;
770: P g,t;
771: GFS ev;
772:
773: for ( g = f, i = 0, tvl = rvl; tvl; tvl = NEXT(tvl), i++ ) {
774: if ( !mev )
775: ev = 0;
776: else
777: indextogfs(mev[i],&ev);
778: substp(vl,g,tvl->v,(P)ev,&t); g = t;
779: }
780: *r = g;
781: }
782:
783: /*
784: * f <- f(X+sgn*mev)
785: */
786:
787: void shift_sf(VL vl, VL rvl, P f, int *mev, int sgn, P *r)
788: {
789: VL tvl;
790: int i;
791: P x,g,t,s;
792: GFS ev;
793:
794: for ( g = f, tvl = rvl, i = 0; tvl; tvl = NEXT(tvl), i++ ) {
795: if ( !mev[i] )
796: continue;
797: indextogfs(mev[i],&ev);
798: MKV(tvl->v,x);
799: if ( sgn > 0 )
800: addp(vl,x,(P)ev,&t);
801: else
802: subp(vl,x,(P)ev,&t);
803: substp(vl,g,tvl->v,t,&s); g = s;
804: }
805: *r = g;
806: }
807:
808: /*
809: * pp(f(0)) = u0*v0
810: */
811:
1.12 ! noro 812: void mfctrsf_hensel(VL vl,VL rvl,P f,P pp0,P u0,P v0,P lcu,P lcv,int *mev,P *up)
1.7 noro 813: {
814: VL tvl,onevl;
815: P t,s,w,u,v,ff,si,wu,wv,fj,cont;
816: UM ydy;
817: V vx,vy;
818: int dy,n,i,dbd,nv,j;
819: int *md;
820: P *uh,*vh;
1.12 ! noro 821: P x,du0,dv0,m,q,r,fin;
1.7 noro 822: P *cu,*cv;
823: GFSN inv;
824:
825: /* adjust coeffs */
1.12 ! noro 826: /* u0 = am x^m+ ... -> lcu*x^m + a(m-1)*(lcu(mev)/am)*x^(m-1)+... */
! 827: /* v0 = bm x^l+ ... -> lcv*x^l + b(l-1)*(lcv(mev)/bl)*x^(l-1)+... */
1.10 noro 828: /* f -> lcu*lcv*x^(m+l)+... */
1.12 ! noro 829: adjust_coef_sf(vl,rvl,lcu,u0,mev,&u);
! 830: adjust_coef_sf(vl,rvl,lcv,v0,mev,&v);
1.10 noro 831: mulp(vl,lcu,lcv,&t); divsp(vl,t,LC(f),&m); mulp(vl,m,f,&t); f = t;
832:
1.12 ! noro 833: /* f <- f(X+mev), u <- u(X+mev), v <- v(X+mev) */
! 834: fin = f;
! 835: shift_sf(vl,rvl,f,mev,1,&s); f = s;
! 836: shift_sf(vl,rvl,u,mev,1,&s); u = s;
! 837: shift_sf(vl,rvl,v,mev,1,&s); v = s;
! 838:
1.7 noro 839: vx = vl->v; vy = NEXT(vl)->v;
840: n = getdeg(vx,f);
841: dy = getdeg(vy,f)+1;
842: MKV(vx,x);
843: cu = (P *)ALLOCA((n+1)*sizeof(P));
844: cv = (P *)ALLOCA((n+1)*sizeof(P));
845:
846: /* ydy = y^dy */
1.10 noro 847: ydy = C_UMALLOC(dy); DEG(ydy) = dy; COEF(ydy)[dy] = _onesf();
1.7 noro 848: setmod_gfsn(ydy);
849:
850: /* (R[y]/(y^dy))[x,X] */
1.10 noro 851: poly_to_gfsn_poly(vl,f,vy,&ff);
1.7 noro 852: poly_to_gfsn_poly(vl,u,vy,&t); u = t;
853: poly_to_gfsn_poly(vl,v,vy,&t); v = t;
854: substvp_sf(vl,rvl,u,0,&u0);
855: substvp_sf(vl,rvl,v,0,&v0);
856:
857: /* compute a(x,y), b(x,y) s.t. a*u0+b*v0 = 1 mod y^dy */
1.8 noro 858: extended_gcd_modyk(u0,v0,vx,vy,dy,&cu[0],&cv[0]);
1.7 noro 859:
860: /* dv0 = LC(v0)^(-1)*v0 mod y^dy */
861: invgfsn((GFSN)LC(v0),&inv); mulp(vl,v0,(P)inv,&dv0);
862:
863: /* cu[i]*u0+cv[i]*v0 = x^i mod y^dy */
1.10 noro 864: /* (x*cu[i])*u0+(x*cv[i])*v0 = x^(i+1) */
865: /* x*cu[i] = q*dv0+r => cu[i+1] = r */
866: /* cv[i+1]*v0 = x*cv[i]*v0+q*u0*dv0 = (x*cv[i]+q*u0*inv)*v0 */
1.7 noro 867: for ( i = 1; i <= n; i++ ) {
868: mulp(vl,x,cu[i-1],&m); divsrp(vl,m,dv0,&q,&cu[i]);
1.10 noro 869: mulp(vl,x,cv[i-1],&m); mulp(vl,q,(P)inv,&t);
870: mulp(vl,t,u0,&s);
871: addp(vl,m,s,&cv[i]);
872: }
873:
874: #if 0
875: /* XXX : check */
876: for ( i = 0; i <= n; i++ ) {
877: mulp(vl,cu[i],u0,&m); mulp(vl,cv[i],v0,&s);
878: addp(vl,m,s,&w);
879: printexpr(vl,w);
880: fprintf(asir_out,"\n");
1.7 noro 881: }
1.10 noro 882: #endif
883:
1.7 noro 884: dbd = dbound(vx,f)+1;
885:
886: /* extract homogeneous parts */
887: W_CALLOC(dbd,P,uh); W_CALLOC(dbd,P,vh);
888: for ( i = 0; i <= dbd; i++ ) {
889: exthpc(vl,vx,u,i,&uh[i]); exthpc(vl,vx,v,i,&vh[i]);
890: }
891:
892: /* register degrees in each variables */
893: for ( nv = 0, tvl = rvl; tvl; tvl = NEXT(tvl), nv++ );
894: md = (int *)ALLOCA(nv*sizeof(int));
895: for ( i = 0, tvl = rvl; i < nv; tvl = NEXT(tvl), i++ )
1.10 noro 896: md[i] = getdeg(tvl->v,f);
1.7 noro 897:
898: /* XXX for removing content of factor wrt vx */
899: NEWVL(onevl); onevl->v = vx; NEXT(onevl) = 0;
900:
901: for ( j = 1; j <= dbd; j++ ) {
902: for ( i = 0, tvl = rvl; i < nv; tvl = NEXT(tvl), i++ )
903: if ( getdeg(tvl->v,u)+getdeg(tvl->v,v) > md[i] ) {
904: *up = 0;
905: return;
906: }
907: for ( i = 0, t = 0; i <= j; i++ ) {
908: mulp(vl,uh[i],vh[j-i],&s); addp(vl,s,t,&w); t = w;
909: }
1.10 noro 910:
1.7 noro 911: /* s = degree j part of (f-uv) */
912: exthpc(vl,vx,ff,j,&fj); subp(vl,fj,t,&s);
913: for ( i = 0, wu = 0, wv = 0; i <= n; i++ ) {
1.10 noro 914: if ( !s )
1.7 noro 915: si = 0;
916: else if ( VR(s) == vx )
917: coefp(s,i,&si);
918: else if ( i == 0 )
919: si = s;
920: else
921: si = 0;
922: if ( si ) {
1.10 noro 923: mulp(vl,si,cv[i],&m); addp(vl,wu,m,&t); wu = t;
924: mulp(vl,si,cu[i],&m); addp(vl,wv,m,&t); wv = t;
1.7 noro 925: }
926: }
927: if ( !wu ) {
1.10 noro 928: gfsn_poly_to_poly(vl,u,vy,&t);
1.12 ! noro 929: shift_sf(vl,rvl,t,mev,-1,&s);
! 930: if ( divtp(vl,fin,s,&q) ) {
! 931: cont_pp_mv_sf(vl,onevl,s,&cont,up);
1.7 noro 932: return;
933: }
934: }
935: if ( !wv ) {
1.10 noro 936: gfsn_poly_to_poly(vl,v,vy,&t);
1.12 ! noro 937: shift_sf(vl,rvl,t,mev,-1,&s);
! 938: if ( divtp(vl,fin,s,&q) ) {
1.7 noro 939: cont_pp_mv_sf(vl,onevl,q,&cont,up);
940: return;
941: }
942: }
943: addp(vl,u,wu,&t); u = t;
944: addp(vl,uh[j],wu,&t); uh[j] = t;
945: addp(vl,v,wv,&t); v = t;
946: addp(vl,vh[j],wv,&t); vh[j] = t;
947: }
948: }
949:
1.12 ! noro 950: void adjust_coef_sf(VL vl,VL rvl,P lcu,P u0,int *mev,P *r)
1.7 noro 951: {
952: P lcu0,cu;
953: DCP dc0,dcu,dc;
954:
1.12 ! noro 955: substvp_sf(vl,rvl,lcu,mev,&lcu0);
1.7 noro 956: divsp(vl,lcu0,LC(u0),&cu);
957: for ( dc0 = 0, dcu = DC(u0); dcu; dcu = NEXT(dcu) ) {
958: if ( !dc0 ) {
959: NEXTDC(dc0,dc);
960: COEF(dc) = lcu;
961: } else {
962: NEXTDC(dc0,dc);
963: mulp(vl,cu,COEF(dcu),&COEF(dc));
964: }
965: DEG(dc) = DEG(dcu);
966: }
967: NEXT(dc) = 0;
968: MKP(VR(u0),dc0,*r);
969: }
970:
1.8 noro 971: void extended_gcd_modyk(P u0,P v0,V x,V y,int dy,P *cu,P *cv)
1.6 noro 972: {
1.8 noro 973: BM g,h,a,b;
974:
975: gfsn_univariate_to_sfbm(u0,dy,&g);
976: gfsn_univariate_to_sfbm(v0,dy,&h);
977: sfexgcd_by_hensel(g,h,dy,&a,&b);
978: sfbm_to_gfsn_univariate(a,x,y,cu);
979: sfbm_to_gfsn_univariate(b,x,y,cv);
980: }
981:
982: /* (F[y])[x] -> F[x][y] */
983:
984: void gfsn_univariate_to_sfbm(P f,int dy,BM *r)
985: {
986: int dx,d,i;
987: BM b;
988: UM cy;
989: DCP dc;
990:
991: dx = getdeg(VR(f),f);
992: b = BMALLOC(dx,dy);
993: DEG(b) = dy;
994: for ( dc = DC(f); dc; dc = NEXT(dc) ) {
995: /* d : degree in x, cy : poly in y */
996: d = QTOS(DEG(dc));
997: cy = BDY((GFSN)COEF(dc));
998: for ( i = DEG(cy); i >= 0; i-- )
999: COEF(COEF(b)[i])[d] = COEF(cy)[i];
1000: }
1.9 noro 1001: for ( i = 0; i <= dy; i++ )
1002: degum(COEF(b)[i],dx);
1.8 noro 1003: *r = b;
1004: }
1005:
1006: void sfbm_to_gfsn_univariate(BM f,V x,V y,P *r)
1007: {
1008: P g;
1009: VL vl;
1010:
1011: sfbmtop(f,x,y,&g);
1012: NEWVL(vl); vl->v = x;
1013: NEWVL(NEXT(vl)); NEXT(vl)->v = y;
1014: NEXT(NEXT(vl)) = 0;
1015: poly_to_gfsn_poly(vl,g,y,r);
1.6 noro 1016: }
1017:
1.7 noro 1018: void poly_to_gfsn_poly(VL vl,P f,V v,P *r)
1.6 noro 1019: {
1.8 noro 1020: VL tvl,nvl0,nvl;
1021: P g;
1022:
1023: /* (x,y,...,v,...) -> (x,y,...,v) */
1024: for ( nvl0 = 0, tvl = vl; tvl; tvl = NEXT(tvl) ) {
1025: if ( tvl->v != v ) {
1026: NEXTVL(nvl0,nvl);
1027: nvl->v = tvl->v;
1028: }
1029: }
1030: NEXTVL(nvl0,nvl);
1031: nvl->v = v;
1032: NEXT(nvl) = 0;
1033: reorderp(nvl0,vl,f,&g);
1034: poly_to_gfsn_poly_main(g,v,r);
1035: }
1036:
1037: void poly_to_gfsn_poly_main(P f,V v,P *r)
1038: {
1039: int d;
1040: UM u;
1041: GFSN g;
1042: DCP dc,dct,dc0;
1043:
1.9 noro 1044: if ( !f )
1.8 noro 1045: *r = f;
1.9 noro 1046: else if ( NUM(f) || VR(f) == v ) {
1.8 noro 1047: d = getdeg(v,f);
1048: u = UMALLOC(d);
1049: ptosfum(f,u);
1050: MKGFSN(u,g);
1051: *r = (P)g;
1052: } else {
1053: for ( dc0 = 0, dct = DC(f); dct; dct = NEXT(dct) ) {
1054: NEXTDC(dc0,dc);
1055: DEG(dc) = DEG(dct);
1056: poly_to_gfsn_poly_main(COEF(dct),v,&COEF(dc));
1057: }
1058: NEXT(dc) = 0;
1059: MKP(VR(f),dc0,*r);
1060: }
1.6 noro 1061: }
1062:
1.7 noro 1063: void gfsn_poly_to_poly(VL vl,P f,V v,P *r)
1.6 noro 1064: {
1.8 noro 1065: VL tvl,nvl0,nvl;
1066: P g;
1067:
1068: gfsn_poly_to_poly_main(f,v,&g);
1069: /* (x,y,...,v,...) -> (x,y,...,v) */
1070: for ( nvl0 = 0, tvl = vl; tvl; tvl = NEXT(tvl) ) {
1071: if ( tvl->v != v ) {
1072: NEXTVL(nvl0,nvl);
1073: nvl->v = tvl->v;
1074: }
1075: }
1076: NEXTVL(nvl0,nvl);
1077: nvl->v = v;
1078: NEXT(nvl) = 0;
1079: reorderp(vl,nvl0,g,r);
1080: }
1081:
1082: void gfsn_poly_to_poly_main(P f,V v,P *r)
1083: {
1084: DCP dc,dc0,dct;
1085:
1086: if ( !f )
1087: *r = f;
1088: else if ( NUM(f) ) {
1089: if ( NID((Num)f) == N_GFSN )
1090: sfumtop(v,BDY((GFSN)f),r);
1091: else
1092: *r = f;
1093: } else {
1094: for ( dc0 = 0, dct = DC(f); dct; dct = NEXT(dct) ) {
1095: NEXTDC(dc0,dc);
1096: DEG(dc) = DEG(dct);
1097: gfsn_poly_to_poly_main(COEF(dct),v,&COEF(dc));
1098: }
1099: NEXT(dc) = 0;
1100: MKP(VR(f),dc0,*r);
1101: }
1.1 noro 1102: }
1.9 noro 1103:
1104: void printsfum(UM f)
1105: {
1106: int i;
1107:
1108: for ( i = DEG(f); i >= 0; i-- ) {
1109: printf("+(");
1110: printf("%d",IFTOF(COEF(f)[i]));
1111: printf(")*y^%d",i);
1112: }
1113: }
1114:
1115: void printsfbm(BM f)
1116: {
1117: int i;
1118:
1119: for ( i = DEG(f); i >= 0; i-- ) {
1120: printf("+(");
1121: printsfum(COEF(f)[i]);
1122: printf(")*y^%d",i);
1123: }
1124: }
1125:
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>