Annotation of OpenXM_contrib2/asir2000/lib/gr, Revision 1.14
1.5 noro 1: /*
2: * Copyright (c) 1994-2000 FUJITSU LABORATORIES LIMITED
3: * All rights reserved.
4: *
5: * FUJITSU LABORATORIES LIMITED ("FLL") hereby grants you a limited,
6: * non-exclusive and royalty-free license to use, copy, modify and
7: * redistribute, solely for non-commercial and non-profit purposes, the
8: * computer program, "Risa/Asir" ("SOFTWARE"), subject to the terms and
9: * conditions of this Agreement. For the avoidance of doubt, you acquire
10: * only a limited right to use the SOFTWARE hereunder, and FLL or any
11: * third party developer retains all rights, including but not limited to
12: * copyrights, in and to the SOFTWARE.
13: *
14: * (1) FLL does not grant you a license in any way for commercial
15: * purposes. You may use the SOFTWARE only for non-commercial and
16: * non-profit purposes only, such as academic, research and internal
17: * business use.
18: * (2) The SOFTWARE is protected by the Copyright Law of Japan and
19: * international copyright treaties. If you make copies of the SOFTWARE,
20: * with or without modification, as permitted hereunder, you shall affix
21: * to all such copies of the SOFTWARE the above copyright notice.
22: * (3) An explicit reference to this SOFTWARE and its copyright owner
23: * shall be made on your publication or presentation in any form of the
24: * results obtained by use of the SOFTWARE.
25: * (4) In the event that you modify the SOFTWARE, you shall notify FLL by
1.6 noro 26: * e-mail at risa-admin@sec.flab.fujitsu.co.jp of the detailed specification
1.5 noro 27: * for such modification or the source code of the modified part of the
28: * SOFTWARE.
29: *
30: * THE SOFTWARE IS PROVIDED AS IS WITHOUT ANY WARRANTY OF ANY KIND. FLL
31: * MAKES ABSOLUTELY NO WARRANTIES, EXPRESSED, IMPLIED OR STATUTORY, AND
32: * EXPRESSLY DISCLAIMS ANY IMPLIED WARRANTY OF MERCHANTABILITY, FITNESS
33: * FOR A PARTICULAR PURPOSE OR NONINFRINGEMENT OF THIRD PARTIES'
34: * RIGHTS. NO FLL DEALER, AGENT, EMPLOYEES IS AUTHORIZED TO MAKE ANY
35: * MODIFICATIONS, EXTENSIONS, OR ADDITIONS TO THIS WARRANTY.
36: * UNDER NO CIRCUMSTANCES AND UNDER NO LEGAL THEORY, TORT, CONTRACT,
37: * OR OTHERWISE, SHALL FLL BE LIABLE TO YOU OR ANY OTHER PERSON FOR ANY
38: * DIRECT, INDIRECT, SPECIAL, INCIDENTAL, PUNITIVE OR CONSEQUENTIAL
39: * DAMAGES OF ANY CHARACTER, INCLUDING, WITHOUT LIMITATION, DAMAGES
40: * ARISING OUT OF OR RELATING TO THE SOFTWARE OR THIS AGREEMENT, DAMAGES
41: * FOR LOSS OF GOODWILL, WORK STOPPAGE, OR LOSS OF DATA, OR FOR ANY
42: * DAMAGES, EVEN IF FLL SHALL HAVE BEEN INFORMED OF THE POSSIBILITY OF
43: * SUCH DAMAGES, OR FOR ANY CLAIM BY ANY OTHER PARTY. EVEN IF A PART
44: * OF THE SOFTWARE HAS BEEN DEVELOPED BY A THIRD PARTY, THE THIRD PARTY
45: * DEVELOPER SHALL HAVE NO LIABILITY IN CONNECTION WITH THE USE,
46: * PERFORMANCE OR NON-PERFORMANCE OF THE SOFTWARE.
47: *
1.14 ! noro 48: * $OpenXM: OpenXM_contrib2/asir2000/lib/gr,v 1.13 2001/11/19 00:57:13 noro Exp $
1.5 noro 49: */
1.1 noro 50: extern INIT_COUNT,ITOR_FAIL$
51: extern REMOTE_MATRIX,REMOTE_NF,REMOTE_VARS$
52:
53: #define MAX(a,b) ((a)>(b)?(a):(b))
54: #define HigherDim 0
55: #define ZeroDim 1
56: #define MiniPoly 2
57:
58: /* toplevel functions for Groebner basis computation */
59:
60: def gr(B,V,O)
61: {
62: G = dp_gr_main(B,V,0,1,O);
63: return G;
64: }
65:
66: def hgr(B,V,O)
67: {
68: G = dp_gr_main(B,V,1,1,O);
69: return G;
70: }
71:
72: def gr_mod(B,V,O,M)
73: {
74: G = dp_gr_mod_main(B,V,0,M,O);
75: return G;
76: }
77:
78: def hgr_mod(B,V,O,M)
79: {
80: G = dp_gr_mod_main(B,V,1,M,O);
81: return G;
82: }
83:
84: /* toplevel functions for change-of-ordering */
85:
86: def lex_hensel(B,V,O,W,H)
87: {
88: G = dp_gr_main(B,V,H,1,O);
89: return tolex(G,V,O,W);
90: }
91:
92: def lex_hensel_gsl(B,V,O,W,H)
93: {
94: G = dp_gr_main(B,V,H,1,O);
95: return tolex_gsl(G,V,O,W);
96: }
97:
98: def gr_minipoly(B,V,O,P,V0,H)
99: {
100: G = dp_gr_main(B,V,H,1,O);
101: return minipoly(G,V,O,P,V0);
102: }
103:
104: def lex_tl(B,V,O,W,H)
105: {
106: G = dp_gr_main(B,V,H,1,O);
107: return tolex_tl(G,V,O,W,H);
108: }
109:
110: def tolex_tl(G0,V,O,W,H)
111: {
112: N = length(V); HM = hmlist(G0,V,O); ZD = zero_dim(HM,V,O);
113: for ( I = 0; ; I++ ) {
114: M = lprime(I);
115: if ( !valid_modulus(HM,M) )
116: continue;
117: if ( ZD ) {
118: if ( G3 = dp_gr_main(G0,W,H,-M,3) )
119: for ( J = 0; ; J++ )
120: if ( G2 = dp_gr_main(G3,W,0,-lprime(J),2) )
121: return G2;
122: } else if ( G2 = dp_gr_main(G0,W,H,-M,2) )
123: return G2;
124: }
125: }
126:
127: def tolex(G0,V,O,W)
128: {
129: TM = TE = TNF = 0;
130: N = length(V); HM = hmlist(G0,V,O); ZD = zero_dim(HM,V,O);
131: if ( !ZD )
132: error("tolex : ideal is not zero-dimensional!");
133: MB = dp_mbase(map(dp_ptod,HM,V));
134: for ( J = 0; ; J++ ) {
135: M = lprime(J);
136: if ( !valid_modulus(HM,M) )
137: continue;
138: T0 = time()[0]; GM = tolexm(G0,V,O,W,M); TM += time()[0] - T0;
139: dp_ord(2);
140: DL = map(dp_etov,map(dp_ht,map(dp_ptod,GM,W)));
141: D = newvect(N); TL = [];
142: do
143: TL = cons(dp_dtop(dp_vtoe(D),W),TL);
144: while ( nextm(D,DL,N) );
145: L = npos_check(DL); NPOSV = L[0]; DIM = L[1];
146: T0 = time()[0]; NF = gennf(G0,TL,V,O,W[N-1],1)[0];
147: TNF += time()[0] - T0;
148: T0 = time()[0];
149: R = tolex_main(V,O,NF,GM,M,MB);
150: TE += time()[0] - T0;
151: if ( R ) {
152: if ( dp_gr_print() )
153: print("mod="+rtostr(TM)+",nf="+rtostr(TNF)+",eq="+rtostr(TE));
154: return R;
155: }
156: }
157: }
158:
159: def tolex_gsl(G0,V,O,W)
160: {
161: TM = TE = TNF = 0;
162: N = length(V); HM = hmlist(G0,V,O); ZD = zero_dim(HM,V,O);
163: MB = dp_mbase(map(dp_ptod,HM,V));
164: if ( !ZD )
165: error("tolex_gsl : ideal is not zero-dimensional!");
166: for ( J = 0; ; J++ ) {
167: M = lprime(J);
168: if ( !valid_modulus(HM,M) )
169: continue;
170: T0 = time()[0]; GM = tolexm(G0,V,O,W,M); TM += time()[0] - T0;
171: dp_ord(2);
172: DL = map(dp_etov,map(dp_ht,map(dp_ptod,GM,W)));
173: D = newvect(N); TL = [];
174: do
175: TL = cons(dp_dtop(dp_vtoe(D),W),TL);
176: while ( nextm(D,DL,N) );
177: L = npos_check(DL); NPOSV = L[0]; DIM = L[1];
178: if ( NPOSV >= 0 ) {
179: V0 = W[NPOSV];
180: T0 = time()[0]; NFL = gennf(G0,TL,V,O,V0,1);
181: TNF += time()[0] - T0;
182: T0 = time()[0];
183: R = tolex_gsl_main(G0,V,O,W,NFL,NPOSV,GM,M,MB);
184: TE += time()[0] - T0;
185: } else {
186: T0 = time()[0]; NF = gennf(G0,TL,V,O,W[N-1],1)[0];
187: TNF += time()[0] - T0;
188: T0 = time()[0];
189: R = tolex_main(V,O,NF,GM,M,MB);
190: TE += time()[0] - T0;
191: }
192: if ( R ) {
193: if ( dp_gr_print() )
194: print("mod="+rtostr(TM)+",nf="+rtostr(TNF)+",eq="+rtostr(TE));
195: return R;
196: }
197: }
198: }
199:
200: def termstomat(NF,TERMS,MB,MOD)
201: {
202: DN = NF[1];
203: NF = NF[0];
204: N = length(MB);
205: M = length(TERMS);
206: MAT = newmat(N,M);
207: W = newvect(N);
208: Len = length(NF);
209: for ( I = 0; I < M; I++ ) {
210: T = TERMS[I];
211: for ( K = 0; K < Len; K++ )
212: if ( T == NF[K][1] )
213: break;
214: dptov(NF[K][0],W,MB);
215: for ( J = 0; J < N; J++ )
216: MAT[J][I] = W[J];
217: }
218: return [henleq_prep(MAT,MOD),DN];
219: }
220:
221: def tolex_gsl_main(G0,V,O,W,NFL,NPOSV,GM,M,MB)
222: {
223: NF = NFL[0]; PS = NFL[1]; GI = NFL[2];
224: V0 = W[NPOSV]; N = length(W);
225: DIM = length(MB);
226: DV = newvect(DIM);
227: TERMS = gather_terms(GM,W,M,NPOSV);
228: Len = length(TERMS);
229: dp_ord(O); RHS = termstomat(NF,map(dp_ptod,TERMS,V),MB,M);
230: for ( T = GM; T != []; T = cdr(T) )
231: if ( vars(car(T)) == [V0] )
232: break;
233: dp_ord(0); NHT = nf_tab_gsl(dp_ptod(V0^deg(car(T),V0),V),NF);
234: dptov(NHT[0],DV,MB);
235: B = hen_ttob_gsl([DV,NHT[1]],RHS,TERMS,M);
236: if ( !B )
237: return 0;
238: for ( I = 0, U = B[1]*V0^deg(car(T),V0); I < Len; I++ )
239: U += B[0][I]*TERMS[I];
240: DN0 = diff(U,V0);
241: dp_ord(O); DN0NF = nf_tab_gsl(dp_ptod(DN0,V),NF);
242: SL = [[V0,U,DN0]];
243: for ( I = N-1, LCM = 1; I >= 0; I-- ) {
244: if ( I == NPOSV )
245: continue;
246: V1 = W[I];
247: dp_ord(O); L = nf(GI,DN0NF[0]*dp_ptod(-LCM*V1,V),DN0NF[1],PS);
248: L = remove_cont(L);
249: dptov(L[0],DV,MB);
250: dp_ord(O); B = hen_ttob_gsl([DV,L[1]],RHS,TERMS,M);
251: if ( !B )
252: return 0;
253: for ( K = 0, R = 0; K < Len; K++ )
254: R += B[0][K]*TERMS[K];
255: LCM *= B[1];
256: SL = cons(cons(V1,[R,LCM]),SL);
1.7 noro 257: if ( dp_gr_print() )
258: print(["DN",B[1]]);
1.1 noro 259: }
260: return SL;
261: }
262:
263: def hen_ttob_gsl(LHS,RHS,TERMS,M)
264: {
265: LDN = LHS[1]; RDN = RHS[1]; LCM = ilcm(LDN,RDN);
266: L1 = idiv(LCM,LDN); R1 = idiv(LCM,RDN);
267: T0 = time()[0];
268: S = henleq_gsl(RHS[0],LHS[0]*L1,M);
1.7 noro 269: if ( dp_gr_print() )
270: print(["henleq_gsl",time()[0]-T0]);
1.1 noro 271: N = length(TERMS);
272: return [S[0],S[1]*R1];
273: }
274:
275: def gather_terms(GM,W,M,NPOSV)
276: {
277: N = length(W); V0 = W[NPOSV];
278: for ( T = GM; T != []; T = cdr(T) ) {
279: if ( vars(car(T)) == [V0] )
280: break;
281: }
282: U = car(T); DU = diff(U,V0);
283: R = tpoly(cdr(p_terms(U,W,2)));
284: for ( I = 0; I < N; I++ ) {
285: if ( I == NPOSV )
286: continue;
287: V1 = W[I];
288: for ( T = GM; T != []; T = cdr(T) )
289: if ( member(V1,vars(car(T))) )
290: break;
291: P = car(T);
292: R += tpoly(p_terms(srem(DU*coef(P,0,V1),U,M),W,2));
293: }
294: return p_terms(R,W,2);
295: }
296:
297: def tpoly(L)
298: {
299: for ( R = 0; L != []; L = cdr(L) )
300: R += car(L);
301: return R;
302: }
303:
304: def dptov(P,W,MB)
305: {
306: N = size(W)[0];
307: for ( I = 0; I < N; I++ )
308: W[I] = 0;
309: for ( I = 0, S = MB; P; P = dp_rest(P) ) {
310: HM = dp_hm(P); C = dp_hc(HM); T = dp_ht(HM);
311: for ( ; T != car(S); S = cdr(S), I++ );
312: W[I] = C;
313: I++; S = cdr(S);
314: }
315: }
316:
317: def tolex_main(V,O,NF,GM,M,MB)
318: {
319: DIM = length(MB);
320: DV = newvect(DIM);
321: for ( T = GM, SL = [], LCM = 1; T != []; T = cdr(T) ) {
322: S = p_terms(car(T),V,2);
323: dp_ord(O); RHS = termstomat(NF,map(dp_ptod,cdr(S),V),MB,M);
324: dp_ord(0); NHT = nf_tab_gsl(dp_ptod(LCM*car(S),V),NF);
325: dptov(NHT[0],DV,MB);
326: dp_ord(O); B = hen_ttob_gsl([DV,NHT[1]],RHS,cdr(S),M);
327: if ( !B )
328: return 0;
329: Len = length(S);
330: LCM *= B[1];
331: for ( U = LCM*car(S), I = 1; I < Len; I++ )
332: U += B[0][I-1]*S[I];
333: R = ptozp(U);
334: SL = cons(R,SL);
1.7 noro 335: if ( dp_gr_print() )
336: print(["DN",B[1]]);
1.1 noro 337: }
338: return SL;
339: }
340:
341: def reduce_dn(L)
342: {
343: NM = L[0]; DN = L[1]; V = vars(NM);
344: T = remove_cont([dp_ptod(NM,V),DN]);
345: return [dp_dtop(T[0],V),T[1]];
346: }
347:
348: /* a function for computation of minimal polynomial */
349:
350: def minipoly(G0,V,O,P,V0)
351: {
352: if ( !zero_dim(hmlist(G0,V,O),V,O) )
353: error("tolex : ideal is not zero-dimensional!");
354:
355: G1 = cons(V0-P,G0);
356: O1 = [[0,1],[O,length(V)]];
357: V1 = cons(V0,V);
358: W = append(V,[V0]);
359:
360: N = length(V1);
361: dp_ord(O1);
362: HM = hmlist(G1,V1,O1);
363: MB = dp_mbase(map(dp_ptod,HM,V1));
364: dp_ord(O);
365:
366: for ( J = 0; ; J++ ) {
367: M = lprime(J);
368: if ( !valid_modulus(HM,M) )
369: continue;
370: MP = minipolym(G0,V,O,P,V0,M);
371: for ( D = deg(MP,V0), TL = [], J = 0; J <= D; J++ )
372: TL = cons(V0^J,TL);
373: NF = gennf(G1,TL,V1,O1,V0,1)[0];
374: R = tolex_main(V1,O1,NF,[MP],M,MB);
375: return R[0];
376: }
377: }
378:
379: /* subroutines */
380:
381: def gennf(G,TL,V,O,V0,FLAG)
382: {
383: N = length(V); Len = length(G); dp_ord(O); PS = newvect(Len);
384: for ( I = 0, T = G, HL = []; T != []; T = cdr(T), I++ ) {
385: PS[I] = dp_ptod(car(T),V); HL = cons(dp_ht(PS[I]),HL);
386: }
387: for ( I = 0, DTL = []; TL != []; TL = cdr(TL) )
388: DTL = cons(dp_ptod(car(TL),V),DTL);
389: for ( I = Len - 1, GI = []; I >= 0; I-- )
390: GI = cons(I,GI);
391: T = car(DTL); DTL = cdr(DTL);
392: H = [nf(GI,T,T,PS)];
393:
394: USE_TAB = (FLAG != 0);
395: if ( USE_TAB ) {
396: T0 = time()[0];
397: MB = dp_mbase(HL); DIM = length(MB);
398: U = dp_ptod(V0,V);
399: UTAB = newvect(DIM);
400: for ( I = 0; I < DIM; I++ ) {
401: UTAB[I] = [MB[I],remove_cont(dp_true_nf(GI,U*MB[I],PS,1))];
402: if ( dp_gr_print() )
403: print(".",2);
404: }
1.7 noro 405: if ( dp_gr_print() )
406: print("");
1.1 noro 407: TTAB = time()[0]-T0;
408: }
409:
410: T0 = time()[0];
411: for ( LCM = 1; DTL != []; ) {
412: if ( dp_gr_print() )
413: print(".",2);
414: T = car(DTL); DTL = cdr(DTL);
415: if ( L = search_redble(T,H) ) {
416: DD = dp_subd(T,L[1]);
417: if ( USE_TAB && (DD == U) ) {
418: NF = nf_tab(L[0],UTAB);
419: NF = [NF[0],dp_hc(L[1])*NF[1]*T];
420: } else
421: NF = nf(GI,L[0]*dp_subd(T,L[1]),dp_hc(L[1])*T,PS);
422: } else
423: NF = nf(GI,T,T,PS);
424: NF = remove_cont(NF);
425: H = cons(NF,H);
426: LCM = ilcm(LCM,dp_hc(NF[1]));
427: }
428: TNF = time()[0]-T0;
429: if ( dp_gr_print() )
430: print("gennf(TAB="+rtostr(TTAB)+" NF="+rtostr(TNF)+")");
431: return [[map(adj_dn,H,LCM),LCM],PS,GI];
432: }
433:
434: def adj_dn(P,D)
435: {
436: return [(idiv(D,dp_hc(P[1])))*P[0],dp_ht(P[1])];
437: }
438:
439: def hen_ttob(T,NF,LHS,V,MOD)
440: {
441: if ( length(T) == 1 )
442: return car(T);
443: T0 = time()[0]; M = etom(leq_nf(T,NF,LHS,V)); TE = time()[0] - T0;
444: T0 = time()[0]; U = henleq(M,MOD); TH = time()[0] - T0;
445: if ( dp_gr_print() ) {
446: print("(etom="+rtostr(TE)+" hen="+rtostr(TH)+")");
447: }
448: return U ? vtop(T,U,LHS) : 0;
449: }
450:
451: def vtop(S,L,GSL)
452: {
453: U = L[0]; H = L[1];
454: if ( GSL ) {
455: for ( A = 0, I = 0; S != []; S = cdr(S), I++ )
456: A += U[I]*car(S);
457: return [A,H];
458: } else {
459: for ( A = H*car(S), S = cdr(S), I = 0; S != []; S = cdr(S), I++ )
460: A += U[I]*car(S);
461: return ptozp(A);
462: }
463: }
464:
465: def leq_nf(TL,NF,LHS,V)
466: {
467: TLen = length(NF);
468: T = newvect(TLen); M = newvect(TLen);
469: for ( I = 0; I < TLen; I++ ) {
470: T[I] = dp_ht(NF[I][1]);
471: M[I] = dp_hc(NF[I][1]);
472: }
473: Len = length(TL); INDEX = newvect(Len); COEF = newvect(Len);
474: for ( L = TL, J = 0; L != []; L = cdr(L), J++ ) {
475: D = dp_ptod(car(L),V);
476: for ( I = 0; I < TLen; I++ )
477: if ( D == T[I] )
478: break;
479: INDEX[J] = I; COEF[J] = strtov("u"+rtostr(J));
480: }
481: if ( !LHS ) {
482: COEF[0] = 1; NM = 0; DN = 1;
483: } else {
484: NM = LHS[0]; DN = LHS[1];
485: }
486: for ( J = 0, S = -NM; J < Len; J++ ) {
487: DNJ = M[INDEX[J]];
488: GCD = igcd(DN,DNJ); CS = DNJ/GCD; CJ = DN/GCD;
489: S = CS*S + CJ*NF[INDEX[J]][0]*COEF[J];
490: DN *= CS;
491: }
492: for ( D = S, E = []; D; D = dp_rest(D) )
493: E = cons(dp_hc(D),E);
494: BOUND = LHS ? 0 : 1;
495: for ( I = Len - 1, W = []; I >= BOUND; I-- )
496: W = cons(COEF[I],W);
497: return [E,W];
498: }
499:
500: def nf_tab(F,TAB)
501: {
502: for ( NM = 0, DN = 1, I = 0; F; F = dp_rest(F) ) {
503: T = dp_ht(F);
504: for ( ; TAB[I][0] != T; I++);
505: NF = TAB[I][1]; N = NF[0]; D = NF[1];
506: G = igcd(DN,D); DN1 = idiv(DN,G); D1 = idiv(D,G);
507: NM = D1*NM + DN1*dp_hc(F)*N; DN *= D1;
508: }
509: return [NM,DN];
510: }
511:
512: def nf_tab_gsl(A,NF)
513: {
514: DN = NF[1];
515: NF = NF[0];
516: TLen = length(NF);
517: for ( R = 0; A; A = dp_rest(A) ) {
518: HM = dp_hm(A); C = dp_hc(HM); T = dp_ht(HM);
519: for ( I = 0; I < TLen; I++ )
520: if ( NF[I][1] == T )
521: break;
522: R += C*NF[I][0];
523: }
524: return remove_cont([R,DN]);
525: }
526:
527: def redble(D1,D2,N)
528: {
529: for ( I = 0; I < N; I++ )
530: if ( D1[I] > D2[I] )
531: break;
532: return I == N ? 1 : 0;
533: }
534:
535: def tolexm(G,V,O,W,M)
536: {
537: N = length(V); Len = length(G);
538: dp_ord(O); setmod(M); PS = newvect(Len);
539: for ( I = 0, T = G; T != []; T = cdr(T), I++ )
540: PS[I] = dp_mod(dp_ptod(car(T),V),M,[]);
541: for ( I = Len-1, HL = []; I >= 0; I-- )
542: HL = cons(dp_ht(PS[I]),HL);
543: G2 = tolexm_main(PS,HL,V,W,M,ZeroDim);
544: L = map(dp_dtop,G2,V);
545: return L;
546: }
547:
548: def tolexm_main(PS,HL,V,W,M,FLAG)
549: {
550: N = length(W); D = newvect(N); Len = size(PS)[0];
551: for ( I = Len - 1, GI = []; I >= 0; I-- )
552: GI = cons(I,GI);
553: MB = dp_mbase(HL); DIM = length(MB);
554: U = dp_mod(dp_ptod(W[N-1],V),M,[]);
555: UTAB = newvect(DIM);
556: for ( I = 0; I < DIM; I++ ) {
557: if ( dp_gr_print() )
558: print(".",2);
559: UTAB[I] = [MB[I],dp_nf_mod(GI,U*dp_mod(MB[I],M,[]),PS,1,M)];
560: }
1.7 noro 561: if ( dp_gr_print() )
562: print("");
1.1 noro 563: T = dp_mod(dp_ptod(dp_dtop(dp_vtoe(D),W),V),M,[]);
564: H = G = [[T,T]];
565: DL = []; G2 = [];
566: TNF = 0;
567: while ( 1 ) {
568: if ( dp_gr_print() )
569: print(".",2);
570: S = nextm(D,DL,N);
571: if ( !S )
572: break;
573: T = dp_mod(dp_ptod(dp_dtop(dp_vtoe(D),W),V),M,[]);
574: T0 = time()[0];
575: if ( L = search_redble(T,H) ) {
576: DD = dp_mod(dp_subd(T,L[1]),M,[]);
577: if ( DD == U )
578: NT = dp_nf_tab_mod(L[0],UTAB,M);
579: else
580: NT = dp_nf_mod(GI,L[0]*DD,PS,1,M);
581: } else
582: NT = dp_nf_mod(GI,T,PS,1,M);
583: TNF += time()[0] - T0;
584: H = cons([NT,T],H);
585: T0 = time()[0];
586: L = dp_lnf_mod([NT,T],G,M); N1 = L[0]; N2 = L[1];
587: TLNF += time()[0] - T0;
588: if ( !N1 ) {
589: G2 = cons(N2,G2);
590: if ( FLAG == MiniPoly )
591: break;
592: D1 = newvect(N);
593: for ( I = 0; I < N; I++ )
594: D1[I] = D[I];
595: DL = cons(D1,DL);
596: } else
597: G = insert(G,L);
598: }
599: if ( dp_gr_print() )
600: print("tolexm(nfm="+rtostr(TNF)+" lnfm="+rtostr(TLNF)+")");
601: return G2;
602: }
603:
604: def minipolym(G,V,O,P,V0,M)
605: {
606: N = length(V); Len = length(G);
607: dp_ord(O); setmod(M); PS = newvect(Len);
608: for ( I = 0, T = G; T != []; T = cdr(T), I++ )
609: PS[I] = dp_mod(dp_ptod(car(T),V),M,[]);
610: for ( I = Len-1, HL = []; I >= 0; I-- )
611: HL = cons(dp_ht(PS[I]),HL);
612: for ( I = Len - 1, GI = []; I >= 0; I-- )
613: GI = cons(I,GI);
614: MB = dp_mbase(HL); DIM = length(MB); UT = newvect(DIM);
615: U = dp_mod(dp_ptod(P,V),M,[]);
616: for ( I = 0; I < DIM; I++ )
617: UT[I] = [MB[I],dp_nf_mod(GI,U*dp_mod(MB[I],M,[]),PS,1,M)];
618: T = dp_mod(<<0>>,M,[]); TT = dp_mod(dp_ptod(1,V),M,[]);
619: G = H = [[TT,T]]; TNF = TLNF = 0;
620: for ( I = 1; ; I++ ) {
621: T = dp_mod(<<I>>,M,[]);
622: T0 = time()[0]; NT = dp_nf_tab_mod(H[0][0],UT,M); TNF += time()[0] - T0;
623: H = cons([NT,T],H);
624: T0 = time()[0]; L = dp_lnf_mod([NT,T],G,M); TLNF += time()[0] - T0;
625: if ( !L[0] ) {
626: if ( dp_gr_print() ) print(["nfm",TNF,"lnfm",TLNF]);
627: return dp_dtop(L[1],[V0]);
628: } else
629: G = insert(G,L);
630: }
631: }
632:
633: def nextm(D,DL,N)
634: {
635: for ( I = N-1; I >= 0; ) {
636: D[I]++;
637: for ( T = DL; T != []; T = cdr(T) )
638: if ( car(T) == D )
639: return 1;
640: else if ( redble(car(T),D,N) )
641: break;
642: if ( T != [] ) {
643: for ( J = N-1; J >= I; J-- )
644: D[J] = 0;
645: I--;
646: } else
647: break;
648: }
649: if ( I < 0 )
650: return 0;
651: else
652: return 1;
653: }
654:
655: def search_redble(T,G)
656: {
657: for ( ; G != []; G = cdr(G) )
658: if ( dp_redble(T,car(G)[1]) )
659: return car(G);
660: return 0;
661: }
662:
663: def insert(G,A)
664: {
665: if ( G == [] )
666: return [A];
667: else if ( dp_ht(car(A)) > dp_ht(car(car(G))) )
668: return cons(A,G);
669: else
670: return cons(car(G),insert(cdr(G),A));
671: }
672:
673: #if 0
674: def etom(L) {
675: E = L[0]; W = L[1];
676: LE = length(E); LW = length(W);
677: M = newmat(LE,LW+1);
678: for(J=0;J<LE;J++) {
679: for ( T = E[J]; T && (type(T) == 2); )
680: for ( V = var(T), I = 0; I < LW; I++ )
681: if ( V == W[I] ) {
682: M[J][I] = coef(T,1,V);
683: T = coef(T,0,V);
684: }
685: M[J][LW] = T;
686: }
687: return M;
688: }
689: #endif
690:
691: def etom(L) {
692: E = L[0]; W = L[1];
693: LE = length(E); LW = length(W);
694: M = newmat(LE,LW+1);
695: for(J=0;J<LE;J++) {
696: for ( I = 0, T = E[J]; I < LW; I++ ) {
697: M[J][I] = coef(T,1,W[I]); T = coef(T,0,W[I]);
698: }
699: M[J][LW] = T;
700: }
701: return M;
702: }
703:
704: def calcb_old(M) {
705: N = 2*M;
706: T = gr_sqrt(N);
707: if ( T^2 <= N && N < (T+1)^2 )
708: return idiv(T,2);
709: else
710: error("afo");
711: }
712:
713: def calcb_special(PK,P,K) { /* PK = P^K */
714: N = 2*PK;
715: T = sqrt_special(N,2,P,K);
716: if ( T^2 <= N && N < (T+1)^2 )
717: return idiv(T,2);
718: else
719: error("afo");
720: }
721:
722: def sqrt_special(A,C,M,K) { /* A = C*M^K */
723: L = idiv(K,2); B = M^L;
724: if ( K % 2 )
725: C *= M;
726: D = 2^K; X = idiv((gr_sqrt(C*D^2)+1)*B,D)+1;
727: while ( 1 )
728: if ( (Y = X^2) <= A )
729: return X;
730: else
731: X = idiv(A + Y,2*X);
732: }
733:
734: def gr_sqrt(A) {
735: for ( J = 0, T = A; T >= 2^27; J++ ) {
736: T = idiv(T,2^27)+1;
737: }
738: for ( I = 0; T >= 2; I++ ) {
739: S = idiv(T,2);
740: if ( T = S+S )
741: T = S;
742: else
743: T = S+1;
744: }
745: X = (2^27)^idiv(J,2)*2^idiv(I,2);
746: while ( 1 ) {
747: if ( (Y=X^2) < A )
748: X += X;
749: else if ( Y == A )
750: return X;
751: else
752: break;
753: }
754: while ( 1 )
755: if ( (Y = X^2) <= A )
756: return X;
757: else
758: X = idiv(A + Y,2*X);
759: }
760:
761: #define ABS(a) ((a)>=0?(a):(-a))
762:
763: def inttorat_asir(C,M,B)
764: {
765: if ( M < 0 )
766: M = -M;
767: C %= M;
768: if ( C < 0 )
769: C += M;
770: U1 = 0; U2 = M; V1 = 1; V2 = C;
771: while ( V2 >= B ) {
772: L = iqr(U2,V2); Q = L[0]; R2 = L[1];
773: R1 = U1 - Q*V1;
774: U1 = V1; U2 = V2;
775: V1 = R1; V2 = R2;
776: }
777: if ( ABS(V1) >= B )
778: return 0;
779: else
780: if ( V1 < 0 )
781: return [-V2,-V1];
782: else
783: return [V2,V1];
784: }
785:
786: def intvtoratv(V,M,B) {
787: if ( !B )
788: B = 1;
789: N = size(V)[0];
790: W = newvect(N);
791: if ( ITOR_FAIL >= 0 ) {
792: if ( V[ITOR_FAIL] ) {
793: T = inttorat(V[ITOR_FAIL],M,B);
794: if ( !T ) {
795: if ( dp_gr_print() ) {
796: print("F",2);
797: }
798: return 0;
799: }
800: }
801: }
802: for ( I = 0, DN = 1; I < N; I++ )
803: if ( V[I] ) {
804: T = inttorat((V[I]*DN) % M,M,B);
805: if ( !T ) {
806: ITOR_FAIL = I;
807: if ( dp_gr_print() ) {
808: #if 0
809: print("intvtoratv : failed at I = ",0); print(ITOR_FAIL);
810: #endif
811: print("F",2);
812: }
813: return 0;
814: } else {
815: for( J = 0; J < I; J++ )
816: W[J] *= T[1];
817: W[I] = T[0]; DN *= T[1];
818: }
819: }
820: return [W,DN];
821: }
822:
823: def nf(B,G,M,PS)
824: {
825: for ( D = 0; G; ) {
826: for ( U = 0, L = B; L != []; L = cdr(L) ) {
827: if ( dp_redble(G,R=PS[car(L)]) > 0 ) {
828: GCD = igcd(dp_hc(G),dp_hc(R));
829: CG = idiv(dp_hc(R),GCD); CR = idiv(dp_hc(G),GCD);
830: U = CG*G-dp_subd(G,R)*CR*R;
831: if ( !U )
832: return [D,M];
833: D *= CG; M *= CG;
834: break;
835: }
836: }
837: if ( U )
838: G = U;
839: else {
840: D += dp_hm(G); G = dp_rest(G);
841: }
842: }
843: return [D,M];
844: }
845:
846: def remove_cont(L)
847: {
848: if ( type(L[1]) == 1 ) {
849: T = remove_cont([L[0],L[1]*<<0>>]);
850: return [T[0],dp_hc(T[1])];
851: } else if ( !L[0] )
852: return [0,dp_ptozp(L[1])];
853: else if ( !L[1] )
854: return [dp_ptozp(L[0]),0];
855: else {
856: A0 = dp_ptozp(L[0]); A1 = dp_ptozp(L[1]);
857: C0 = idiv(dp_hc(L[0]),dp_hc(A0)); C1 = idiv(dp_hc(L[1]),dp_hc(A1));
858: GCD = igcd(C0,C1); M0 = idiv(C0,GCD); M1 = idiv(C1,GCD);
859: return [M0*A0,M1*A1];
860: }
861: }
862:
863: def union(A,B)
864: {
865: for ( T = B; T != []; T = cdr(T) )
866: A = union1(A,car(T));
867: return A;
868: }
869:
870: def union1(A,E)
871: {
872: if ( A == [] )
873: return [E];
874: else if ( car(A) == E )
875: return A;
876: else
877: return cons(car(A),union1(cdr(A),E));
878: }
879:
880: def setminus(A,B) {
881: for ( T = reverse(A), R = []; T != []; T = cdr(T) ) {
882: for ( S = B, M = car(T); S != []; S = cdr(S) )
883: if ( car(S) == M )
884: break;
885: if ( S == [] )
886: R = cons(M,R);
887: }
888: return R;
889: }
890:
891: def member(A,L) {
892: for ( ; L != []; L = cdr(L) )
893: if ( A == car(L) )
894: return 1;
895: return 0;
896: }
897:
898: /* several functions for computation of normal forms etc. */
899:
900: def p_nf(P,B,V,O) {
901: dp_ord(O); DP = dp_ptod(P,V);
902: N = length(B); DB = newvect(N);
903: for ( I = N-1, IL = []; I >= 0; I-- ) {
904: DB[I] = dp_ptod(B[I],V);
905: IL = cons(I,IL);
906: }
907: return dp_dtop(dp_nf(IL,DP,DB,1),V);
908: }
909:
910: def p_true_nf(P,B,V,O) {
911: dp_ord(O); DP = dp_ptod(P,V);
912: N = length(B); DB = newvect(N);
913: for ( I = N-1, IL = []; I >= 0; I-- ) {
914: DB[I] = dp_ptod(B[I],V);
915: IL = cons(I,IL);
916: }
917: L = dp_true_nf(IL,DP,DB,1);
918: return [dp_dtop(L[0],V),L[1]];
1.12 noro 919: }
920:
921: def p_nf_mod(P,B,V,O,Mod) {
922: setmod(Mod);
923: dp_ord(O); DP = dp_mod(dp_ptod(P,V),Mod,[]);
924: N = length(B); DB = newvect(N);
925: for ( I = N-1, IL = []; I >= 0; I-- ) {
926: DB[I] = dp_mod(dp_ptod(B[I],V),Mod,[]);
927: IL = cons(I,IL);
928: }
929: return dp_dtop(dp_nf_mod(IL,DP,DB,1,Mod),V);
1.1 noro 930: }
931:
932: def p_terms(D,V,O)
933: {
934: dp_ord(O);
935: for ( L = [], T = dp_ptod(D,V); T; T = dp_rest(T) )
936: L = cons(dp_dtop(dp_ht(T),V),L);
937: return reverse(L);
938: }
939:
940: def dp_terms(D,V)
941: {
942: for ( L = [], T = D; T; T = dp_rest(T) )
943: L = cons(dp_dtop(dp_ht(T),V),L);
944: return reverse(L);
945: }
946:
947: def gb_comp(A,B)
948: {
1.8 noro 949: LA = length(A);
950: LB = length(B);
951: if ( LA != LB )
952: return 0;
953: A1 = qsort(newvect(LA,A));
954: B1 = qsort(newvect(LB,B));
955: for ( I = 0; I < LA; I++ )
956: if ( A1[I] != B1[I] && A1[I] != -B1[I] )
1.1 noro 957: break;
1.8 noro 958: return I == LA ? 1 : 0;
1.1 noro 959: }
960:
961: def zero_dim(G,V,O) {
962: dp_ord(O);
963: HL = map(dp_dtop,map(dp_ht,map(dp_ptod,G,V)),V);
964: for ( L = []; HL != []; HL = cdr(HL) )
965: if ( length(vars(car(HL))) == 1 )
966: L = cons(car(HL),L);
967: return length(vars(L)) == length(V) ? 1 : 0;
968: }
969:
970: def hmlist(G,V,O) {
971: dp_ord(O);
972: return map(dp_dtop,map(dp_hm,map(dp_ptod,G,V)),V);
973: }
974:
975: def valid_modulus(HL,M) {
976: V = vars(HL);
977: for ( T = HL; T != []; T = cdr(T) )
978: if ( !dp_mod(dp_ptod(car(T),V),M,[]) )
979: break;
980: return T == [] ? 1 : 0;
981: }
982:
983: def npos_check(DL) {
984: N = size(car(DL))[0];
985: if ( length(DL) != N )
986: return [-1,0];
987: D = newvect(N);
988: for ( I = 0; I < N; I++ ) {
989: for ( J = 0; J < N; J++ )
990: D[J] = 0;
991: D[I] = 1;
992: for ( T = DL; T != []; T = cdr(T) )
993: if ( D == car(T) )
994: break;
995: if ( T != [] )
996: DL = setminus(DL,[car(T)]);
997: }
998: if ( length(DL) != 1 )
999: return [-1,0];
1000: U = car(DL);
1001: for ( I = 0, J = 0, I0 = -1; I < N; I++ )
1002: if ( U[I] ) {
1003: I0 = I; J++;
1004: }
1005: if ( J != 1 )
1006: return [-1,0];
1007: else
1008: return [I0,U[I0]];
1009: }
1010:
1011: def mult_mat(L,TAB,MB)
1012: {
1013: A = L[0]; DN0 = L[1];
1014: for ( NM = 0, DN = 1, I = 0; A; A = dp_rest(A) ) {
1015: H = dp_ht(A);
1016: for ( ; MB[I] != H; I++ );
1017: NM1 = TAB[I][0]; DN1 = TAB[I][1]; I++;
1018: GCD = igcd(DN,DN1); C = DN1/GCD; C1 = DN/GCD;
1019: NM = C*NM + C1*dp_hc(A)*NM1;
1020: DN *= C;
1021: }
1022: Z=remove_cont([NM,DN*DN0]);
1023: return Z;
1024: }
1025:
1026: def sepm(MAT)
1027: {
1028: S = size(MAT); N = S[0]; M = S[1]-1;
1029: A = newmat(N,M); B = newvect(N);
1030: for ( I = 0; I < N; I++ )
1031: for ( J = 0, T1 = MAT[I], T2 = A[I]; J < M; J++ )
1032: T2[J] = T1[J];
1033: for ( I = 0; I < N; I++ )
1034: B[I] = MAT[I][M];
1035: return [A,B];
1036: }
1037:
1038: def henleq(M,MOD)
1039: {
1040: SIZE = size(M); ROW = SIZE[0]; COL = SIZE[1];
1041: W = newvect(COL);
1042: L = sepm(M); A = L[0]; B = L[1];
1043: COUNT = INIT_COUNT?INIT_COUNT:idiv(max_mag(M),54);
1044: if ( !COUNT )
1045: COUNT = 1;
1046:
1047: TINV = TC = TR = TS = TM = TDIV = 0;
1048:
1049: T0 = time()[0];
1050: L = geninvm_swap(A,MOD); INV = L[0]; INDEX = L[1];
1051: TS += time()[0] - T0;
1052:
1053: COL1 = COL - 1;
1054: AA = newmat(COL1,COL1); BB = newvect(COL1);
1055: for ( I = 0; I < COL1; I++ ) {
1056: for ( J = 0, T = AA[I], S = A[INDEX[I]]; J < COL1; J++ )
1057: T[J] = S[J];
1058: BB[I] = B[INDEX[I]];
1059: }
1060: if ( COL1 != ROW ) {
1061: RESTA = newmat(ROW-COL1,COL1); RESTB = newvect(ROW-COL1);
1062: for ( ; I < ROW; I++ ) {
1063: for ( J = 0, T = RESTA[I-COL1], S = A[INDEX[I]]; J < COL1; J++ )
1064: T[J] = S[J];
1065: RESTB[I-COL1] = B[INDEX[I]];
1066: }
1067: } else
1068: RESTA = RESTB = 0;
1069:
1070: MOD2 = idiv(MOD,2);
1071: for ( I = 0, C = BB, X = 0, PK = 1, CCC = 0, ITOR_FAIL = -1; ;
1072: I++, PK *= MOD ) {
1073: if ( COUNT == CCC ) {
1074: CCC = 0;
1075: T0 = time()[0];
1076: ND = intvtoratv(X,PK,ishift(calcb_special(PK,MOD,I),32));
1077: TR += time()[0]-T0;
1078: if ( ND ) {
1079: T0 = time()[0];
1080: F = ND[0]; LCM = ND[1]; T = AA*F+LCM*BB;
1081: TM += time()[0]-T0;
1082: if ( zerovector(T) ) {
1083: T0 = time()[0]; T = RESTA*F+LCM*RESTB; TM += time()[0]-T0;
1084: if ( zerovector(T) ) {
1085: #if 0
1086: if ( dp_gr_print() ) print(["init",TS,"pinv",TINV,"c",TC,"div",TDIV,"rat",TR,"mul",TM]);
1087: #endif
1088: if ( dp_gr_print() ) print("end",2);
1089: return [F,LCM];
1090: } else
1091: return 0;
1092: }
1093: } else {
1094: #if 0
1095: if ( dp_gr_print() ) print(I);
1096: #endif
1097: }
1098: } else {
1099: #if 0
1100: if ( dp_gr_print() ) print([I,TINV,TC,TDIV]);
1101: #endif
1102: if ( dp_gr_print() ) print(".",2);
1103: CCC++;
1104: }
1105: T0 = time()[0];
1106: XT = sremainder(INV*sremainder(-C,MOD),MOD);
1107: XT = map(adj_sgn,XT,MOD,MOD2);
1108: TINV += time()[0] - T0;
1109: X += XT*PK;
1110: T0 = time()[0];
1111: C += mul_mat_vect_int(AA,XT);
1112: TC += time()[0] - T0;
1113: T0 = time()[0]; C = map(idiv,C,MOD); TDIV += time()[0] - T0;
1114: }
1115: }
1116:
1117: def henleq_prep(A,MOD)
1118: {
1119: SIZE = size(A); ROW = SIZE[0]; COL = SIZE[1];
1120: L = geninvm_swap(A,MOD); INV = L[0]; INDEX = L[1];
1121: AA = newmat(COL,COL);
1122: for ( I = 0; I < COL; I++ )
1123: for ( J = 0, T = AA[I], S = A[INDEX[I]]; J < COL; J++ )
1124: T[J] = S[J];
1125: if ( COL != ROW ) {
1126: RESTA = newmat(ROW-COL,COL);
1127: for ( ; I < ROW; I++ )
1128: for ( J = 0, T = RESTA[I-COL], S = A[INDEX[I]]; J < COL; J++ )
1129: T[J] = S[J];
1130: } else
1131: RESTA = 0;
1132: return [[A,AA,RESTA],L];
1133: }
1134:
1135: def henleq_gsl(L,B,MOD)
1136: {
1137: AL = L[0]; INVL = L[1];
1138: A = AL[0]; AA = AL[1]; RESTA = AL[2];
1139: INV = INVL[0]; INDEX = INVL[1];
1140: SIZE = size(A); ROW = SIZE[0]; COL = SIZE[1];
1141: BB = newvect(COL);
1142: for ( I = 0; I < COL; I++ )
1143: BB[I] = B[INDEX[I]];
1144: if ( COL != ROW ) {
1145: RESTB = newvect(ROW-COL);
1146: for ( ; I < ROW; I++ )
1147: RESTB[I-COL] = B[INDEX[I]];
1148: } else
1149: RESTB = 0;
1150:
1151: COUNT = INIT_COUNT?INIT_COUNT:idiv(MAX(max_mag(A),max_mag_vect(B)),54);
1152: if ( !COUNT )
1153: COUNT = 1;
1154: MOD2 = idiv(MOD,2);
1.3 noro 1155: X = newvect(size(AA)[0]);
1156: for ( I = 0, C = BB, PK = 1, CCC = 0, ITOR_FAIL = -1; ;
1.1 noro 1157: I++, PK *= MOD ) {
1158: if ( zerovector(C) )
1159: if ( zerovector(RESTA*X+RESTB) ) {
1160: if ( dp_gr_print() ) print("end",0);
1161: return [X,1];
1162: } else
1163: return 0;
1164: else if ( COUNT == CCC ) {
1165: CCC = 0;
1166: ND = intvtoratv(X,PK,ishift(calcb_special(PK,MOD,I),32));
1167: if ( ND ) {
1168: F = ND[0]; LCM = ND[1]; T = AA*F+LCM*BB;
1169: if ( zerovector(T) ) {
1170: T = RESTA*F+LCM*RESTB;
1171: if ( zerovector(T) ) {
1172: if ( dp_gr_print() ) print("end",0);
1173: return [F,LCM];
1174: } else
1175: return 0;
1176: }
1177: } else {
1178: }
1179: } else {
1180: if ( dp_gr_print() ) print(".",2);
1181: CCC++;
1182: }
1183: XT = sremainder(INV*sremainder(-C,MOD),MOD);
1184: XT = map(adj_sgn,XT,MOD,MOD2);
1185: X += XT*PK;
1186: C += mul_mat_vect_int(AA,XT);
1187: C = map(idiv,C,MOD);
1188: }
1189: }
1190:
1191: def adj_sgn(A,M,M2)
1192: {
1193: return A > M2 ? A-M : A;
1194: }
1195:
1196: def zerovector(C)
1197: {
1198: if ( !C )
1199: return 1;
1200: for ( I = size(C)[0]-1; I >= 0 && !C[I]; I-- );
1201: if ( I < 0 )
1202: return 1;
1203: else
1204: return 0;
1205: }
1206:
1207: def solvem(INV,COMP,V,MOD)
1208: {
1209: T = COMP*V;
1210: N = size(T)[0];
1211: for ( I = 0; I < N; I++ )
1212: if ( T[I] % MOD )
1213: return 0;
1214: return modvect(INV*V,MOD);
1215: }
1216:
1217: def modmat(A,MOD)
1218: {
1219: if ( !A )
1220: return 0;
1221: S = size(A); N = S[0]; M = S[1];
1222: MAT = newmat(N,M);
1223: for ( I = 0, NZ = 0; I < N; I++ )
1224: for ( J = 0, T1 = A[I], T2 = MAT[I]; J < M; J++ ) {
1225: T2[J] = T1[J] % MOD;
1226: NZ = NZ || T2[J];
1227: }
1228: return NZ?MAT:0;
1229: }
1230:
1231: def modvect(A,MOD)
1232: {
1233: if ( !A )
1234: return 0;
1235: N = size(A)[0];
1236: VECT = newvect(N);
1237: for ( I = 0, NZ = 0; I < N; I++ ) {
1238: VECT[I] = A[I] % MOD;
1239: NZ = NZ || VECT[I];
1240: }
1241: return NZ?VECT:0;
1242: }
1243:
1244: def qrmat(A,MOD)
1245: {
1246: if ( !A )
1247: return [0,0];
1248: S = size(A); N = S[0]; M = S[1];
1249: Q = newmat(N,M); R = newmat(N,M);
1250: for ( I = 0, NZQ = 0, NZR = 0; I < N; I++ )
1251: for ( J = 0, TA = A[I], TQ = Q[I], TR = R[I]; J < M; J++ ) {
1252: L = iqr(TA[J],MOD); TQ[J] = L[0]; TR[J] = L[1];
1253: NZQ = NZQ || TQ[J]; NZR = NZR || TR[J];
1254: }
1255: return [NZQ?Q:0,NZR?R:0];
1256: }
1257:
1258: def qrvect(A,MOD)
1259: {
1260: if ( !A )
1261: return [0,0];
1262: N = size(A)[0];
1263: Q = newvect(N); R = newvect(N);
1264: for ( I = 0, NZQ = 0, NZR = 0; I < N; I++ ) {
1265: L = iqr(A[I],MOD); Q[I] = L[0]; R[I] = L[1];
1266: NZQ = NZQ || Q[I]; NZR = NZR || R[I];
1267: }
1268: return [NZQ?Q:0,NZR?R:0];
1269: }
1270:
1271: def max_mag(M)
1272: {
1273: R = size(M)[0];
1274: U = 1;
1275: for ( I = 0; I < R; I++ ) {
1276: A = max_mag_vect(M[I]);
1277: U = MAX(A,U);
1278: }
1279: return U;
1280: }
1281:
1282: def max_mag_vect(V)
1283: {
1284: R = size(V)[0];
1285: U = 1;
1286: for ( I = 0; I < R; I++ ) {
1287: A = dp_mag(V[I]*<<0>>);
1288: U = MAX(A,U);
1289: }
1290: return U;
1291: }
1292:
1293: def gsl_check(B,V,S)
1294: {
1295: N = length(V);
1296: U = S[N-1]; M = U[1]; D = U[2];
1297: W = setminus(V,[var(M)]);
1298: H = uc(); VH = append(W,[H]);
1299: for ( T = B; T != []; T = cdr(T) ) {
1300: A = car(T);
1301: AH = dp_dtop(dp_homo(dp_ptod(A,W)),VH);
1302: for ( I = 0, Z = S; I < N-1; I++, Z = cdr(Z) ) {
1303: L = car(Z); AH = ptozp(subst(AH,L[0],L[1]/L[2]));
1304: }
1305: AH = ptozp(subst(AH,H,D));
1306: R = srem(AH,M);
1307: if ( dp_gr_print() )
1308: if ( !R )
1309: print([A,"ok"]);
1310: else
1311: print([A,"bad"]);
1312: if ( R )
1313: break;
1314: }
1315: return T == [] ? 1 : 0;
1316: }
1317:
1318: def vs_dim(G,V,O)
1319: {
1320: HM = hmlist(G,V,O); ZD = zero_dim(HM,V,O);
1321: if ( ZD ) {
1322: MB = dp_mbase(map(dp_ptod,HM,V));
1323: return length(MB);
1324: } else
1325: error("vs_dim : ideal is not zero-dimensional!");
1326: }
1327:
1.2 noro 1328: def dgr(G,V,O)
1.1 noro 1329: {
1.2 noro 1330: P = getopt(proc);
1331: if ( type(P) == -1 )
1332: return gr(G,V,O);
1.1 noro 1333: P0 = P[0]; P1 = P[1]; P = [P0,P1];
1.2 noro 1334: map(ox_reset,P);
1335: ox_cmo_rpc(P0,"dp_gr_main",G,V,0,1,O);
1336: ox_cmo_rpc(P1,"dp_gr_main",G,V,1,1,O);
1337: map(ox_push_cmd,P,262); /* 262 = OX_popCMO */
1338: F = ox_select(P);
1339: R = ox_get(F[0]);
1340: if ( F[0] == P0 ) {
1341: Win = "nonhomo";
1342: Lose = P1;
1343: } else {
1.11 noro 1344: Win = "homo";
1345: Lose = P0;
1346: }
1347: ox_reset(Lose);
1348: return [Win,R];
1349: }
1350:
1351: /* competitive Gbase computation : F4 vs. Bucbberger */
1352: /* P : process list */
1353:
1354: def dgrf4mod(G,V,M,O)
1355: {
1356: P = getopt(proc);
1357: if ( type(P) == -1 )
1358: return dp_f4_mod_main(G,V,M,O);
1359: P0 = P[0]; P1 = P[1]; P = [P0,P1];
1360: map(ox_reset,P);
1361: ox_cmo_rpc(P0,"dp_f4_mod_main",G,V,M,O);
1362: ox_cmo_rpc(P1,"dp_gr_mod_main",G,V,0,M,O);
1363: map(ox_push_cmd,P,262); /* 262 = OX_popCMO */
1364: F = ox_select(P);
1365: R = ox_get(F[0]);
1366: if ( F[0] == P0 ) {
1367: Win = "F4";
1368: Lose = P1;
1369: } else {
1370: Win = "Buchberger";
1.2 noro 1371: Lose = P0;
1372: }
1373: ox_reset(Lose);
1374: return [Win,R];
1.1 noro 1375: }
1376:
1377: /* functions for rpc */
1378:
1379: def register_matrix(M)
1380: {
1381: REMOTE_MATRIX = M; return 0;
1382: }
1383:
1384: def register_nfv(L)
1385: {
1386: REMOTE_NF = L[0]; REMOTE_VARS = L[1]; return 0;
1387: }
1388:
1389: def r_ttob(T,M)
1390: {
1391: return hen_ttob(T,REMOTE_NF,0,REMOTE_VARS,M);
1392: }
1393:
1394: def r_ttob_gsl(L,M)
1395: {
1396: return cons(L[2],hen_ttob(L[0],REMOTE_NF,L[1],REMOTE_VARS,M));
1397: }
1398:
1399: def get_matrix()
1400: {
1401: REMOTE_MATRIX;
1.4 noro 1402: }
1403:
1404: extern NFArray$
1405:
1406: /*
1407: * HL = [[c,i,m,d],...]
1408: * if c != 0
1409: * g = 0
1410: * g = (c*g + m*gi)/d
1411: * ...
1412: * finally compare g with NF
1413: * if g == NF then NFArray[NFIndex] = g
1414: *
1415: * if c = 0 then HL consists of single history [0,i,0,0],
1416: * which means that dehomogenization of NFArray[i] should be
1417: * eqall to NF.
1418: */
1419:
1420: def check_trace(NF,NFIndex,HL)
1421: {
1422: if ( !car(HL)[0] ) {
1423: /* dehomogenization */
1424: DH = dp_dehomo(NFArray[car(HL)[1]]);
1425: if ( NF == DH ) {
1426: realloc_NFArray(NFIndex);
1427: NFArray[NFIndex] = NF;
1428: return 0;
1429: } else
1430: error("check_trace(dehomo)");
1431: }
1432:
1433: for ( G = 0, T = HL; T != []; T = cdr(T) ) {
1434: H = car(T);
1435:
1436: Coeff = H[0];
1437: Index = H[1];
1438: Monomial = H[2];
1439: Denominator = H[3];
1440:
1441: Reducer = NFArray[Index];
1442: G = (Coeff*G+Monomial*Reducer)/Denominator;
1443: }
1444: if ( NF == G ) {
1445: realloc_NFArray(NFIndex);
1446: NFArray[NFIndex] = NF;
1447: return 0;
1448: } else
1449: error("check_trace");
1450: }
1451:
1452: /*
1453: * realloc NFArray so that it can hold * an element as NFArray[Ind].
1454: */
1455:
1456: def realloc_NFArray(Ind)
1457: {
1458: if ( Ind == size(NFArray)[0] ) {
1459: New = newvect(Ind + 100);
1460: for ( I = 0; I < Ind; I++ )
1461: New[I] = NFArray[I];
1462: NFArray = New;
1463: }
1464: }
1465:
1466: /*
1467: * create NFArray and initialize it by List.
1468: */
1469:
1470: def register_input(List)
1471: {
1472: Len = length(List);
1473: NFArray = newvect(Len+100,List);
1.1 noro 1474: }
1.9 noro 1475:
1476: /*
1477: tracetogen(): preliminary version
1478:
1479: dp_gr_main() returns [GB,GBIndex,Trace].
1480: GB : groebner basis
1481: GBIndex : IndexList (corresponding to Trace)
1482: Trace : [InputList,Trace0,Trace1,...]
1483: TraceI : [Index,TraceList]
1484: TraceList : [[Coef,Index,Monomial,Denominator],...]
1485: Poly <- 0
1486: Poly <- (Coef*Poly+Monomial*PolyList[Index])/Denominator
1487: */
1488:
1.10 noro 1489: def tracetogen(G)
1.9 noro 1490: {
1.10 noro 1491: GB = G[0]; GBIndex = G[1]; Trace = G[2];
1492:
1.9 noro 1493: InputList = Trace[0];
1494: Trace = cdr(Trace);
1495:
1496: /* number of initial basis */
1497: Nini = length(InputList);
1498:
1499: /* number of generated basis */
1500: Ngen = length(Trace);
1501:
1502: N = Nini + Ngen;
1503:
1504: /* stores traces */
1505: Tr = vector(N);
1506:
1507: /* stores coeffs */
1508: Coef = vector(N);
1509:
1.10 noro 1510: /* XXX create dp_ptod(1,V) */
1511: HT = dp_ht(InputList[0]);
1512: One = dp_subd(HT,HT);
1513:
1.9 noro 1514: for ( I = 0; I < Nini; I++ ) {
1.10 noro 1515: Tr[I] = [1,I,One,1];
1.9 noro 1516: C = vector(Nini);
1.10 noro 1517: C[I] = One;
1.9 noro 1518: Coef[I] = C;
1519: }
1520: for ( ; I < N; I++ )
1521: Tr[I] = Trace[I-Nini][1];
1522:
1523: for ( T = GBIndex; T != []; T = cdr(T) )
1524: compute_coef_by_trace(car(T),Tr,Coef);
1525: return Coef;
1526: }
1527:
1528: def compute_coef_by_trace(I,Tr,Coef)
1529: {
1530: if ( Coef[I] )
1531: return;
1532:
1533: /* XXX */
1534: Nini = size(Coef[0])[0];
1535:
1536: /* initialize coef vector */
1537: CI = vector(Nini);
1538:
1539: for ( T = Tr[I]; T != []; T = cdr(T) ) {
1540: /* Trace = [Coef,Index,Monomial,Denominator] */
1541: Trace = car(T);
1542: C = Trace[0];
1543: Ind = Trace[1];
1544: Mon = Trace[2];
1545: Den = Trace[3];
1546: if ( !Coef[Ind] )
1547: compute_coef_by_trace(Ind,Tr,Coef);
1548:
1549: /* XXX */
1550: CT = newvect(Nini);
1551: for ( J = 0; J < Nini; J++ )
1552: CT[J] = (C*CI[J]+Mon*Coef[Ind][J])/Den;
1553: CI = CT;
1554: }
1555: Coef[I] = CI;
1.13 noro 1556: }
1557:
1558: extern Gbcheck_DP,Gbcheck_IL$
1559:
1560: def register_data_for_gbcheck(DPL)
1561: {
1562: for ( IL = [], I = length(DPL)-1; I >= 0; I-- )
1563: IL = cons(I,IL);
1564: Gbcheck_DP = newvect(length(DPL),DPL);
1565: Gbcheck_IL = IL;
1566: }
1567:
1568: def sp_nf_for_gbcheck(Pair)
1569: {
1570: SP = dp_sp(Gbcheck_DP[Pair[0]],Gbcheck_DP[Pair[1]]);
1571: return dp_nf(Gbcheck_IL,SP,Gbcheck_DP,1);
1572: }
1573:
1574: def gbcheck(B,V,O)
1575: {
1576: dp_ord(O);
1577: D = map(dp_ptod,B,V);
1.14 ! noro 1578: L = dp_gr_checklist(D,length(V));
1.13 noro 1579: DP = L[0]; Plist = L[1];
1580: for ( IL = [], I = size(DP)[0]-1; I >= 0; I-- )
1581: IL = cons(I,IL);
1582: Procs = getopt(proc);
1583: if ( type(Procs) == 4 ) {
1584: map(ox_reset,Procs);
1585: /* register DP in servers */
1586: map(ox_cmo_rpc,Procs,"register_data_for_gbcheck",vtol(DP));
1587: /* discard return value in stack */
1588: map(ox_pop_cmo,Procs);
1589: Free = Procs;
1590: Busy = [];
1591: T = Plist;
1592: while ( T != [] || Busy != [] ){
1593: if ( Free == [] || T == [] ) {
1594: /* someone is working; wait for data */
1595: Ready = ox_select(Busy);
1596: Busy = setminus(Busy,Ready);
1597: Free = append(Ready,Free);
1598: for ( ; Ready != []; Ready = cdr(Ready) ) {
1599: if ( ox_get(car(Ready)) ) {
1600: map(ox_reset,Procs);
1601: return 0;
1602: }
1603: }
1604: } else {
1605: P = car(Free);
1606: Free = cdr(Free);
1607: Busy = cons(P,Busy);
1608: Pair = car(T);
1609: T = cdr(T);
1610: ox_cmo_rpc(P,"sp_nf_for_gbcheck",Pair);
1611: ox_push_cmd(P,262); /* 262 = OX_popCMO */
1612: }
1613: }
1614: map(ox_reset,Procs);
1615: return 1;
1616: } else {
1617: for ( T = Plist; T != []; T = cdr(T) ) {
1618: Pair = T[0];
1619: SP = dp_sp(DP[Pair[0]],DP[Pair[1]]);
1620: if ( dp_nf(IL,SP,DP,1) )
1621: return 0;
1622: }
1623: return 1;
1624: }
1.9 noro 1625: }
1.1 noro 1626: end$
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>