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