Annotation of OpenXM/src/kan96xx/Kan/dr.sm1, Revision 1.27
1.27 ! takayama 1: % $OpenXM: OpenXM/src/kan96xx/Kan/dr.sm1,v 1.26 2003/12/06 02:49:22 takayama Exp $
1.1 maekawa 2: %% dr.sm1 (Define Ring) 1994/9/25, 26
3: %% This file is error clean.
4:
5: @@@.quiet { }
1.5 takayama 6: { (macro package : dr.sm1, 9/26,1995 --- Version 12/10, 2000. ) message } ifelse
1.1 maekawa 7:
8: /ctrlC-hook {
9: %%% define your own routing in case of error.
10: } def
11: [(ctrlC-hook)
12: [(When ctrl-C is pressed, this function is executed.)
13: (User can define one's own ctrlC-hook function.)
14: ]] putUsages
15:
16: %% n evenQ bool
17: /evenQ {
18: /arg1 set
19: arg1 2 idiv 2 mul arg1 sub 0 eq
20: { true }
21: { false } ifelse
22: } def
23:
24: %% (x,y,z) polynomial_ring [x-list, d-list , paramList]
25: /ring_of_polynomials {
26: /arg1 set
27: [/vars /n /i /xList /dList /param] pushVariables
28: %dup print (-----) message
29: [
30: (mmLarger) (matrix) switch_function
31: (mpMult) (poly) switch_function
32: (red@) (module1) switch_function
33: (groebner) (standard) switch_function
34: (isSameComponent) (x) switch_function
35:
36: [arg1 to_records pop] /vars set
37: vars length evenQ
38: { }
39: { vars [(PAD)] join /vars set }
40: ifelse
41: vars length 2 idiv /n set
42: [ << n 1 sub >> -1 0
43: { /i set
44: vars i get
45: } for
46: ] /xList set
47: [ << n 1 sub >> -1 0
48: { /i set
49: vars << i n add >> get
50: } for
51: ] /dList set
52:
53: [(H)] xList join [@@@.esymbol] join /xList set
54: [(h)] dList join [@@@.Esymbol] join /dList set
55: [0 %% dummy characteristic
56: << xList length >> << xList length >> << xList length >>
57: << xList length >>
58: << xList length 1 sub >> << xList length >> << xList length >>
59: << xList length >>
60: ] /param set
61:
62: [xList dList param] /arg1 set
63: ] pop
64: popVariables
65: arg1
66: } def
67:
68: %% (x,y,z) polynomial_ring [x-list, d-list , paramList]
69: %% with no graduation and homogenization variables.
70: /ring_of_polynomials2 {
71: /arg1 set
72: [/vars /n /i /xList /dList /param] pushVariables
73: %dup print (-----) message
74: [
75: (mmLarger) (matrix) switch_function
76: (mpMult) (poly) switch_function
77: (red@) (module1) switch_function
78: (groebner) (standard) switch_function
79: (isSameComponent) (x) switch_function
80:
81: [arg1 to_records pop] /vars set
82: vars length evenQ
83: { }
84: { vars [(PAD)] join /vars set }
85: ifelse
86: vars length 2 idiv /n set
87: [ << n 1 sub >> -1 0
88: { /i set
89: vars i get
90: } for
91: ] /xList set
92: [ << n 1 sub >> -1 0
93: { /i set
94: vars << i n add >> get
95: } for
96: ] /dList set
97:
98: [0 %% dummy characteristic
99: << xList length >> << xList length >> << xList length >>
100: << xList length >>
101: << xList length >> << xList length >> << xList length >>
102: << xList length >>
103: ] /param set
104:
105: [xList dList param] /arg1 set
106: ] pop
107: popVariables
108: arg1
109: } def
110:
111: %% (x,y,z) polynomial_ring [x-list, d-list , paramList]
112: %% with no homogenization variables.
113: /ring_of_polynomials3 {
114: /arg1 set
115: [/vars /n /i /xList /dList /param] pushVariables
116: %dup print (-----) message
117: [
118: (mmLarger) (matrix) switch_function
119: (mpMult) (poly) switch_function
120: (red@) (module1) switch_function
121: (groebner) (standard) switch_function
122: (isSameComponent) (x) switch_function
123:
124: [arg1 to_records pop] /vars set
125: vars length evenQ
126: { }
127: { vars [(PAD)] join /vars set }
128: ifelse
129: vars length 2 idiv /n set
130: [ << n 1 sub >> -1 0
131: { /i set
132: vars i get
133: } for
134: ] /xList set
135: xList [@@@.esymbol] join /xList set
136: [ << n 1 sub >> -1 0
137: { /i set
138: vars << i n add >> get
139: } for
140: ] /dList set
141: dList [@@@.Esymbol] join /dList set
142:
143: [0 %% dummy characteristic
144: << xList length >> << xList length >> << xList length >>
145: << xList length >>
146: << xList length >> << xList length >> << xList length >>
147: << xList length >>
148: ] /param set
149:
150: [xList dList param] /arg1 set
151: ] pop
152: popVariables
153: arg1
154: } def
155:
156: /ring_of_differential_operators {
157: /arg1 set
158: [/vars /n /i /xList /dList /param] pushVariables
159: [
160: (mmLarger) (matrix) switch_function
161: (mpMult) (diff) switch_function
162: (red@) (module1) switch_function
163: (groebner) (standard) switch_function
164: (isSameComponent) (x) switch_function
165:
166: [arg1 to_records pop] /vars set %[x y z]
167: vars reverse /xList set %[z y x]
168: vars {@@@.Dsymbol 2 1 roll 2 cat_n} map
169: reverse /dList set %[Dz Dy Dx]
170: [(H)] xList join [@@@.esymbol] join /xList set
171: [(h)] dList join [@@@.Esymbol] join /dList set
172: [0 1 1 1 << xList length >>
173: 1 1 1 << xList length 1 sub >> ] /param set
174: [ xList dList param ] /arg1 set
175: ] pop
176: popVariables
177: arg1
178: } def
179:
180: /ring_of_differential_operators3 {
181: %% with no homogenization variables.
182: /arg1 set
183: [/vars /n /i /xList /dList /param] pushVariables
184: [
185: (mmLarger) (matrix) switch_function
186: (mpMult) (diff) switch_function
187: (red@) (module1) switch_function
188: (groebner) (standard) switch_function
189: (isSameComponent) (x) switch_function
190:
191: [arg1 to_records pop] /vars set %[x y z]
192: vars reverse /xList set %[z y x]
193: vars {@@@.Dsymbol 2 1 roll 2 cat_n} map
194: reverse /dList set %[Dz Dy Dx]
195: xList [@@@.esymbol] join /xList set
196: dList [@@@.Esymbol] join /dList set
197: [0 0 0 0 << xList length >>
198: 0 0 0 << xList length 1 sub >> ] /param set
199: [ xList dList param ] /arg1 set
200: ] pop
201: popVariables
202: arg1
203: } def
204:
205: /ring_of_q_difference_operators {
206: /arg1 set
207: [/vars /n /i /xList /dList /param] pushVariables
208: [
209: (mmLarger) (matrix) switch_function
210: (mpMult) (diff) switch_function
211: (red@) (module1) switch_function
212: (groebner) (standard) switch_function
213: (isSameComponent) (x) switch_function
214:
215: [arg1 to_records pop] /vars set %[x y z]
216: vars reverse /xList set %[z y x]
217: vars {@@@.Qsymbol 2 1 roll 2 cat_n} map
218: reverse /dList set %[Dz Dy Dx]
219: [(q)] xList join [@@@.esymbol] join /xList set
220: [(h)] dList join [@@@.Esymbol] join /dList set
221: [0 1 << xList length >> << xList length >> << xList length >>
222: 1 << xList length 1 sub >> << xList length >> << xList length >> ]
223: /param set
224: [ xList dList param ] /arg1 set
225: ] pop
226: popVariables
227: arg1
228: } def
229:
230: /ring_of_q_difference_operators3 {
231: %% with no homogenization and q variables.
232: /arg1 set
233: [/vars /n /i /xList /dList /param] pushVariables
234: [
235: (mmLarger) (matrix) switch_function
236: (mpMult) (diff) switch_function
237: (red@) (module1) switch_function
238: (groebner) (standard) switch_function
239: (isSameComponent) (x) switch_function
240:
241: [arg1 to_records pop] /vars set %[x y z]
242: vars reverse /xList set %[z y x]
243: vars {@@@.Qsymbol 2 1 roll 2 cat_n} map
244: reverse /dList set %[Dz Dy Dx]
245: xList [@@@.esymbol] join /xList set
246: dList [@@@.Esymbol] join /dList set
247: [0 0 << xList length >> << xList length >> << xList length >>
248: 0 << xList length 1 sub >> << xList length >> << xList length >> ]
249: /param set
250: [ xList dList param ] /arg1 set
251: ] pop
252: popVariables
253: arg1
254: } def
255:
256: /ring_of_difference_operators {
257: /arg1 set
258: [/vars /n /i /xList /dList /param] pushVariables
259: [
1.8 takayama 260: (This is an obsolete macro. Use ring_of_differential_difference_operators)
261: error
1.1 maekawa 262: (mmLarger) (matrix) switch_function
263: (mpMult) (difference) switch_function
264: (red@) (module1) switch_function
265: (groebner) (standard) switch_function
266: (isSameComponent) (x) switch_function
267:
268: [arg1 to_records pop] /vars set %[x y z]
269: vars reverse /xList set %[z y x]
270: vars {@@@.diffEsymbol 2 1 roll 2 cat_n} map
271: reverse /dList set %[Dz Dy Dx]
272: [(H)] xList join [@@@.esymbol] join /xList set
273: [(h)] dList join [@@@.Esymbol] join /dList set
274: [0 1 1 << xList length >> << xList length >>
275: 1 1 << xList length 1 sub >> << xList length >> ] /param set
276: [ xList dList param ] /arg1 set
277: ] pop
278: popVariables
279: arg1
280: } def
281:
282:
1.8 takayama 283: /ring_of_differential_difference_operators {
284: /arg1 set
285: [/vars /n /i /xList /dList /param /dvar /evar /vars2 ] pushVariables
286: [
287: /vars arg1 def
288: vars tag 6 eq not {
289: ( List is expected as the argument for ring_of_differential_difference_operators ) error
290: } { } ifelse
291: vars 0 get /dvar set
292: vars 1 get /evar set
293: (mmLarger) (matrix) switch_function
294: (mpMult) (difference) switch_function
295: (red@) (module1) switch_function
296: (groebner) (standard) switch_function
297: (isSameComponent) (x) switch_function
298:
299: [dvar to_records pop] /vars set %[x y z]
300: vars reverse /xList set %[z y x]
301:
302: [evar to_records pop] /vars2 set %[s1 s2]
303:
304: vars2 reverse {@@@.Esymbol 2 1 roll 2 cat_n} map
305: xList
306: join /xList set %[Es2 Es1 z y x]
307:
308: vars2 reverse
309: vars {@@@.Dsymbol 2 1 roll 2 cat_n} map
310: reverse join /dList set %[s2 s1 Dz Dy Dx]
311: [(H)] xList join [@@@.esymbol] join /xList set
312: [(h)] dList join [@@@.Esymbol] join /dList set
313: [0 1 1 << vars2 length 1 add >> << xList length >>
314: 1 1 << vars2 length 1 add >> << xList length 1 sub >> ] /param set
315: [ xList dList param ] /arg1 set
316: ] pop
317: popVariables
318: arg1
319: } def
1.1 maekawa 320:
321: /reverse {
322: /arg1 set
323: arg1 length 1 lt
324: { [ ] }
325: {
326: [
327: << arg1 length 1 sub >> -1 0
328: {
329: arg1 2 1 roll get
330: } for
331: ]
332: } ifelse
333: } def
334:
335: /memberQ {
336: %% a set0 memberQ bool
337: /arg2 set /arg1 set
338: [/a /set0 /flag /i ] pushVariables
339: [
340: /a arg1 def /set0 arg2 def
341: /flag 0 def
342: 0 1 << set0 length 1 sub >>
343: {
344: /i set
345: << set0 i get >> a eq
346: {
347: /flag 1 def
348: }
349: { }
350: ifelse
351: } for
352: ] pop
353: /arg1 flag def
354: popVariables
355: arg1
356: } def
357:
358: /transpose {
359: /arg1 set
360: [/mat /m /n /ans /i /j] pushVariables
361: [
362: /mat arg1 def
363: /m mat length def
364: mat 0 get isArray
365: { }
366: { (transpose: Argument must be an array of arrays.) error }
367: ifelse
368: /n mat 0 get length def
369: /ans [ 1 1 n { pop [ 1 1 m { pop 0 } for ]} for ] def
370: 0 1 << m 1 sub >> {
371: /i set
372: 0 1 << n 1 sub >> {
373: /j set
374: ans [ j i ] << mat i get j get >> put
375: } for
376: } for
377: /arg1 ans def
378: ] pop
379: popVariables
380: arg1
381: } def
382:
383:
384: /getPerm {
385: %% old new getPerm perm
386: /arg2 set /arg1 set
387: [/old /new /i /j /p] pushVariables
388: [
389: /old arg1 def
390: /new arg2 def
391: [
392: /p old length def
393: 0 1 << p 1 sub >>
394: {
395: /i set
396: 0 1 << p 1 sub >>
397: {
398: /j set
399: old i get
400: new j get
401: eq
402: { j }
403: { } ifelse
404: } for
405: } for
406: ] /arg1 set
407: ] pop
408: popVariables
409: arg1
410: } def
411:
412: /permuteOrderMatrix {
413: %% order perm puermuteOrderMatrix newOrder
414: /arg2 set /arg1 set
415: [/order /perm /newOrder /k ] pushVariables
416: [
417: /order arg1 def
418: /perm arg2 def
419: order transpose /order set
420: order 1 copy /newOrder set pop
421:
422: 0 1 << perm length 1 sub >>
423: {
424: /k set
425: newOrder << perm k get >> << order k get >> put
426: } for
427: newOrder transpose /newOrder set
428: ] pop
429: /arg1 newOrder def
430: popVariables
431: arg1
432: } def
433:
434:
435:
436: /complement {
437: %% set0 universe complement compl
438: /arg2 set /arg1 set
439: [/set0 /universe /compl /i] pushVariables
440: /set0 arg1 def /universe arg2 def
441: [
442: 0 1 << universe length 1 sub >>
443: {
444: /i set
445: << universe i get >> set0 memberQ
446: { }
447: { universe i get }
448: ifelse
449: } for
450: ] /arg1 set
451: popVariables
452: arg1
453: } def
454:
455:
456: %%% from order.sm1
457:
458: %% size i evec [0 0 ... 0 1 0 ... 0]
459: /evec {
460: /arg2 set /arg1 set
461: [/size /iii] pushVariables
462: /size arg1 def /iii arg2 def
463: [
464: 0 1 << size 1 sub >>
465: {
466: iii eq
467: { 1 }
468: { 0 }
469: ifelse
470: } for
471: ] /arg1 set
472: popVariables
473: arg1
474: } def
475:
476: %% size i evec_neg [0 0 ... 0 -1 0 ... 0]
477: /evec_neg {
478: /arg2 set /arg1 set
479: [/size /iii] pushVariables
480: /size arg1 def /iii arg2 def
481: [
482: 0 1 << size 1 sub >>
483: {
484: iii eq
485: { -1 }
486: { 0 }
487: ifelse
488: } for
489: ] /arg1 set
490: popVariables
491: arg1
492: } def
493:
494:
495: %% size i j e_ij << matrix e(i,j) >>
496: /e_ij {
497: /arg3 set /arg2 set /arg1 set
498: [/size /k /i /j] pushVariables
499: [
500: /size arg1 def /i arg2 def /j arg3 def
501: [ 0 1 << size 1 sub >>
502: {
503: /k set
504: k i eq
505: { size j evec }
506: {
507: k j eq
508: { size i evec }
509: { size k evec }
510: ifelse
511: } ifelse
512: } for
513: ] /arg1 set
514: ] pop
515: popVariables
516: arg1
517: } def
518:
519:
520: %% size i j d_ij << matrix E_{ij} >>
521: /d_ij {
522: /arg3 set /arg2 set /arg1 set
523: [/size /k /i /j] pushVariables
524: [
525: /size arg1 def /i arg2 def /j arg3 def
526: [ 0 1 << size 1 sub >>
527: {
528: /k set
529: k i eq
530: { size j evec }
531: {
532: [ 0 1 << size 1 sub >> { pop 0} for ]
533: } ifelse
534: } for
535: ] /arg1 set
536: ] pop
537: popVariables
538: arg1
539: } def
540:
541: %% size matid << id matrix >>
542: /matid {
543: /arg1 set
544: [/size /k ] pushVariables
545: [
546: /size arg1 def
547: [ 0 1 << size 1 sub >>
548: {
549: /k set
550: size k evec
551: } for
552: ] /arg1 set
553: ] pop
554: popVariables
555: arg1
556: } def
557:
558:
559: %% m1 m2 oplus
560: /oplus {
561: /arg2 set /arg1 set
562: [/m1 /m2 /n /m /k ] pushVariables
563: [
564: /m1 arg1 def /m2 arg2 def
565: m1 length /n set
566: m2 length /m set
567: [
568: 0 1 << n m add 1 sub >>
569: {
570: /k set
571: k n lt
572: {
573: << m1 k get >> << m -1 evec >> join
574: }
575: {
576: << n -1 evec >> << m2 << k n sub >> get >> join
577: } ifelse
578: } for
579: ] /arg1 set
580: ] pop
581: popVariables
582: arg1
583: } def
584:
585: %%%%%%%%%%%%%%%%%%%%%%%
586:
587: /eliminationOrderTemplate { %% esize >= 1
588: %% if esize == 0, it returns reverse lexicographic order.
589: %% m esize eliminationOrderTemplate mat
590: /arg2 set /arg1 set
591: [/m /esize /m1 /m2 /k ] pushVariables
592: [
593: /m arg1 def /esize arg2 def
594: /m1 m esize sub 1 sub def
595: /m2 esize 1 sub def
596: [esize 0 gt
597: {
598: [1 1 esize
599: { pop 1 } for
600: esize 1 << m 1 sub >>
601: { pop 0 } for
602: ] %% 1st vector
603: }
604: { } ifelse
605:
606: m esize gt
607: {
608: [1 1 esize
609: { pop 0 } for
610: esize 1 << m 1 sub >>
611: { pop 1 } for
612: ] %% 2nd vector
613: }
614: { } ifelse
615:
616: m1 0 gt
617: {
618: m 1 sub -1 << m m1 sub >>
619: {
620: /k set
621: m k evec_neg
622: } for
623: }
624: { } ifelse
625:
626: m2 0 gt
627: {
628: << esize 1 sub >> -1 1
629: {
630: /k set
631: m k evec_neg
632: } for
633: }
634: { } ifelse
635:
636: ] /arg1 set
637: ] pop
638: popVariables
639: arg1
640: } def
641:
642: /elimination_order {
643: %% [x-list d-list params] (x,y,z) elimination_order
644: %% vars evars
645: %% [x-list d-list params order]
646: /arg2 set /arg1 set
647: [/vars /evars /univ /order /perm /univ0 /compl] pushVariables
648: /vars arg1 def /evars [arg2 to_records pop] def
649: [
650: /univ vars 0 get reverse
651: vars 1 get reverse join
652: def
653:
654: << univ length 2 sub >>
655: << evars length >>
656: eliminationOrderTemplate /order set
657:
658: [[1]] order oplus [[1]] oplus /order set
659:
660: /univ0 [univ reverse aload pop pop] reverse def %% [e,x,y,h] --> [x,y,h]
661:
662: /compl
663: [univ 0 get] evars join evars univ0 complement join
664: def
665: compl univ
666: getPerm /perm set
667: %%perm :: univ :: compl ::
668:
669: order perm permuteOrderMatrix /order set
670:
671:
672: vars [order] join /arg1 set
673: ] pop
674: popVariables
675: arg1
676: } def
677:
678: /elimination_order2 {
679: %% [x-list d-list params] (x,y,z) elimination_order
680: %% vars evars
681: %% [x-list d-list params order]
682: %% with no graduation and homogenization variables.
683: /arg2 set /arg1 set
684: [/vars /evars /univ /order /perm /compl] pushVariables
685: /vars arg1 def /evars [arg2 to_records pop] def
686: [
687: /univ vars 0 get reverse
688: vars 1 get reverse join
689: def
690:
691: << univ length >>
692: << evars length >>
693: eliminationOrderTemplate /order set
694: /compl
695: evars << evars univ complement >> join
696: def
697: compl univ
698: getPerm /perm set
699: %%perm :: univ :: compl ::
700:
701: order perm permuteOrderMatrix /order set
702:
703: vars [order] join /arg1 set
704: ] pop
705: popVariables
706: arg1
707: } def
708:
709:
710: /elimination_order3 {
711: %% [x-list d-list params] (x,y,z) elimination_order
712: %% vars evars
713: %% [x-list d-list params order]
714: /arg2 set /arg1 set
715: [/vars /evars /univ /order /perm /univ0 /compl] pushVariables
716: /vars arg1 def /evars [arg2 to_records pop] def
717: [
718: /univ vars 0 get reverse
719: vars 1 get reverse join
720: def
721:
722: << univ length 1 sub >>
723: << evars length >>
724: eliminationOrderTemplate /order set
725:
726: [[1]] order oplus /order set
727:
728: /univ0 [univ reverse aload pop pop] reverse def %% [e,x,y] --> [x,y]
729:
730: /compl
731: [univ 0 get] evars join evars univ0 complement join
732: def
733: compl univ
734: getPerm /perm set
735: %%perm :: univ :: compl ::
736:
737: order perm permuteOrderMatrix /order set
738:
739: vars [order] join /arg1 set
740: ] pop
741: popVariables
742: arg1
743: } def
744:
745:
746: /define_ring {
747: %[ (x,y,z) ring_of_polynominals
748: % (x,y) elimination_order
749: % 17
750: %] define_ring
751: % or
752: %[ (x,y,z) ring_of_polynominals
753: % (x,y) elimination_order
754: % 17
755: % [(keyword) value (keyword) value ...]
756: %] define_ring
757: /arg1 set
758: [/rp /param /foo] pushVariables
759: [/rp arg1 def
760:
761: rp 0 get length 3 eq {
762: rp 0 [rp 0 get 0 get rp 0 get 1 get rp 0 get 2 get ]
763: ( ) elimination_order put
764: } { } ifelse
765:
766: [
767: rp 0 get 0 get %% x-list
768: rp 0 get 1 get %% d-list
769: rp 0 get 2 get /param set
770: param 0 << rp 1 get >> put %% << rp 1 get >> is 17 in the example.
771: param %% parameters.
772: rp 0 get 3 get %% order matrix.
773: rp length 2 eq
774: { [ ] } %% null optional argument.
775: { rp 2 get }
776: ifelse
777: ] /foo set
778: foo aload pop set_up_ring@
779: ] pop
780: popVariables
781: [(CurrentRingp)] system_variable
782: } def
783:
784:
785: [(define_qring)
786: [( [varlist ring_of_q_difference_operators order characteristic] define_qring)
787: ( Pointer to the ring. )
788: (Example: [$x,y$ ring_of_q_difference_operators $Qx,Qy$ elimination_order)
789: ( 0] define_qring )
790: (cf. define_ring, set_up_ring@ <coefficient ring>, ring_def, << ,, >>)
791: ]
792: ] putUsages
793: /define_qring {
794: %[ (x,y,z) ring_of_q_difference_operators
795: % (Qx,Qy) elimination_order
796: % 17
797: %] define_qring
798: /arg1 set
799: [/rp /param /foo /cring /ppp] pushVariables
800: [/rp arg1 def
801: /ppp rp 1 get def
802: %% define coefficient ring.
803: [(q) @@@.esymbol] [(h) @@@.Esymbol]
804: [ppp 2 2 2 2 1 2 2 2]
805: [[1 0 0 0] [0 1 0 0] [0 0 1 0] [0 0 0 1]]
806: [(mpMult) (poly)] set_up_ring@
807: /cring [(CurrentRingp)] system_variable def
808:
809: rp 0 get length 3 eq {
810: rp 0 [rp 0 get 0 get rp 0 get 1 get rp 0 get 2 get ]
811: ( ) elimination_order put
812: } { } ifelse
813:
814: [
815: rp 0 get 0 get %% x-list
816: rp 0 get 1 get %% d-list
817: rp 0 get 2 get /param set
818: param 0 << rp 1 get >> put %% << rp 1 get >> is 17 in the example.
819: param %% parameters.
820: rp 0 get 3 get %% order matrix.
821: rp length 2 eq
822: { [(mpMult) (diff) (coefficient ring) cring] } %% optional argument.
823: { [(mpMult) (diff) (coefficient ring) cring] rp 2 get join }
824: ifelse
825: ] /foo set
826: foo aload pop set_up_ring@
827: ] pop
828: popVariables
829: [(CurrentRingp)] system_variable
830: } def
831:
832: [(ring_def)
833: [(ring ring_def)
834: (Set the current ring to the <<ring>>)
835: (Example: [(x,y) ring_of_polynomials [[(x) 1]] weight_vector 0 ] define_ring)
836: ( /R set)
837: ( R ring_def)
838: (In order to get the ring object R to which a given polynomial f belongs,)
839: (one may use the command )
840: ( f (ring) data_conversion /R set)
841: (cf. define_ring, define_qring, system_variable, poly (ring) data_conversion)
842: (cf. << ,, >>)
843: ]
844: ] putUsages
845:
846: /ring_def {
847: /arg1 set
848: [(CurrentRingp) arg1] system_variable
849: } def
850:
851:
852:
853: /lexicographicOrderTemplate {
854: % size lexicographicOrderTemplate matrix
855: /arg1 set
856: [/k /size] pushVariables
857: [
858: /size arg1 def
859: [ 0 1 << size 1 sub >>
860: {
861: /k set
862: size k evec
863: } for
864: ] /arg1 set
865: ] pop
866: popVariables
867: arg1
868: } def
869:
870: /lexicographic_order {
871: %% [x-list d-list params] (x,y,z) lexicograhic_order
872: %% vars evars
873: %% [x-list d-list params order]
874: /arg2 set /arg1 set
875: [/vars /evars /univ /order /perm /univ0 /compl] pushVariables
876: /vars arg1 def /evars [arg2 to_records pop] def
877: [
878: /univ vars 0 get reverse
879: vars 1 get reverse join
880: def
881:
882: << univ length 2 sub >>
883: lexicographicOrderTemplate /order set
884:
885: [[1]] order oplus [[1]] oplus /order set
886:
887: /univ0 [univ reverse aload pop pop] reverse def %% [e,x,y,h] --> [x,y,h]
888:
889: /compl
890: [univ 0 get] evars join evars univ0 complement join
891: def
892: compl univ
893: getPerm /perm set
894: %%perm :: univ :: compl ::
895:
896: order perm permuteOrderMatrix /order set
897:
898: vars [order] join /arg1 set
899: ] pop
900: popVariables
901: arg1
902: } def
903:
904: /lexicographic_order2 {
905: %% [x-list d-list params] (x,y,z) lexicograhic_order
906: %% vars evars
907: %% [x-list d-list params order]
908: %% with no graduation and homogenization variables
909: /arg2 set /arg1 set
910: [/vars /evars /univ /order /perm /compl] pushVariables
911: /vars arg1 def /evars [arg2 to_records pop] def
912: [
913: /univ vars 0 get reverse
914: vars 1 get reverse join
915: def
916:
917: << univ length >>
918: lexicographicOrderTemplate /order set
919:
920: /compl
921: evars << evars univ complement >> join
922: def
923: compl univ
924: getPerm /perm set
925:
926: order perm permuteOrderMatrix /order set
927:
928: vars [order] join /arg1 set
929: ] pop
930: popVariables
931: arg1
932: } def
933:
934: /lexicographic_order3 {
935: %% [x-list d-list params] (x,y,z) lexicograhic_order
936: %% vars evars
937: %% [x-list d-list params order]
938: %% with no homogenization variable.
939: /arg2 set /arg1 set
940: [/vars /evars /univ /order /perm /univ0 /compl] pushVariables
941: /vars arg1 def /evars [arg2 to_records pop] def
942: [
943: /univ vars 0 get reverse
944: vars 1 get reverse join
945: def
946:
947: << univ length 1 sub >>
948: lexicographicOrderTemplate /order set
949:
950: [[1]] order oplus /order set
951:
952: /univ0 [univ reverse aload pop pop] reverse def %% [e,x,y] --> [x,y]
953:
954: /compl
955: [univ 0 get] evars join evars univ0 complement join
956: def
957: compl univ
958: getPerm /perm set
959: %%perm :: univ :: compl ::
960:
961: order perm permuteOrderMatrix /order set
962:
963: vars [order] join /arg1 set
964: ] pop
965: popVariables
966: arg1
967: } def
968:
969: %%%%%% add_rings %%%%%%%%%%%%%% 10/5
970:
971: /graded_reverse_lexicographic_order {
972: ( ) elimination_order
973: } def
974:
975:
976: /getX {
977: %% param [1|2|3|4] getX [var-lists] ; 1->c,2->l,3->m,4->n
978: /arg2 set /arg1 set
979: [/k /param /func /low /top] pushVariables
980: [
981: /param arg1 def /func arg2 def
982: func 1 eq
983: {
984: /low 0 def
985: }
986: {
987: /low << param 2 get >> << func 1 sub >> get def
988: } ifelse
989: /top << param 2 get >> << func 4 add >> get 1 sub def
990: [
991: low 1 top
992: {
993: /k set
994: param 0 get k get
995: } for
996: ] /arg1 set
997: ] pop
998: popVariables
999: arg1
1000: } def
1001:
1002: /getD {
1003: %% param [1|2|3|4] getD [var-lists] ; 1->c,2->l,3->m,4->n
1004: /arg2 set /arg1 set
1005: [/k /param /func /low /top] pushVariables
1006: [
1007: /param arg1 def /func arg2 def
1008: func 1 eq
1009: {
1010: /low 0 def
1011: }
1012: {
1013: /low << param 2 get >> << func 1 sub >> get def
1014: } ifelse
1015: /top << param 2 get >> << func 4 add >> get 1 sub def
1016: [
1017: low 1 top
1018: {
1019: /k set
1020: param 1 get k get
1021: } for
1022: ] /arg1 set
1023: ] pop
1024: popVariables
1025: arg1
1026: } def
1027:
1028: /getXV {
1029: %% param [1|2|3|4] getXV [var-lists] ; 1->c,2->l,3->m,4->n
1030: /arg2 set /arg1 set
1031: [/k /param /func /low /top] pushVariables
1032: [
1033: /param arg1 def /func arg2 def
1034: /low << param 2 get >> << func 4 add >> get def
1035: /top << param 2 get >> func get 1 sub def
1036: [
1037: low 1 top
1038: {
1039: /k set
1040: param 0 get k get
1041: } for
1042: ] /arg1 set
1043: ] pop
1044: popVariables
1045: arg1
1046: } def
1047:
1048: /getDV {
1049: %% param [1|2|3|4] getDV [var-lists] ; 1->c,2->l,3->m,4->n
1050: /arg2 set /arg1 set
1051: [/k /param /func /low /top] pushVariables
1052: [
1053: /param arg1 def /func arg2 def
1054: /low << param 2 get >> << func 4 add >> get def
1055: /top << param 2 get >> func get 1 sub def
1056: [
1057: low 1 top
1058: {
1059: /k set
1060: param 1 get k get
1061: } for
1062: ] /arg1 set
1063: ] pop
1064: popVariables
1065: arg1
1066: } def
1067:
1068: /reNaming {
1069: %% It also changes oldx2 and oldd2, which are globals.
1070: /arg1 set
1071: [/i /j /new /count /ostr /k] pushVariables
1072: [
1073: /new arg1 def
1074: /count 0 def
1075: 0 1 << new length 1 sub >> {
1076: /i set
1077: << i 1 add >> 1 << new length 1 sub >> {
1078: /j set
1079: << new i get >> << new j get >> eq
1080: {
1081: new j get /ostr set
1082: (The two rings have the same name :) messagen
1083: new i get messagen (.) message
1084: (The name ) messagen
1085: new i get messagen ( is changed into ) messagen
1086: new j << new i get << 48 count add $string$ data_conversion >>
1087: 2 cat_n >> put
1088: new j get messagen (.) message
1089: /oldx2 ostr << new j get >> reNaming2
1090: /oldd2 ostr << new j get >> reNaming2
1091: /count count 1 add def
1092: }
1093: { }
1094: ifelse
1095: } for
1096: } for
1097: /arg1 new def
1098: ] pop
1099: popVariables
1100: arg1
1101: } def
1102:
1103: /reNaming2 {
1104: %% array oldString newString reNaming2
1105: %% /aa (x) (y) reNaming2
1106: /arg3 set /arg2 set /arg1 set
1107: [/array /oldString /newString /k] pushVariables
1108: [
1109: /array arg1 def /oldString arg2 def /newString arg3 def
1110: 0 1 << array load length 1 sub >>
1111: {
1112: /k set
1113: << array load k get >> oldString eq
1114: {
1115: array load k newString put
1116: }
1117: { } ifelse
1118: } for
1119: ] pop
1120: popVariables
1121: } def
1122:
1123: /add_rings {
1124: /arg2 set /arg1 set
1125: [/param1 /param2
1126: /newx /newd /newv
1127: /k /const /od1 /od2 /od
1128: /oldx2 /oldd2 % these will be changed in reNaming.
1129: /oldv
1130: ] pushVariables
1131: [
1132: /param1 arg1 def /param2 arg2 def
1133: %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1134: /newx
1135: [ ]
1136: param2 1 getX join param1 1 getX join
1137: param2 1 getXV join param1 1 getXV join
1138:
1139: param2 2 getX join param1 2 getX join
1140: param2 2 getXV join param1 2 getXV join
1141:
1142: param2 3 getX join param1 3 getX join
1143: param2 3 getXV join param1 3 getXV join
1144:
1145: param2 4 getX join param1 4 getX join
1146: param2 4 getXV join param1 4 getXV join
1147: def
1148: /newd
1149: [ ]
1150: param2 1 getD join param1 1 getD join
1151: param2 1 getDV join param1 1 getDV join
1152:
1153: param2 2 getD join param1 2 getD join
1154: param2 2 getDV join param1 2 getDV join
1155:
1156: param2 3 getD join param1 3 getD join
1157: param2 3 getDV join param1 3 getDV join
1158:
1159: param2 4 getD join param1 4 getD join
1160: param2 4 getDV join param1 4 getDV join
1161: def
1162:
1163: /newv newx newd join def
1164: /oldx2 param2 0 get def /oldd2 param2 1 get def
1165: /oldx2 oldx2 {1 copy 2 1 roll pop} map def
1166: /oldd2 oldd2 {1 copy 2 1 roll pop} map def
1167: /newv newv reNaming def
1168:
1169: /newx [
1170: 0 1 << newv length 2 idiv 1 sub >>
1171: {
1172: /k set
1173: newv k get
1174: } for
1175: ] def
1176: /newd [
1177: 0 1 << newv length 2 idiv 1 sub >>
1178: {
1179: /k set
1180: newv << newv length 2 idiv k add >> get
1181: } for
1182: ] def
1183: /const [
1184: << param1 2 get 0 get >>
1185: << param1 2 get 1 get param2 2 get 1 get add >>
1186: << param1 2 get 2 get param2 2 get 2 get add >>
1187: << param1 2 get 3 get param2 2 get 3 get add >>
1188: << param1 2 get 4 get param2 2 get 4 get add >>
1189: << param1 2 get 5 get param2 2 get 5 get add >>
1190: << param1 2 get 6 get param2 2 get 6 get add >>
1191: << param1 2 get 7 get param2 2 get 7 get add >>
1192: << param1 2 get 8 get param2 2 get 8 get add >>
1193: ] def
1194:
1195: /od1 param1 3 get def /od2 param2 3 get def
1196: od1 od2 oplus /od set
1197:
1198: %%oldx2 :: oldd2 ::
1199: << param1 0 get reverse >> << param1 1 get reverse >> join
1200: << oldx2 reverse >> << oldd2 reverse >> join
1201: join /oldv set
1202:
1203:
1204: od << oldv << newx reverse newd reverse join >> getPerm >>
1205: permuteOrderMatrix /od set
1206:
1207: /arg1 [newx newd const od] def
1208: ] pop
1209: popVariables
1210: arg1
1211: } def
1212:
1213:
1214: %%%% end of add_rings
1215:
1216:
1217:
1218: [(swap01) [
1219: $[ .... ] swap01 [....]$
1220: $Examples: [(x,y) ring_of_polynomials (x) elmination_order 0] swap01 $
1221: $ define_ring$
1222: ]] putUsages
1223: %
1224: /swap01 {
1225: /arg1 set
1226: [/rg /ch ] pushVariables
1227: [
1228: arg1 0 get /rg set % ring
1229: arg1 1 get /ch set % characteristics
1230: [rg 0 get , rg 1 get , rg 2 get ,
1231: << rg 3 get length >> 0 1 e_ij << rg 3 get >> mul ] /rg set
1232: /arg1 [ rg ch ] def
1233: ] pop
1234: popVariables
1235: arg1
1236: } def
1237:
1238: [(swap0k) [
1239: $[ .... ] k swap0k [....]$
1240: $Examples: [(x,y) ring_of_polynomials (x) elmination_order 0] 1 swap0k $
1241: $ define_ring$
1242: $swap01 == 1 swap0k$
1243: ]] putUsages
1244: %
1245: /swap0k {
1246: /arg2 set
1247: /arg1 set
1248: [/rg /ch /kk] pushVariables
1249: [
1250: arg2 /kk set
1251: arg1 0 get /rg set % ring
1252: arg1 1 get /ch set % characteristics
1253: [rg 0 get , rg 1 get , rg 2 get ,
1254: << rg 3 get length >> 0 kk e_ij << rg 3 get >> mul ] /rg set
1255: /arg1 [ rg ch ] def
1256: ] pop
1257: popVariables
1258: arg1
1259: } def
1260:
1261: %%%%%%%%%%%%% weight vector
1262: [(position)
1263: [(set element position number)
1264: (Example: [(cat) (dog) (hot chocolate)] (cat) position ===> 0.)
1265: ]
1266: ] putUsages
1267: /position {
1268: /arg2 set /arg1 set
1269: [/univ /elem /num /flag] pushVariables
1270: [
1271: /univ arg1 def
1272: /elem arg2 def
1273: /num -1 def /flag -1 def
1274: 0 1 << univ length 1 sub >>
1275: {
1276: /num set
1277: univ num get elem eq
1278: { /flag 0 def exit }
1279: { }
1280: ifelse
1281: } for
1282: flag -1 eq
1283: {/num -1 def}
1284: { }
1285: ifelse
1286: ] pop
1287: /arg1 num def
1288: popVariables
1289: arg1
1290: } def
1291:
1292:
1293: [(evecw)
1294: [(size position weight evecw [0 0 ... 0 weight 0 ... 0] )
1295: (Example: 3 0 113 evecw ===> [113 0 0])
1296: ]
1297: ] putUsages
1298: /evecw {
1299: /arg3 set /arg2 set /arg1 set
1300: [/size /iii /www] pushVariables
1301: /size arg1 def /iii arg2 def /www arg3 def
1302: [
1303: 0 1 << size 1 sub >>
1304: {
1305: iii eq
1306: { www }
1307: { 0 }
1308: ifelse
1309: } for
1310: ] /arg1 set
1311: popVariables
1312: arg1
1313: } def
1314:
1315: [(weight_vector)
1316: [ ([x-list d-list params] [[(name) weight ...] [...] ...] weight_vector)
1317: ([x-list d-list params order])
1318: (Example:)
1319: ( [(x,y,z) ring_of_polynomials [[(x) 100 (y) 10]] weight_vector 0] )
1320: ( define_ring )
1321: ]
1322: ] putUsages
1323: /weight_vector {
1324: /arg2 set /arg1 set
1325: [/vars /univ /w-vectors /www /k /order1 /order2] pushVariables
1326: /vars arg1 def /w-vectors arg2 def
1327: [
1328: /univ vars 0 get reverse
1329: vars 1 get reverse join
1330: def
1331: [
1332: 0 1 << w-vectors length 1 sub >>
1333: {
1334: /k set
1335: univ w-vectors k get w_to_vec
1336: } for
1337: ] /order1 set
1338: %% order1 ::
1339:
1340: vars ( ) elimination_order 3 get /order2 set
1341: vars [ << order1 order2 join >> ] join /arg1 set
1342: ] pop
1343: popVariables
1344: arg1
1345: } def
1346:
1347: %% [@@@.esymbol (x) (y) (h)] [(x) 100 (y) 10] w_to_vec [0 100 10 0]
1348: %% univ www
1349: /w_to_vec {
1350: /arg2 set /arg1 set
1351: [/univ /www /k /vname /vweight /ans] pushVariables
1352: /univ arg1 def /www arg2 def
1353: [
1354: /ans << univ length >> -1 0 evecw def
1355: 0 2 << www length 2 sub >>
1356: {
1357: %% ans ::
1358: /k set
1359: www k get /vname set
1360: www << k 1 add >> get /vweight set
1361: << univ length >>
1362: << univ vname position >>
1363: vweight evecw
1364: ans add /ans set
1365: } for
1366: /arg1 ans def
1367: ] pop
1368: popVariables
1369: arg1
1370: } def
1371:
1372: %%%%%%%%%% end of weight_vector macro
1373:
1374: %%%%%%%% eliminatev macro
1375: [(eliminatev)
1376: [([g1 g2 g3 ...gm] [list of variables] eliminatev [r1 ... rp])
1377: (Example: [(x y z - 1). (z-1). (y-1).] [(x) (y)] eliminatev [ z-1 ])
1378: ]
1379: ] putUsages
1380: /eliminatev {
1381: /arg2 set /arg1 set
1382: [/gb /var /vars /ans /k] pushVariables
1383: [
1384: /gb arg1 def
1385: /vars arg2 def
1386: /ans gb def
1387: 0 1 << vars length 1 sub >> {
1388: /k set
1389: ans << vars k get >> eliminatev.tmp
1390: /ans set
1391: } for
1392: /arg1 ans def
1393: ] pop
1394: popVariables
1395: arg1
1396: } def
1397: /eliminatev.tmp {
1398: /arg2 set /arg1 set
1399: [/gb /degs /ans /n /var /ff /rr /gg] pushVariables
1400: [
1401: /gb arg1 def
1402: /var arg2 def
1403: /degs gb {
1404: /gg set
1405: gg (0). eq
1406: { 0 }
1407: { gg (ring) data_conversion /rr set
1408: gg << var rr ,, >> degree
1409: } ifelse
1410: } map def
1411: %%degs message
1412: /ans [
1413: 0 1 << gb length 1 sub >> {
1414: /n set
1415: << degs n get >> 0 eq
1416: { gb n get /ff set
1417: ff (0). eq
1418: { }
1419: { ff } ifelse
1420: }
1421: { } ifelse
1422: } for
1423: ] def
1424: /arg1 ans def
1425: ] pop
1426: popVariables
1427: arg1
1428: } def
1429:
1430: /eliminatev.tmp.org {
1431: /arg2 set /arg1 set
1432: [/gb /degs /ans /n /var /ff] pushVariables
1433: [
1434: /gb arg1 def
1435: /var arg2 def
1436: /degs gb {var . degree} map def
1437: /ans [
1438: 0 1 << gb length 1 sub >> {
1439: /n set
1440: << degs n get >> 0 eq
1441: { gb n get /ff set
1442: ff (0). eq
1443: { }
1444: { ff } ifelse
1445: }
1446: { } ifelse
1447: } for
1448: ] def
1449: /arg1 ans def
1450: ] pop
1451: popVariables
1452: arg1
1453: } def
1454: %%% end of eliminatev macro
1455:
1456: %%% macro for output
1457:
1458: [(isInteger)
1459: [(obj isInteger bool) ]
1460: ] putUsages
1461: /isInteger {
1462: (type?) data_conversion << 0 (type?) data_conversion >> eq
1463: } def
1464:
1465: [(isArray)
1466: [(obj isArray bool) ]
1467: ] putUsages
1468: /isArray {
1469: (type?) data_conversion << [ ] (type?) data_conversion >> eq
1470: } def
1471:
1472: [(isPolynomial)
1473: [(obj isPolynomial bool) ]
1474: ] putUsages
1475: /isPolynomial {
1476: (type?) data_conversion
1477: << [(x) (var) 0] system_variable . (type?) data_conversion >> eq
1478: } def
1479:
1480: [(isString)
1481: [(obj isString bool) ]
1482: ] putUsages
1483: /isString {
1484: (type?) data_conversion
1485: << (Hi) (type?) data_conversion >> eq
1486: } def
1487:
1488: [(isClass)
1489: [(obj isClass bool) ]
1490: ] putUsages
1491: /isClass {
1492: (type?) data_conversion ClassP eq
1493: } def
1494:
1495: [(isUniversalNumber)
1496: [(obj isUniversalNumber bool) ]
1497: ] putUsages
1498: /isUniversalNumber {
1499: (type?) data_conversion UniversalNumberP eq
1500: } def
1501:
1502: [(isDouble)
1503: [(obj isDouble bool) ]
1504: ] putUsages
1505: /isDouble {
1506: (type?) data_conversion DoubleP eq
1507: } def
1508:
1509: [(isRational)
1510: [(obj isRational bool) ]
1511: ] putUsages
1512: /isRational {
1513: (type?) data_conversion RationalFunctionP eq
1.7 takayama 1514: } def
1515:
1516: [(isRing)
1517: [(obj isRing bool) ]
1518: ] putUsages
1519: /isRing {
1520: (type?) data_conversion RingP eq
1.1 maekawa 1521: } def
1522:
1523: /toString.tmp {
1524: /arg1 set
1525: [/obj /fname] pushVariables
1526: /obj arg1 def
1527: [
1528: obj isArray
1529: {
1530: obj {toString.tmp} map
1531: }
1532: { } ifelse
1533: obj isInteger
1534: {
1535: obj (dollar) data_conversion %% not string. It returns the ascii code.
1536: }
1537: { } ifelse
1538: obj isPolynomial
1539: {
1540: obj (string) data_conversion
1541: }
1542: { } ifelse
1543: obj isString
1544: { obj }
1545: { } ifelse
1546: obj isUniversalNumber
1547: { obj (string) data_conversion } { } ifelse
1548: obj isDouble
1549: { obj (string) data_conversion } { } ifelse
1550: obj isRational
1551: { obj (string) data_conversion } { } ifelse
1552: obj tag 0 eq
1553: { (null) } { } ifelse
1554:
1555: %%% New code that uses a file.
1556: obj tag 2 eq obj tag 13 eq or obj tag 14 eq or obj tag 17 eq or
1557: { [(getUniqueFileName) (/tmp/sm1_toString)] extension /fname set
1558: [(outputObjectToFile) fname obj] extension pop
1559: fname pushfile
1560: [(/bin/rm -rf ) fname] cat system
1561: } { } ifelse
1562: ] /arg1 set
1563: popVariables
1564: arg1 aload pop
1565: } def
1566:
1567:
1568:
1569: %% [(xy) [(x+1) (2)]] toString.tmp2 ([ xy , [ x+1 , 2 ] ])
1570: /toString.tmp2 {
1571: /arg1 set
1572: [/obj /i /n /r] pushVariables
1573: [
1574: /obj arg1 def
1575: obj isArray
1576: {
1.2 takayama 1577: [(LeftBracket)] system_variable %%( [ )
1.1 maekawa 1578: obj {toString.tmp2} map /r set
1579: /n r length 1 sub def
1580: [0 1 n {
1581: /i set
1582: i n eq {
1583: r i get
1584: }
1585: { r i get ( , ) 2 cat_n }
1586: ifelse
1587: } for
1588: ] aload length cat_n
1.2 takayama 1589: [(RightBracket)] system_variable %%( ] )
1.1 maekawa 1590: 3 cat_n
1591: }
1592: {
1593: obj
1594: } ifelse
1595: ] /arg1 set
1596: popVariables
1597: arg1 aload pop
1598: } def
1599:
1600:
1601: [(toString)
1602: [(obj toString)
1603: (Convert obj to a string.)
1604: (Example: [ 1 (x+1). [ 2 (Hello)]] toString ==> $[ 1 , x+1 , [ 2 , Hello ] ]$)
1605: ]
1606: ] putUsages
1607: /toString {
1608: /arg1 set
1609: [/obj ] pushVariables
1610: [
1611: /obj arg1 def
1612: obj isString
1613: { obj }
1614: { obj toString.tmp toString.tmp2 }
1615: ifelse /arg1 set
1616: ] pop
1617: popVariables
1618: arg1
1619: } def
1620:
1621: [(output)
1622: [(obj output) (Output the object to the standard file sm1out.txt)]
1623: ] putUsages
1624: /output {
1625: /arg1 set
1626: [/obj /fd ] pushVariables
1627: [
1628: /obj arg1 def
1629: (sm1out.txt) (a) file /fd set
1630: (Writing to sm1out.txt ...) messagen
1631: [ fd << obj toString >> writestring ] pop
1632: [ fd << 10 (string) data_conversion >> writestring ] pop
1633: ( Done.) message
1634: fd closefile
1635: ] pop
1636: popVariables
1637: } def
1638: %%%% end of macro for output.
1639: [(tag)
1640: [(obj tag integer)
1641: (tag returns datatype.)
1642: (cf. data_conversion)
1643: (Example: 2 tag IntegerP eq ---> 1)
1644: ]
1645: ] putUsages
1646: /etag {(type??) data_conversion} def
1647: [(etag)
1648: [(obj etag integer)
1649: (etag returns extended object tag. cf. kclass.c)
1650: ]
1651: ] putUsages
1652: /tag {(type?) data_conversion} def
1653: %% datatype constants
1654: /IntegerP 1 (type?) data_conversion def
1655: /LiteralP /arg1 (type?) data_conversion def %Sstring
1656: /StringP (?) (type?) data_conversion def %Sdollar
1657: /ExecutableArrayP { 1 } (type?) data_conversion def
1658: /ArrayP [ 0 ] (type?) data_conversion def
1659: /PolyP (1). (type?) data_conversion def
1660: /FileP 13 def
1661: /RingP 14 def
1662: /UniversalNumberP 15 def
1663: /RationalFunctionP 16 def
1664: /ClassP 17 def
1665: /DoubleP 18 def
1666: /@.datatypeConstant.usage [
1667: (IntegerP, LiteralP, StringP, ExecutableArrayP, ArrayP, PolyP, FileP, RingP,)
1668: (UniversalNumberP, RationalFunctionP, ClassP, DoubleP)
1669: ( return data type identifiers.)
1670: (Example: 7 tag IntegerP eq ---> 1)
1671: ] def
1672: [(IntegerP) @.datatypeConstant.usage ] putUsages
1673: [(LiteralP) @.datatypeConstant.usage ] putUsages
1674: [(StringP) @.datatypeConstant.usage ] putUsages
1675: [(ExecutableArrayP) @.datatypeConstant.usage ] putUsages
1676: [(ArrayP) @.datatypeConstant.usage ] putUsages
1677: [(PolyP) @.datatypeConstant.usage ] putUsages
1678: [(RingP) @.datatypeConstant.usage ] putUsages
1679: [(UniversalNumberP) @.datatypeConstant.usage ] putUsages
1680: [(RationalFunctionP) @.datatypeConstant.usage ] putUsages
1681: [(ClassP) @.datatypeConstant.usage ] putUsages
1682: [(DoubleP) @.datatypeConstant.usage ] putUsages
1683:
1684: [(,,)
1685: [( string ring ,, polynomial)
1686: (Parse the <<string>> as an element in the <<ring>> and returns)
1687: (the polynomial.)
1688: (cf. define_ring, define_qring, ring_def)
1689: (Example: [(x,y) ring_of_polynomials [[(x) 1]] weight_vector 7]define_ring)
1690: ( /myring set)
1691: ( ((x+y)^4) myring ,, /f set)
1692: ]] putUsages
1693:
1694: /,, {
1695: /arg2 set /arg1 set
1696: [/rrr] pushVariables
1697: [ arg1 tag StringP eq
1698: arg2 tag RingP eq and
1699: { [(CurrentRingp)] system_variable /rrr set
1700: [(CurrentRingp) arg2] system_variable
1701: /arg1 arg1 expand def
1702: [(CurrentRingp) rrr] system_variable
1703: }
1704: {(Argument Error for ,, ) error }
1705: ifelse
1706: ] pop
1707: popVariables
1708: arg1
1709: } def
1710:
1711: [(..)
1712: [( string .. universalNumber)
1713: (Parse the << string >> as a universalNumber.)
1714: (Example: (123431232123123).. /n set)
1715: ]] putUsages
1716: /.. { (universalNumber) data_conversion } def
1717:
1718: [(dc)
1719: [(Abbreviation of data_conversion.)
1720: ]] putUsages
1721: /dc { data_conversion } def
1722:
1723:
1724: %%% start of shell sort macro.
1725: [(and) [(obj1 obj2 and bool)]] putUsages
1726: /and { add 1 copy 2 eq {pop 1} {pop 0} ifelse } def
1727:
1728: [(or) [(obj1 obj2 or bool)]] putUsages
1729: /or { add 1 copy 2 eq {pop 1} { } ifelse} def
1730:
1731: [(ge) [(obj1 obj2 ge bool) (greater than or equal)]] putUsages
1732: %% 2 copy is equivalent to dup 3 -1 roll dup 4 -2 roll 3 -1 roll 2 -1 roll
1733: /ge { dup 3 -1 roll dup 4 -2 roll 3 -1 roll 2 -1 roll
1734: eq {pop pop 1}
1735: { gt {1}
1736: {0}
1737: ifelse}
1738: ifelse} def
1739:
1740: [(le) [(obj1 obj2 le bool) (less than or equal)]] putUsages
1741: /le { dup 3 -1 roll dup 4 -2 roll 3 -1 roll 2 -1 roll
1742: eq {pop pop 1}
1743: { lt {1}
1744: {0}
1745: ifelse}
1746: ifelse} def
1747:
1748: [(break)
1749: [(bool break)]
1750: ] putUsages
1751: /break { {exit} { } ifelse } def
1752:
1753: /not { 0 eq {1} {0} ifelse} def
1754: /append { /arg2 set [arg2] join } def
1755:
1756: [(power)
1757: [(obj1 obj2 power obj3)
1758: $obj3 is (obj1)^(obj2). cf. npower$
1759: $Example: (2). 8 power :: ===> 256 $
1760: ]
1761: ] putUsages
1762: %% From SSWork/yacc/incmac.sm1
1763: %% f k power f^k
1764: /power {
1765: /arg2 set
1766: /arg1 set
1767: [/f /k /i /ans] pushVariables
1768: [
1.26 takayama 1769: /ans (1).. def
1770: [(QuoteMode)] system_variable {
1771: /f arg1 def /k arg2 def
1772: [(ooPower) f k] extension /ans set
1773: } {
1.1 maekawa 1774: /f arg1 def /k arg2 ..int def
1775: k 0 lt {
1776: 1 1 << 0 k sub >> {
1777: /ans f ans {mul} sendmsg2 def
1778: } for
1779: /ans (1).. ans {div} sendmsg2 def
1780: }
1781: {
1782: 1 1 k {
1783: /ans f ans {mul} sendmsg2 def
1784: } for
1785: } ifelse
1.26 takayama 1786: } ifelse
1787: /arg1 ans def
1.1 maekawa 1788: ] pop
1789: popVariables
1790: arg1
1791: } def
1792: [(..int)
1793: [ (universalNumber ..int int)]] putUsages
1794: /..int { %% universal number to int
1795: (integer) data_conversion
1796: } def
1797: [(SmallRing) [(SmallRing is the ring of polynomials Q[t,x,T,h].)]] putUsages
1798: /SmallRing [(CurrentRingp)] system_variable def
1799:
1800: %%% From SSWork/yacc/lib/printSVector.modified.sm1
1801: %%% supporting code for printSVector.
1802: /greaterThanOrEqual {
1803: /arg2 set /arg1 set
1804: arg1 arg2 gt { 1 }
1805: { arg1 arg2 eq {1} {0} ifelse} ifelse
1806: } def
1807:
1808: /lengthUniv {
1809: length (universalNumber) dc
1810: } def
1811:
1812: /getUniv {
1813: (integer) dc get
1814: } def %% Do not forget to thow away /.
1815:
1816: %%[(@@@.printSVector)
1817: %% [( vector @@@.printSVector outputs the <<vector>> in a pretty way.)
1818: %% ( The elements of the vector must be strings.)
1819: %% ]
1820: %%] putUsages
1821:
1822: %%% compiled code by d0, 1996, 8/17.
1823: /@@@.printSVector {
1824: /arg1 set
1825: [ %%start of local variables
1826: /keys /i /j /n /max /width /m /k /kk /tmp0 ] pushVariables [ %%local variables
1827: /keys arg1 def
1828: /n
1829: keys lengthUniv
1830: def
1831: /max (0).. def
1832: /i (0).. def
1833: %%for init.
1834: %%for
1835: { i n lt
1836: { } {exit} ifelse
1837: [ {%%increment
1838: /i i (1).. add def
1839: } %%end of increment{A}
1840: {%%start of B part{B}
1841: keys i getUniv lengthUniv
1842: max gt
1843: %% if-condition
1844: { %%ifbody
1845: /max
1846: keys i getUniv lengthUniv
1847: def
1848: }%%end if if body
1849: { %%if- else part
1850: } ifelse
1851: } %% end of B part. {B}
1852: 2 1 roll] {exec} map
1853: } loop %%end of for
1854: /max max (3).. add
1855: def
1856: /width (80).. def
1857: /m (0).. def
1858:
1859: %%while
1860: { m max mul
1861: (80).. lt
1862: { } {exit} ifelse
1863: /m m (1).. add
1864: def
1865: } loop
1866: /k (0).. def
1867: /kk (0).. def
1868: /i (0).. def
1869: %%for init.
1870: %%for
1871: { i n lt
1872: { } {exit} ifelse
1873: [ {%%increment
1874: /i i (1).. add def
1875: } %%end of increment{A}
1876: {%%start of B part{B}
1877: keys i getUniv messagen
1878: /kk kk (1).. add
1879: def
1880: /k k
1881: keys i getUniv lengthUniv
1882: add
1883: def
1884: /tmp0 max
1885: keys i getUniv lengthUniv
1886: sub
1887: def
1888: /j (0).. def
1889: %%for init.
1890: %%for
1891: { j tmp0 lt
1892: { } {exit} ifelse
1893: [ {%%increment
1894: /j j (1).. add def
1895: } %%end of increment{A}
1896: {%%start of B part{B}
1897: /k k (1).. add
1898: def
1899: kk m lt
1900: %% if-condition
1901: { %%ifbody
1902: ( ) messagen
1903: }%%end if if body
1904: { %%if- else part
1905: } ifelse
1906: } %% end of B part. {B}
1907: 2 1 roll] {exec} map
1908: } loop %%end of for
1909: kk m greaterThanOrEqual
1910: %% if-condition
1911: { %%ifbody
1912: /kk (0).. def
1913: /k (0).. def
1914: newline
1915: }%%end if if body
1916: { %%if- else part
1917: } ifelse
1918: } %% end of B part. {B}
1919: 2 1 roll] {exec} map
1920: } loop %%end of for
1921: newline
1922: /ExitPoint ]pop popVariables %%pop the local variables
1923: } def
1924: %%end of function
1925:
1926: /rest { % returns remainder of a given list
1927: [ 2 1 roll aload length -1 roll pop ]
1928: } def
1929: [(rest)
1930: [(array rest the-rest-of-the-array)
1931: (Ex. [1 2 [3 0]] rest ===> [2 [3 0]])
1932: ]
1933: ] putUsages
1934:
1935: %% from SSkan/develop/minbase.sm1
1936: /reducedBase {
1937: /arg1 set
1938: [/base /minbase /n /i /j /myring /zero /f] pushVariables
1939: [
1940: /base arg1 def
1941: base isArray { }
1942: { (The argument of reducedBase must be an array of polynomials)
1943: error
1944: } ifelse
1945: base 0 get isPolynomial { }
1946: { (The element of the argument of reducedBase must be polynomials)
1947: error
1948: } ifelse
1949: /myring base 0 get (ring) dc def
1950: /zero (0) myring ,, def
1951: base length 1 sub /n set
1952: /minbase [ 0 1 n { /i set base i get } for ] def
1953: 0 1 n {
1954: /i set
1955: minbase i get /f set
1956: f zero eq {
1957: }
1958: {
1959: 0 1 n {
1960: /j set
1961: << minbase j get zero eq >> << i j eq >> or {
1962: }
1963: {
1964: [(isReducible) << minbase j get >> f] gbext
1965: {
1966: minbase j zero put
1967: }
1968: { } ifelse
1969: } ifelse
1970: } for
1971: } ifelse
1972: } for
1973: minbase { minbase.iszero } map /arg1 set
1974: ] pop
1975: popVariables
1976: arg1
1977: } def
1978:
1979: [(reducedBase)
1980: [(base reducedBase reducedBase)
1981: (<<reducedBase>> prunes redundant elements in the Grobner basis <<base>> and)
1982: (returns <<reducedBase>>.)
1983: (Ex. [(x^2+1). (x+1). (x^3).] reducedBase ---> [(x+1).])
1984: ]
1985: ] putUsages
1986:
1987: %% package functions
1988: /minbase.iszero {
1989: dup (0). eq {
1990: pop
1991: }
1992: { } ifelse
1993: } def
1994:
1995: /== {
1996: message
1997: } def
1998: [(==)
1999: [(obj ==)
2000: (Print obj)
2001: ]
2002: ] putUsages
2003:
2004: /@@@.all_variables {
2005: [/n /i] pushVariables
2006: [
2007: /n [(N)] system_variable def
2008: [
2009: 0 1 n 1 sub {
2010: /i set
2011: [(x) (var) i] system_variable
2012: } for
2013: 0 1 n 1 sub {
2014: /i set
2015: [(D) (var) i] system_variable
2016: } for
2017: ] /arg1 set
2018: ] pop
2019: popVariables
2020: arg1
2021: } def
2022:
2023: /weightv {
2024: @@@.all_variables
2025: 2 1 roll w_to_vec
2026: } def
2027:
2028: [(weightv)
2029: [(array weightv weight_vector_for_init)
2030: (cf. init)
2031: (Example: /w [(x) 10 (h) 2] weightv def)
2032: ( ((x-h)^10). w init ::)
2033: ]
2034: ] putUsages
2035:
2036: /output_order {
2037: /arg1 set
2038: [/vars /vlist /perm /total /ans] pushVariables
2039: [
2040: /vlist arg1 def
2041: /vars @@@.all_variables def
2042: vlist { vars 2 1 roll position } map /perm set
2043: perm ==
2044: /total [ 0 1 [(N)] system_variable 2 mul 1 sub { } for ] def
2045: perm perm total complement join /ans set
2046: [(outputOrder) ans] system_variable
2047: ] pop
2048: popVariables
2049: } def
2050:
2051: [(output_order)
2052: [$ [(v1) (v2) ...] output_order $
2053: (Set the order of variables to print for the current ring.)
2054: (cf. system_variable)
2055: (Example: [(y) (x)] output_order)
2056: $ (x*y). :: ===> y*x $
2057: ]
2058: ] putUsages
2059:
2060: %% destraction. SSkan/Kan/debug/des.sm1, 1998, 2/27 , 3/1
2061: %% should be included in dr.sm1
2062:
2063: /factorial {
2064: /arg2 set
2065: /arg1 set
2066: [ /f /n ] pushVariables
2067: [
2068: /f arg1 def
2069: /n arg2 def
2070: /ans (1).. def
2071: n 0 lt { (f n factorial : n must be a non-negative integer)
2072: error } { } ifelse
2073: 0 1 n 1 sub {
2074: (universalNumber) dc /i set
2075: ans << f i sub >> mul /ans set
2076: } for
2077: /arg1 ans def
2078: ] pop
2079: popVariables
2080: arg1
2081: } def
2082:
2083: [(factorial)
2084: [(f n factorial g)
2085: $integer n, g is f (f-1) ... (f-n+1)$
2086: ]
2087: ] putUsages
2088:
2089:
2090: /destraction1 {
2091: /arg4 set
2092: /arg3 set
2093: /arg2 set
2094: /arg1 set
2095: [/ww /f /dx /ss /xx /coeff0 /expvec
2096: /coeffvec /expvec2 /ans /one] pushVariables
2097: [
2098: /f arg1 def /xx arg2 def /dx arg3 def /ss arg4 def
2099: /one (1). def %%
2100: /ww [ xx toString -1 dx toString 1 ] weightv def
2101: f ww init f sub (0). eq { }
2102: { [(destraction1 : inhomogeneous with respect to )
2103: xx ( and ) dx ] cat error } ifelse
2104: f [[xx one]] replace dx coefficients /coeff0 set
2105: /expvec coeff0 0 get { (integer) dc } map def
2106: /coeffvec coeff0 1 get def
2107: expvec { ss 2 -1 roll factorial } map /expvec2 set
2108: expvec2 coeffvec mul /ans set
2109: /arg1 ans def
2110: ] pop
2111: popVariables
2112: arg1
2113: } def
2114:
2115:
2116: /distraction {
2117: /arg4 set
2118: /arg3 set
2119: /arg2 set
2120: /arg1 set
2121: [/f /dx /ss /xx /ans /n /i] pushVariables
2122: [(CurrentRingp)] pushEnv
2123: [
2124: /f arg1 def /xx arg2 def /dx arg3 def /ss arg4 def
2125: f (0). eq { /dist1.L goto } { f (ring) dc ring_def } ifelse
2126: /n xx length def
2127: 0 1 n 1 sub {
2128: /i set
2129: /f f xx i get dx i get ss i get destraction1 /f set
2130: } for
2131: /dist1.L
2132: /arg1 f def
2133: ]pop
2134: popEnv
2135: popVariables
2136: arg1
2137: } def
2138: [(distraction)
2139: [(f [ list of x-variables ] [ list of D-variables ] [ list of s-variables ])
2140: ( distraction result )
2141: $Example: (x Dx Dy + Dy). [(x). (y).] [(Dx). (Dy).] [(x). (y).] distraction$
2142: ]
2143: ] putUsages
2144: /destraction { distraction } def
2145:
2146:
2147:
2148:
2149: %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2150: %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2151: %%%%%%%%%%%%%%%% sorting
2152: %/N 1000 def
2153: %/a.shell [N -1 0 { } for ] def
2154: %a.shell 0 -1000 put
2155: %% You need gate keeper.
2156: [(shell)
2157: [([gate-keeper f1 f2 ... fm] shell result)
2158: (Sort the list. Gate-keeper should be the smallest element)]
2159: ] putUsages
2160: /shell {
2161: /arg1 set
2162: [/N /a.shell /h /i /v /j] pushVariables
2163: [
2164: /a.shell arg1 def
2165: /N a.shell length 1 sub def
2166:
2167: /h 1 def
2168: {/h h 3 mul 1 add def
2169: << h N ge >> break
2170: } loop
2171: {
2172: /h << h 3 idiv >> def
2173: << h 1 add >> 1 N {
2174: /i set
2175: /v a.shell i get def
2176: /j i def
2177: {
2178: %% a.shell print newline
2179: << a.shell << j h sub >> get >> v le break
2180: a.shell j << a.shell << j h sub >> get >> put
2181: /j j h sub def
2182: j h le break
2183: } loop
2184: a.shell j v put
2185: } for
2186: h 1 lt break
2187: } loop
2188: /arg1 a.shell def
2189: ] pop
2190: popVariables
2191: arg1
2192: } def
2193: %%%% end of shell sort macro
2194:
2195: /variableNames {
2196: /arg1 set
2197: [/in-variableNames /rrr /nnn /i /cp] pushVariables
2198: [
2199: /rrr arg1 def
2200: [(CurrentRingp)] system_variable /cp set
2201: [(CurrentRingp) rrr] system_variable
2202: [(N)] system_variable /nnn set
2203: [ 0 1 nnn 1 sub {
2204: /i set [(x) (var) i] system_variable } for ]
2205: [ 0 1 nnn 1 sub {
2206: /i set [(D) (var) i] system_variable } for ]
2207: join /arg1 set
2208: [(CurrentRingp) cp] system_variable
2209: ] pop
2210: popVariables
2211: arg1
2212: } def
2213:
2214:
2215: /makeRingMap {
2216: /arg3 set /arg2 set /arg1 set
2217: [/in-makeRingMap /corres /M /N /corresM /corresN
2218: /vars /vars-org /i /p /ans /cp] pushVariables
2219: [
2220: /corres arg1 def /M arg2 def /N arg3 def
2221: /corresM corres 0 get def
2222: /corresN corres 1 get def
2223: [(CurrentRingp)] system_variable /cp set
2224: [(CurrentRingp) M] system_variable
2225: M variableNames /vars set vars 1 copy /vars-org set
2226: 0 1 corresM length 1 sub {
2227: /i set
2228: vars corresM i get position /p set
2229: p -1 gt {
2230: vars p $($ corresN i get $)$ 3 cat_n put
2231: } { } ifelse
2232: } for
2233: /arg1 [vars M N vars-org] def
2234: [(CurrentRingp) cp] system_variable
2235: ] pop
2236: popVariables
2237: arg1
2238: } def
2239:
2240:
2241:
2242: /ringmap {
2243: /arg2 set /arg1 set
2244: [/in-ringmap /f /M2N /cp /f2] pushVariables
2245: [
2246: /f arg1 def /M2N arg2 def
2247: [(CurrentRingp)] system_variable /cp set
2248: f (0). eq { /f2 f def }
2249: {
2250: %f (ring) dc M2N 1 get eq
2251: %{ }
2252: %{ (The argument polynomial does not belong to the domain ring.) message
2253: % error
2254: % } ifelse
2255: [(CurrentRingp) M2N 1 get] system_variable
2256: [(variableNames) M2N 0 get] system_variable
2257: f toString /f2 set
2258: [(variableNames) M2N 3 get] system_variable
2259: f2 M2N 2 get ,, /f2 set
2260: } ifelse
2261: [(CurrentRingp) cp] system_variable
2262: /arg1 f2 def
2263: ] pop
2264: popVariables
2265: arg1
2266: } def
2267:
2268: [(makeRingMap)
2269: [( rule ring1 ring2 makeRingMap maptable )
2270: (makeRingMap is an auxiliary function for the macro ringmap. See ringmap)
2271: ]
2272: ] putUsages
2273: [(ringmap)
2274: [(f mapTable ringmap r)
2275: (f is mapped to r where the map is defined by the mapTable, which is generated)
2276: (by makeRingMap as follows:)
2277: ( rule ring1 ring2 makeRingMap maptable )
2278: $Example:$
2279: $[(x,y) ring_of_differential_operators ( ) elimination_order 0] define_ring$
2280: $/R1 set$
2281: $[(t,y,z) ring_of_differential_operators ( ) elimination_order 0] define_ring$
2282: $/R2 set$
2283: $[[(x) (Dx)] [((t-1) Dt) (z)]] /r0 set$
2284: $r0 R1 R2 makeRingMap /maptable set$
2285: $(Dx-1) R1 ,, /ff set$
2286: $ ff maptable ringmap :: $
2287: ]
2288: ] putUsages
2289:
2290:
2291: /getVariableNames {
2292: [/in-getVariableNames /ans /i /n] pushVariables
2293: [
2294: /n [(N)] system_variable def
2295: [
2296: n 1 sub -1 0 {
2297: /i set
2298: [(x) (var) i] system_variable
2299: } for
2300: n 1 sub -1 0{
2301: /i set
2302: [(D) (var) i] system_variable
2303: } for
2304: ] /arg1 set
2305: ] pop
2306: popVariables
2307: arg1
2308: } def
2309: [(getVariableNames)
2310: [(getVariableNames list-of-variables)
2311: (Example: getVariableNames :: [e,x,y,E,H,Dx,Dy,h])
2312: ]
2313: ] putUsages
2314:
2315: /tolower {
2316: /arg1 set
2317: [/in-tolower /s /sl] pushVariables
2318: [
2319: /s arg1 def
2320: s (array) dc /s set
2321: s { tolower.aux (string) dc } map /sl set
2322: sl aload length cat_n /arg1 set
2323: ] pop
2324: popVariables
2325: arg1
2326: } def
2327:
2328: /tolower.aux {
2329: /arg1 set
1.9 takayama 2330: arg1 64 gt arg1 91 lt and
1.1 maekawa 2331: { arg1 32 add }
2332: { arg1 } ifelse
2333: } def
2334: [(tolower)
2335: [(string tolower string2)
2336: (Capital letters in string are converted to lower case letters.)
2337: $Example: (Hello World) tolower :: (hello world)$
2338: ]
2339: ] putUsages
2340:
2341: /hilbert {
2342: /arg2 set
2343: /arg1 set
2344: [/in-hilb /base /vlist /rrrorg /rrr /ff /strf] pushVariables
2345: [
2346: /base arg1 def
2347: /vlist arg2 def
2348: [(CurrentRingp)] system_variable /rrrorg set
2349: /strf 0 def
2350: vlist isString
2351: { /vlist [ vlist to_records pop ] def }
2352: { } ifelse
2353: base isArray { }
2354: { (hilb : the first argument must be an array of polynomials.)
2355: error
2356: } ifelse
2357: vlist isArray { }
2358: { (hilb : the second argument must be an array of polynomials.)
2359: error
2360: } ifelse
2361:
2362: vlist 0 get isString{ /strf 1 def } { } ifelse
2363: base 0 get isPolynomial {
2364: base 0 get (ring) dc /rrr set
2365: }
2366: {
2367: [ vlist { (,) } map aload length cat_n ring_of_polynomials 0 ] define_ring
2368: /rrr set
2369: base { . } map /base set
2370: } ifelse
2371: vlist { dup isPolynomial { } { rrr ,, } ifelse } map /vlist set
2372:
2373: [(hilbert) base vlist] extension /ff set
2374: [(CurrentRingp) rrrorg] system_variable
2375: /arg1 ff def
2376: ] pop
2377: popVariables
2378: arg1
2379: } def
2380:
2381: /hilbReduce {
2382: /arg2 set
2383: /arg1 set
2384: [/hhh /f /d /vv /ans] pushVariables
2385: [
2386: /hhh arg1 def %% hilbert function
2387: /vv arg2 def
2388: /f hhh 1 get def
2389: f (0). eq { /ans [0] def /hilbReduce.label goto } { } ifelse
2390: f vv << f (ring) dc >> ,, degree /vv set
2391: hhh 0 get /d set
2392: d d (integer) dc factorial /d set
2393: d << vv (universalNumber) dc vv factorial >> idiv /d set
2394: [(divByN) f d] gbext /ans set
2395: ans 1 get (0). eq
2396: { }
2397: { (hilbReduce : Invalid hilbert function ) error } ifelse
2398: /hilbReduce.label
2399: ans 0 get /arg1 set
2400: ] pop
2401: popVariables
2402: arg1
2403: } def
2404:
2405:
2406: [(hilbReduce)
2407: [([f,g] v hilbReduce p)
2408: (output of hilbert [f,g]; string v; poly p)
2409: (p is (g/(f!))*deg(g)!)
2410: $ [(x) (y^3)] (x,y,z) hilbert (h) hilbReduce $
2411: ]
2412: ] putUsages
2413: [(hilbert)
2414: [(base vlist hilbert [m f])
2415: (array of poly base; array of poly vlist; number m; poly f;)
2416: (array of string base; array of string vlist; number m; poly f;)
2417: (array of string base; string vlist; number m; poly f;)
2418: ([m f] represents the hilbert function (a_d x^d + ...)/m! where f=a_d x^d + ...)
2419: (The << base >> should be a reduced Grobner basis.)
2420: (Or, when the << base >> is an array of string,)
2421: (all entries should be monomials.)
2422: (Example: [(x^2) (x y )] (x,y) hilbert :: [2, 2 h + 4] )
2423: (Example: [(x^2) (y^2)] (x,y) hilbert (h) hilbReduce :: 4)
2424: (Example: [(x^2) (y^2) (x y)] [(x) (y)] hilbert (h) hilbReduce :: 3)
2425: (cf. hilb, hilbReduce)
2426: ]
2427: ] putUsages
2428:
2429: /hilb {
2430: hilbert (h) hilbReduce
2431: } def
2432: [(hilb)
2433: [(base vlist hilb f)
2434: (array of poly base; array of poly vlist; poly f;)
2435: (array of string base; array of string vlist; poly f;)
2436: (array of string base; string vlist; number m; poly f;)
2437: (f is the hilbert function (a_d x^d + ...)/m!)
2438: (The << base >> should be a reduced Grobner basis.)
2439: (Or, when the << base >> is an array of string,)
2440: (all entries should be monomials.)
2441: (Example: [(x^2) (x y )] (x,y) hilb :: h + 2 )
2442: (Example: [(x^2) (y^2)] (x,y) hilb 4)
2443: (Example: [(x^2) (y^2) (x y)] [(x) (y)] hilb :: 3)
2444: (cf. hilbert, hilbReduce)
2445: ]
2446: ] putUsages
2447:
2448: [(diff0)
2449: [ (f v n diff0 fn)
2450: (<poly> fn, v ; <integer> n ; <poly> fn)
2451: (fn = v^n f where v^n is the operator to take the n-th differential.)
2452: (We can use diff0 only in the ring of differential operators.)
2453: (Example: [(x) ring_of_differential_operators 0] define_ring )
2454: ( (x^10-x). (Dx). 1 diff0 ::)
2455: ]
2456: ] putUsages
2457: /diff0 {
2458: /arg3 set /arg2 set /arg1 set
2459: [/in-diff /f /v /n /fn /rrr] pushVariables
2460: [
2461: /f arg1 def /v arg2 def /n arg3 def
2462: f (0). eq
2463: { /fn (0). def }
2464: {
2465: f (ring) dc /rrr set
2466: v toString (^) n toString 3 cat_n rrr ,,
2467: f mul
2468: [[v (0).] [(h) rrr ,, (1) rrr ,,]] replace /fn set
2469: } ifelse
2470: fn /arg1 set
2471: ] pop
2472: popVariables
2473: arg1
2474: } def
2475:
2476: [(action)
2477: [( f g action p )
2478: (<poly> f,g,p)
2479: (Act f on g. The result is p. The homogenization variable h is put to 1.)
2480: (We can use diff0 only in the ring of differential operators.)
2481: (Example: [(x) ring_of_differential_operators 0] define_ring )
2482: ( (Dx^2). (x^2). action ::)
2483: ]
2484: ] putUsages
2485: /action {
2486: /arg2 set /arg1 set
2487: [/in-action /f /g /h /rr /rr.org /rule] pushVariables
2488: [
2489: /f arg1 def /g arg2 def
2490: /rr.org [(CurrentRingp)] system_variable def
2491: f (0). eq
2492: { /h (0). def }
2493: {
2494: f (ring) dc /rr set
2495: [(CurrentRingp) rr] system_variable
2496: f g mul /h set
2497: /rule getVariableNames def
2498: 0 1 rule length 2 idiv { rule rest /rule set } for
2499: rule { . [ 2 1 roll (0). ] } map /rule set
2500: rule << rule length 1 sub >> [(h). (1).] put
2501: %%ex. rule = [[(Dx1). (0).] [(Dx2). (0).] [(h). (1).]]
2502: /h h rule replace def
2503: } ifelse
2504: [(CurrentRingp) rr.org ] system_variable
2505: /arg1 h def
2506: ] pop
2507: popVariables
2508: arg1
2509: } def
2510:
2511: [(ord_w)
2512: [(ff [v1 w1 v2 w2 ... vm wm] ord_w d)
2513: (poly ff; string v1; integer w1; ...)
1.11 takayama 2514: (order of the initial of ff by the weight vector [w1 w2 ...])
1.1 maekawa 2515: (Example: [(x,y) ring_of_polynomials 0] define_ring )
2516: ( (x^2 y^3-x). [(x) 2 (y) 1] ord_w ::)
2517: ]
2518: ] putUsages
2519: /ord_w {
2520: /arg2 set /arg1 set
2521: [/ord_w-in /fff /www /rrr /iii /ddd] pushVariables
2522: [
2523: /fff arg1 def
2524: /www arg2 def
2525: fff (0). eq { /ddd -intInfinity def /ord_w.LLL goto} { } ifelse
2526: fff (ring) dc /rrr set
2527: fff init /fff set
2528: /ddd 0 def
2529: 0 2 www length 1 sub {
2530: /iii set
2531: fff << www iii get rrr ,, >> degree
2532: << www iii 1 add get >> mul
2533: ddd add /ddd set
2534: } for
1.12 takayama 2535: /ord_w.LLL
2536: /arg1 ddd def
2537: ] pop
2538: popVariables
2539: arg1
2540: } def
2541:
2542: [(ord_w_all)
2543: [(ff [v1 w1 v2 w2 ... vm wm] ord_w d)
2544: (poly ff; string v1; integer w1; ...)
2545: (order of ff by the weight vector [w1 w2 ...])
2546: (Example: [(x,y,t) ring_of_polynomials 0] define_ring )
2547: ( (x^2 y^3-x-t). [(t) 1 ] ord_w_all ::)
2548: ]
2549: ] putUsages
2550: /ord_w_all {
2551: /arg2 set /arg1 set
1.13 takayama 2552: [/ord_w_all-in /fff /fff-in /www /rrr /iii /ddd /zzz /ddd-tmp] pushVariables
1.12 takayama 2553: [
2554: /fff arg1 def
2555: /www arg2 def
1.13 takayama 2556: fff (0). eq { /ddd -intInfinity def /ord_w_all.LLL goto} { } ifelse
2557: /ddd -intInfinity def
1.12 takayama 2558: fff (ring) dc /rrr set
2559: /zzz (0) rrr ,, def
2560: fff init /fff-in set
2561: fff fff-in sub /fff set
2562: {
1.13 takayama 2563: /ddd-tmp 0 def
1.12 takayama 2564: 0 2 www length 1 sub {
2565: /iii set
2566: fff-in << www iii get rrr ,, >> degree
2567: << www iii 1 add get >> mul
1.13 takayama 2568: ddd-tmp add /ddd-tmp set
1.12 takayama 2569: } for
1.13 takayama 2570: ddd-tmp ddd gt { /ddd ddd-tmp def } { } ifelse
1.12 takayama 2571: fff zzz eq { exit } { } ifelse
2572: fff init /fff-in set
2573: fff fff-in sub /fff set
2574: } loop
1.13 takayama 2575: /ord_w_all.LLL
1.1 maekawa 2576: /arg1 ddd def
2577: ] pop
2578: popVariables
2579: arg1
2580: } def
2581:
2582: [(laplace0)
2583: [
2584: (f [v1 ... vn] laplace0 g)
2585: (poly f ; string v1 ... vn ; poly g;)
2586: (array of poly f ; string v1 ... vn ; array of poly g;)
2587: ( g is the lapalce transform of f with respect to variables v1, ..., vn.)
2588: $Example: (x Dx + y Dy + z Dz). [(x) (y) (Dx) (Dy)] laplace0$
2589: $ x --> -Dx, Dx --> x, y --> -Dy, Dy --> y. $
2590: ]
2591: ] putUsages
2592: /laplace0 {
2593: /arg2 set /arg1 set
2594: [/in-laplace0 /ff /rule /vv /nn /ii /v0 /v1 /rr /ans1 /Dascii
2595: ] pushVariables
2596: [
2597: /ff arg1 def /vv arg2 def
2598: /Dascii @@@.Dsymbol (array) dc 0 get def %%D-clean
2599: /rule [ ] def
2600: ff isPolynomial {
2601: ff (0). eq { /ans1 (0). def }
2602: {
2603: ff (ring) dc /rr set
2604: /nn vv length def
2605: 0 1 nn 1 sub {
2606: /ii set
2607: vv ii get (type?) dc 1 eq
2608: { } % skip, may be weight [(x) 2 ] is OK.
2609: {
2610: /v0 vv ii get (string) dc def
2611: v0 (array) dc 0 get Dascii eq %% If the first character is D?
2612: { rule %% Dx-->x
2613: [v0 rr ,,
2614: v0 (array) dc rest { (string) dc} map aload length cat_n rr ,,]
2615: append /rule set
2616: }
2617: { rule %% x --> -Dx
2618: [v0 rr ,,
2619: (0).
2620: [Dascii] v0 (array) dc join { (string) dc } map aload length
2621: cat_n rr ,, sub
2622: ]
2623: append /rule set
2624: } ifelse
2625: } ifelse
2626: } for
2627: % rule message
2628: ff rule replace [[(h) rr ,, (1) rr ,,]] replace /ans1 set
2629: } ifelse
2630: }
2631: {
2632: ff isArray { /ans1 ff {vv laplace0 } map def }
2633: {
2634: (laplace0 : the first argument must be a polynomial.) error
2635: }ifelse
2636: } ifelse
2637: /arg1 ans1 def
2638: ] pop
2639: popVariables
2640: arg1
2641: } def
2642:
2643: [(ip1)
2644: [( [v1 ... vn] [w1 ... wn] m ip1 [f1 ... fs])
2645: (<poly> v1 ... vn ; <integer> w1 ... wn m)
2646: (<poly> f1 ... fs )
2647: (Example: [(x,y) ring_of_differential_operators 0] define_ring )
2648: ( [(Dx). (Dy).] [2 1] 3 ip1 :: [(2 Dx Dy). (Dy^3).])
2649: ( Returns Dx^p Dy^q such that 2 p + 1 q = 3.)
2650: ]
2651: ] putUsages
2652: /ip1 {
2653: /arg3 set /arg2 set /arg1 set
2654: [/in-ip1 /vv /ww /m /ans /k /tt /rr /rr.org /ff /tmp1] pushVariables
2655: [
2656: /vv arg1 def /ww arg2 def /m arg3 def
2657: vv 0 get (ring) dc /rr set
2658: /rr.org [(CurrentRingp)] system_variable def
2659: [(CurrentRingp) rr] system_variable
2660: [(x) (var) [(N)] system_variable 1 sub ] system_variable . /tt set
2661: /ans [ ] def
2662: m 0 lt
2663: { }
2664: {
2665: vv
2666: ww { tt 2 1 roll power } map mul /tmp1 set
2667: %% (tmp1 = ) messagen tmp1 message
2668: 0 1 m {
2669: /k set
2670: k 0 eq {
2671: /ff (1). def
2672: }
2673: { tmp1 k power /ff set } ifelse
2674: ff [[(h). (1).]] replace /ff set
2675: %% ff message
2676: {
2677: ff init tt degree m eq {
2678: /ans ans [ ff init [[tt (1).]] replace ] join def
2679: } { } ifelse
2680: ff ff init sub /ff set
2681: ff (0). eq { exit } { } ifelse
2682: } loop
2683: } for
2684: } ifelse
2685: [(CurrentRingp) rr.org] system_variable
2686: /arg1 ans def
2687: ] pop
2688: popVariables
2689: arg1
2690: } def
2691:
2692: [(findIntegralRoots)
2693: [( f findIntegralRoots vlist)
2694: (poly f; list of integers vlist;)
2695: (string f; list of integers vlist;)
2696: (f is a polynomials in one variable s. vlist the list of integral roots sorted.)
2697: (Example: (s^4-1) findIntegralRoots )
2698: ]
2699: ] putUsages
2700:
2701: /findIntegralRoots { findIntegralRoots.slow } def
2702:
2703: /findIntegralRoots.slow { %% by a stupid algorithm
2704: /arg1 set
2705: [/in-findIntegralRoots
2706: /ff /kk /roots /rrr /nn /k0 /d.find
2707: ] pushVariables
2708: [
2709: /ff arg1 def
2710: /roots [ ] def
2711: /rrr [(CurrentRingp)] system_variable def
2712: ff toString /ff set
2713: [(s) ring_of_polynomials ( ) elimination_order 0] define_ring
2714: ff . /ff set
2715:
2716: %%ff message %% Cancel the common numerical factor of the polynomial ff.
2717: ff (s). coeff 1 get { (universalNumber) dc } map ngcd /d.find set
2718: [(divByN) ff d.find] gbext 0 get /ff set
2719: %% d.find message
2720: %% ff message
2721:
2722: ff [[(s). (0).]] replace /k0 set
2723: k0 (universalNumber) dc /k0 set
2724: k0 (0).. eq { roots (0).. append /roots set } { } ifelse
2725:
2726: {
2727: ff [[(s). (0).]] replace /nn set
2728: nn (universalNumber) dc /nn set
2729: nn (0).. eq
2730: { (s^(-1)). ff mul /ff set }
2731: { exit }
2732: ifelse
2733: } loop
2734: ff [[(s). (0).]] replace /k0 set
2735: k0 (universalNumber) dc /k0 set
2736: k0 (-40000).. gt k0 (40000).. lt and not {
2737: [(Roots of b-function cannot be obtained by a stupid method.) nl
2738: (Use ox_asir for efficient factorizations, or restall and bfm manually.)
2739: nl
2740: (ox_asir server will be distributed from the asir ftp cite.) nl
2741: (See lib/ttt.tex for details.) nl
2742: ] cat
2743: error
2744: } { } ifelse
2745: nn (0).. lt { (0).. nn sub /nn set } { } ifelse
2746: /kk (0).. nn sub def
2747: /roots [ kk (1).. sub ] roots join def
2748: {
2749: kk nn gt { exit } { } ifelse
2750: ff [[(s). kk (poly) dc]] replace
2751: (0). eq
2752: { /roots roots kk append def }
2753: { } ifelse
2754: kk (1).. add /kk set
2755: } loop
2756: [(CurrentRingp) rrr] system_variable
2757: roots { (integer) dc } map /roots set %% ?? OK?
2758: roots shell rest /roots set
2759: /arg1 roots def
2760: ] pop
2761: popVariables
2762: arg1
2763: } def
2764:
2765: /ngcd {
2766: /arg1 set
2767: [/in-ngcd /nlist /g.ngcd /ans] pushVariables
2768: [
2769: /nlist arg1 def
2770: nlist length 2 lt
2771: { /ans nlist 0 get def /L.ngcd goto }
2772: {
2773: [(gcd) nlist 0 get nlist 1 get] mpzext /g.ngcd set
2774: g.ngcd (1).. eq { /ans (1).. def /L.ngcd goto } { } ifelse
2775: [g.ngcd] nlist rest rest join ngcd /ans set
2776: } ifelse
2777: /L.ngcd
2778: ans /arg1 set
2779: ] pop
2780: popVariables
2781: arg1
2782: } def
2783:
2784: [(ngcd)
2785: [(nlist ngcd d )
2786: (list of numbers nlist; number d;)
2787: (d is the gcd of the numbers in nlist.)
2788: (Example: [(12345).. (67890).. (98765)..] ngcd )
2789: ]] putUsages
2790:
2791: /dehomogenize {
2792: /arg1 set
2793: [/in-dehomogenize /f /rr /ans /cring] pushVariables
2794: [
2795: /f arg1 def
2796: f isPolynomial {
2797: f (0). eq
2798: { f /ans set }
2799: {
2800: f (ring) dc /rr set
2801: [(CurrentRingp)] system_variable /cring set
2802: [(CurrentRingp) rr] system_variable
2803: f [[[(D) (var) 0] system_variable . (1). ]] replace /ans set
2804: [(CurrentRingp) cring] system_variable
2805: } ifelse
2806: }
2807: {
2808: f isArray {
2809: f { dehomogenize } map /ans set
2810: }
2811: {(dehomogenize: argument should be a polynomial.) error }
2812: ifelse
2813: } ifelse
2814: /arg1 ans def
2815: ] pop
2816: popVariables
2817: arg1
2818: } def
2819:
2820: [(dehomogenize)
2821: [(obj dehomogenize obj2)
2822: (dehomogenize puts the homogenization variable to 1.)
2823: (Example: (x*h+h^2). dehomogenize :: x+1 )
2824: ]
2825: ] putUsages
2826:
2827:
2828: /from_records { { (,) } map aload length cat_n } def
2829: [(from_records)
2830: [ ([s1 s2 s3 ... sn] from_records (s1,s2,...,sn,))
2831: (Example : [(x) (y)] from_records :: (x,y,))
2832: (cf. to_records)
2833: ]
2834: ] putUsages
2835: /popEnv {
2836: { system_variable pop } map pop
2837: } def
2838:
2839: /pushEnv {
2840: %% opt=[(CurrentRingp) (NN)] ==> [[(CurrentRingp) val] [(NN) val]]
2841: { [ 2 1 roll dup [ 2 1 roll ] system_variable ] } map
2842: } def
2843: [(pushEnv)
2844: [(keylist pushEnv envlist)
2845: (array of string keylist, array of [string object] envlist;)
2846: (Values <<envlist>> of the global system variables specified )
2847: (by the <<keylist>> is push on the stack.)
2848: (keylist is an array of keywords for system_variable.)
2849: (cf. system_variable, popEnv)
2850: (Example: [(CurrentRingp) (KanGBmessage)] pushEnv)
2851: ]
2852: ] putUsages
2853: [(popEnv)
2854: [(envlist popEnv)
2855: (cf. pushEnv)
2856: ]
2857: ] putUsages
2858:
2859: /npower {
2860: /arg2 set
2861: /arg1 set
2862: [/f /k /i /ans] pushVariables
2863: [
2864: /f arg1 def /k arg2 ..int def
2865: f tag PolyP eq {
2866: /ans (1). def
2867: } {
2868: /ans (1).. def
2869: } ifelse
2870: k 0 lt {
2871: 1 1 << 0 k sub >> {
2872: /ans f ans {mul} sendmsg2 def
2873: } for
2874: /ans (1).. ans {div} sendmsg2 def
2875: }
2876: {
2877: 1 1 k {
2878: /ans f ans {mul} sendmsg2 def
2879: } for
2880: } ifelse
2881: /arg1 ans def
2882: ] pop
2883: popVariables
2884: arg1
2885: } def
2886: [(npower)
2887: [(obj1 obj2 npower obj3)
2888: (npower returns obj1^obj2 as obj3)
2889: (The difference between power and npower occurs when we compute f^0)
2890: (where f is a polynomial.)
2891: $power returns number(universalNumber) 1, but npower returns 1$
2892: (in the current ring.)
2893: ]
2894: ] putUsages
2895:
2896: /gensym {
2897: (dollar) dc 2 cat_n
2898: } def
2899: [(gensym)
2900: [(x i gensym xi)
2901: (string x; integer i; string xi)
2902: (It generate a string x indexed with the number i.)
2903: $Example: (Dx) 12 gensym (Dx12)$
2904: ]
2905: ] putUsages
2906:
2907: /cat {
2908: { toString } map aload length cat_n
2909: } def
2910: [(cat)
2911: [(a cat s)
2912: (array a ; string s;)
2913: (cat converts each entry of << a >> to a string and concatenates them.)
2914: (Example: [ (x) 1 2] cat ==> (x12))
2915: ]
2916: ] putUsages
2917:
2918:
2919: %%%%%%%%%%%%%%%%%%% pmat-level
2920: /pmat-level {
2921: /arg2 set
2922: /arg1 set
2923: [/n /i /m /lev /flag] pushVariables
2924: [
2925: /m arg1 def
2926: /lev arg2 def
2927: m isArray {
2928: /n m length def
2929: n 0 eq { /flag 0 def }
2930: { m 0 get isArray { /flag 1 def } { /flag 0 def} ifelse } ifelse
2931: } { /flag 0 def } ifelse
2932:
2933: flag {
2934: 0 1 lev {
2935: pop ( ) messagen
2936: } for
2937: ([ ) message
2938: 0 1 n 1 sub {
2939: /i set
2940: m i get lev 1 add pmat-level
2941: } for
2942: 0 1 lev {
2943: pop ( ) messagen
2944: } for
2945: (]) message
2946: }
2947: {
2948: 0 1 lev {
2949: pop ( ) messagen
2950: } for
2951: ( ) messagen
2952: m message
2953: } ifelse
2954: ] pop
2955: popVariables
2956: } def
2957:
2958: /pmat { 0 pmat-level } def
2959:
2960: [(pmat)
2961: [(f pmat)
2962: (array f;)
2963: (f is pretty printed.)
2964: ]
2965: ] putUsages
2966:
2967:
2968: /adjoint1 {
2969: /arg2 set
2970: /arg1 set
2971: [/in-adjoint1 /f /p /q /xx /dxx /ans /g /one] pushVariables
2972: [
2973: /f arg1 def
2974: /xx arg2 def
2975: f isPolynomial { }
2976: { (adjoint1: the first argument must be a polynomial.) message
2977: pop popVariables
2978: (adjoint1: the first argument must be a polynomial.) error
2979: } ifelse
2980: /ans (0). def
2981: f (0). eq { }
2982: {
2983: /xx xx (string) dc def
2984: /dxx [@@@.Dsymbol xx] cat def
2985: /xx xx f (ring) dc ,, def
2986: /dxx dxx f (ring) dc ,, def
2987: /one (1) f (ring) dc ,, def
2988:
2989: {
2990: /g f init def
2991: /f f g sub def
2992: /p g xx degree def
2993: /q g dxx degree def
2994: g [[xx one] [dxx one]] replace /g set
2995: g
2996: << (0). dxx sub q npower xx p npower mul >>
2997: mul
2998: ans add /ans set
2999: f (0). eq { exit } { } ifelse
3000: } loop
3001: ans dehomogenize /ans set
3002: } ifelse
3003: /arg1 ans def
3004: ] pop
3005: popVariables
3006: arg1
3007: } def
3008:
3009: /adjoint {
3010: /arg2 set
3011: /arg1 set
3012: [/in-adjoint /f /xx /xx0] pushVariables
3013: [
3014: /f arg1 def /xx arg2 def
3015: xx toString /xx set
3016: [xx to_records pop] /xx set
3017: xx { /xx0 set f xx0 adjoint1 /f set } map
3018: /arg1 f def
3019: ]pop
3020: popVariables
3021: arg1
3022: } def
3023:
3024: [(adjoint)
3025: [(f xlist adjoint g)
3026: (poly f; string xlist; poly g;)
3027: (g is the adjoint operator of f.)
3028: (The variables to take adjoint are specified by xlist.)
3029: (Example: [(x,y) ring_of_differential_operators 0] define_ring)
3030: ( (x^2 Dx - y x Dx Dy-2). (x,y) adjoint )
3031: $ ((-Dx) x^2 - (-Dx) (-Dy) x y -2). dehomogenize sub :: ==> 0$
3032: ]] putUsages
3033:
3034: %%%%% diagonal for tensor products
3035: %% 1998, 12/4 (Sat)
3036: %% s_i = x_i, t_i = x_i - y_i, Restrict to t_i = 0.
3037: %% x_i = x_i, y_i = s_i - t_i,
3038: %% Dx_i = Dt_i + Ds_i, Dy_i = -Dt_i.
3039: /diagonalx {
3040: /arg2 set
3041: /arg1 set
3042: [/in-diagonalx /f] pushVariables
3043: [
3044: (Not implemented yet.) message
3045: ] pop
3046: popVariables
3047: arg1
3048: } def
3049:
3050:
3051:
3052: %%%%%%%%%%% distraction2 for b-function
3053: /distraction2 {
3054: /arg4 set
3055: /arg3 set
3056: /arg2 set
3057: /arg1 set
3058: [/f /dx /ss /xx /ans /n /i /rr] pushVariables
3059: [
3060: /f arg1 def /xx arg2 def /dx arg3 def /ss arg4 def
3061: f (0). eq { }
3062: {
3063: /rr f (ring) dc def
3064: xx {toString rr ,, } map /xx set
3065: dx {toString rr ,, } map /dx set
3066: ss {toString rr ,, } map /ss set
3067: /n xx length def
3068: 0 1 n 1 sub {
3069: /i set
3070: /f f xx i get dx i get ss i get destraction2.1 /f set
3071: } for
3072: } ifelse
3073: /arg1 f def
3074: ]pop
3075: popVariables
3076: arg1
3077: } def
3078: [(distraction2)
3079: [(f [ list of x-variables ] [ list of D-variables ] [ list of s-variables ])
3080: ( distraction2 result )
3081: $Example 1: [(x,y) ring_of_differential_operators 0] define_ring $
3082: $ (x^2 Dx Dy + x Dy). [(x). (y).] [(Dx). (Dy).] [(x). (y).] distraction2$
3083: $Example 2: (x^4 Dx^2 + x^2). [(x).] [(Dx). ] [(x).] distraction2$
3084: ]
3085: ] putUsages
3086: /destraction2.1 {
3087: /arg4 set
3088: /arg3 set
3089: /arg2 set
3090: /arg1 set
3091: [/ww /f /dx /ss /xx /coeff0 /expvec
3092: /coeffvec /expvec2 /ans /one /rr /dd] pushVariables
3093: [
3094: /f arg1 def /xx arg2 def /dx arg3 def /ss arg4 def
3095: f (ring) dc /rr set
3096: /one (1) rr ,, def %%
3097: /ww [ xx toString -1 dx toString 1 ] weightv def
3098: f ww init f sub (0). eq { }
3099: { [(destraction2.1 : inhomogeneous with respect to )
3100: xx ( and ) dx nl
3101: (Your weight vector may not be generic.)
3102: ] cat error } ifelse
3103: /dd << f dx degree >> << f xx degree >> sub def
3104: f [[xx one]] replace dx coefficients /coeff0 set
3105: /expvec coeff0 0 get { (integer) dc } map def
3106: /coeffvec coeff0 1 get def
3107: expvec { ss 2 -1 roll factorial } map /expvec2 set
3108: expvec2 coeffvec mul /ans set
3109: %% x^p d^q, (p > q) case. x^2( x^2 Dx^2 + x Dx + 1)
3110: dd 0 lt {
3111: %% (ss+1) (ss+2) ... (ss+d)
3112: one 1 1 0 dd sub { (universalNumber) dc ss add mul} for
3113: ans mul /ans set
3114: }
3115: { } ifelse
3116: /arg1 ans def
3117: ] pop
3118: popVariables
3119: arg1
1.3 takayama 3120: } def
3121:
3122: /distraction2* {
3123: /arg1 set
3124: [/in-distraction2* /aa /f /vlist /xlist /dlist /slist ] pushVariables
3125: [(CurrentRingp)] pushEnv
3126: [
3127: /aa arg1 def
3128: /f aa 0 get def
3129: /vlist aa 1 get def
3130: /xlist aa 2 get def
3131: /dlist aa 3 get def
3132: /slist aa 4 get def
3133: vlist isArray
3134: {
3135: vlist { toString } map /vlist set
3136: }
3137: {
3138: vlist toString to_records /vlist set
3139: } ifelse
3140: xlist isArray
3141: {
3142: xlist { toString } map /xlist set
3143: }
3144: {
3145: xlist toString to_records /xlist set
3146: } ifelse
3147: slist isArray
3148: {
3149: slist { toString } map /slist set
3150: }
3151: {
3152: slist toString to_records /slist set
3153: } ifelse
3154: [vlist from_records ring_of_differential_operators 0] define_ring pop
3155: f toString .
3156: xlist { . } map
3157: dlist { toString . } map
3158: slist { toString . } map
3159: distraction2 /arg1 set
3160: ] pop
3161: popEnv
3162: popVariables
3163: arg1
1.1 maekawa 3164: } def
3165:
3166: /message-quiet {
3167: @@@.quiet { pop } { message } ifelse
3168: } def
3169: [(message-quiet)
3170: [(s message-quiet )
3171: (string s;)
3172: (It outputs the message s when @@@.quiet is not equal to 1.)
3173: (@@@.quiet is set to 1 when you start sm1 with the option -q.)
3174: ]] putUsages
3175: /messagen-quiet {
3176: @@@.quiet { pop } { messagen } ifelse
3177: } def
3178: [(messagen-quiet)
3179: [(s messagen-quiet )
3180: (string s;)
3181: (It outputs the message s without the newline when @@@.quiet is not equal to 1.)
3182: (@@@.quiet is set to 1 when you start sm1 with the option -q.)
3183: ]] putUsages
3184:
3185: /getvNames0 {
3186: /arg1 set
3187: [/in-getvNames0 /nlist /nn /i] pushVariables
3188: [
3189: /nlist arg1 def
3190: [(N)] system_variable /nn set
3191: nlist { /i set
3192: i nn lt {
3193: [(x) (var) i] system_variable
3194: } {
3195: [(D) (var) i nn sub] system_variable
3196: } ifelse
3197: } map
3198: /arg1 set
3199: ] pop
3200: popVariables
3201: arg1
3202: } def
3203:
3204: /getvNames {
3205: [/in-getvNames /nn] pushVariables
3206: [
3207: [(N)] system_variable /nn set
3208: [0 1 nn 2 mul 1 sub { } for] getvNames0 /arg1 set
3209: ] pop
3210: popVariables
3211: arg1
3212: } def
3213: [(getvNames)
3214: [(getvNames vlist)
3215: (list vlist)
3216: (It returns of the list of the variables in the order x0, x1, ..., D0, ...)
3217: (Use with [(variableNames) vlist] system_variable.)
3218: (cf. nlist getvNames0 vlist is used internally. cf. getvNamesC)
3219: ]] putUsages
3220:
3221: /getvNamesC {
3222: [/in-getvNamesC /nn /i] pushVariables
3223: [
3224: [(N)] system_variable /nn set
3225: [nn 1 sub -1 0 { } for nn 2 mul 1 sub -1 nn { } for ] getvNames0 /arg1 set
3226: ] pop
3227: popVariables
3228: arg1
3229: } def
3230: [(getvNamesC)
3231: [(getvNamesC vlist)
3232: (list vlist)
3233: $It returns of the list of the variables in the order 0, 1, 2, ... $
3234: $(cmo-order and output_order).$
3235: (cf. getvNames)
3236: ]] putUsages
3237:
3238: /getvNamesCR {
3239: /arg1 set
3240: [/in-getvNamesCR /rrr] pushVariables
3241: [(CurrentRingp)] pushEnv
3242: [
3243: /rrr arg1 def
3244: rrr isPolynomial {
3245: rrr (0). eq { (No name field for 0 polynomial.) error }
3246: { rrr (ring) dc /rrr set } ifelse
3247: } { } ifelse
3248: [(CurrentRingp) rrr] system_variable
3249: getvNamesC /arg1 set
3250: ] pop
3251: popEnv
3252: popVariables
3253: arg1
3254: } def
3255: [(getvNamesCR)
3256: [(obj getvNamesCR vlist)
3257: (obj ring | poly ; list vlist)
3258: $It returns of the list of the variables in the order 0, 1, 2, ... (cmo-order)$
3259: (for <<obj>>.)
3260: (Example: ( (x-2)^3 ). /ff set )
3261: ( [(x) ring_of_differential_operators 0] define_ring ff getvNamesCR ::)
3262: ]] putUsages
3263:
3264:
3265: /reduction-noH {
3266: /arg2 set
3267: /arg1 set
3268: [/in-reduction-noH /ff /gg] pushVariables
3269: [(Homogenize)] pushEnv
3270: [
3271: /ff arg1 def
3272: /gg arg2 def
3273: [(Homogenize) 0] system_variable
3274: ff gg reduction /arg1 set
3275: ] pop
3276: popEnv
3277: popVariables
3278: arg1
3279: } def
3280: [(reduction-noH)
3281: [(f g reduction-noH r)
3282: (poly f; array g; array r;)
3283: (Apply the normal form algorithm for f with the set g. All computations are)
3284: (done with the rule Dx x = x Dx +1, i.e., no homogenization, but other)
3285: (specifications are the same with reduction. cf. reduction)
3286: (g should be dehomogenized.)
3287: ]] putUsages
3288:
3289: /-intInfinity -999999999 def
3290: /intInfinity 999999999 def
3291: [(intInfinity)
3292: [(intInfinity = 999999999)]
3293: ] putUsages
3294: [(-intInfinity)
3295: [(-intInfinity = -999999999)]
3296: ] putUsages
3297:
3298:
3299: /maxInArray {
3300: /arg1 set
3301: [/in-maxInArray /v /ans /i /n] pushVariables
3302: [
3303: /v arg1 def
3304: /n v length def
3305: /maxInArray.pos 0 def
3306: n 0 eq {
3307: /ans null def
3308: } {
3309: /ans v 0 get def
3310: 1 1 n 1 sub {
3311: /i set
3312: v i get ans gt {
3313: /ans v i get def
3314: /maxInArray.pos i def
3315: } { } ifelse
3316: } for
3317: } ifelse
3318: /arg1 ans def
3319: ] pop
3320: popVariables
3321: arg1
3322: } def
3323: [(maxInArray)
3324: [( [v1 v2 ....] maxInArray m )
3325: (m is the maximum in [v1 v2 ...].)
3326: (The position of m is stored in the global variable maxInArray.pos.)
3327: ]] putUsages
3328:
3329: /cancelCoeff {
1.18 takayama 3330: /arg1 set
3331: [(reduceContent) arg1] gbext 0 get
3332: } def
3333: /cancelCoeff_org {
1.1 maekawa 3334: /arg1 set
3335: [/in-cancelCoeff /ff /gg /dd /dd2] pushVariables
3336: [ /ff arg1 def
3337: ff (0). eq {
3338: /label.cancelCoeff2 goto
3339: } { } ifelse
3340: /gg ff def
3341: /dd [(lcoeff) ff init ] gbext (universalNumber) dc def
3342: {
3343: gg (0). eq { exit} { } ifelse
3344: [(lcoeff) gg init] gbext (universalNumber) dc /dd2 set
3345: [(gcd) dd dd2] mpzext /dd set
3346: dd (1).. eq {
3347: /label.cancelCoeff goto
3348: } { } ifelse
3349: /gg gg gg init sub def
3350: } loop
3351: [(divByN) ff dd] gbext 0 get /ff set
3352: /label.cancelCoeff
3353: [(lcoeff) ff init] gbext (universalNumber) dc (0).. lt
3354: { ff (-1).. mul /ff set } { } ifelse
3355: /label.cancelCoeff2
3356: /arg1 ff def
3357: ] pop
3358: popVariables
3359: arg1
3360: } def
3361: [(cancelCoeff)
3362: [(f cancelcoeff g)
3363: (poly f,g;)
3364: (Factor out the gcd of the coefficients.)
3365: (Example: (6 x^2 - 10 x). cancelCoeff)
3366: (See also gbext.)
3367: ]] putUsages
3368:
3369:
3370: /flatten {
3371: /arg1 set
3372: [/in-flatten /mylist] pushVariables
3373: [
3374: /mylist arg1 def
3375: mylist isArray {
3376: mylist { dup isArray { aload pop } { } ifelse } map /mylist set
3377: }{ } ifelse
3378: /arg1 mylist def
3379: ] pop
3380: popVariables
3381: arg1
3382: } def
3383: [(flatten)
3384: [(list flatten list2)
3385: (Flatten the list.)
3386: (Example 1: [ [1 2 3] 4 [2]] flatten ===> [1 2 3 4 2])
3387: ]] putUsages
3388:
3389: %% Take first N elements.
3390: /carN {
3391: /arg2 set
3392: /arg1 set
3393: [/in-res-getN /pp /nn /ans] pushVariables
3394: [
3395: /nn arg2 def
3396: /pp arg1 def
3397: pp isArray {
3398: pp length nn lt {
3399: /ans pp def
3400: } {
3401: [pp aload length nn sub /nn set 1 1 nn { pop pop } for ] /ans set
3402: } ifelse
3403: } {
3404: /ans pp def
3405: } ifelse
3406: /arg1 ans def
3407: ] pop
3408: popVariables
3409: arg1
3410: } def
3411: [(carN)
3412: [([f1 ... fm] n carN [f1 ... fn])
3413: (carN extracts the first n elements from the list.)
3414: ]] putUsages
3415:
3416: /getRing {
3417: /arg1 set
3418: [/in-getRing /aa /n /i /ans] pushVariables
3419: [
3420: /aa arg1 def
3421: /ans null def
3422: aa isPolynomial {
3423: aa (0). eq {
3424: } {
3425: /ans aa (ring) dc def
3426: } ifelse
3427: } {
3428: aa isArray {
3429: /n aa length 1 sub def
3430: 0 1 n { /i set aa i get getRing /ans set
3431: ans tag 0 eq { } { /getRing.LLL goto } ifelse
3432: } for
3433: }{ } ifelse
3434: } ifelse
3435: /getRing.LLL
3436: /arg1 ans def
3437: ] pop
3438: popVariables
3439: arg1
3440: } def
3441: [(getRing)
3442: [(obj getRing rr)
3443: (ring rr;)
3444: (getRing obtains the ring structure from obj.)
3445: (If obj is a polynomial, it returns the ring structure associated to)
3446: (the polynomial.)
3447: (If obj is an array, it recursively looks for the ring structure.)
3448: ]] putUsages
3449: /toVectors {
3450: /arg1 set
3451: [/in-toVectors /gg /n /ans] pushVariables
3452: [
3453: /gg arg1 def
3454: gg isArray {
3455: gg length 0 eq {
3456: /ans [ ] def
3457: /toVectors.LLL goto
3458: } {
3459: gg 0 get isInteger {
3460: gg @@@.toVectors2 /ans set
3461: } {
3462: gg @@@.toVectors /ans set
3463: } ifelse
3464: /toVectors.LLL goto
3465: } ifelse
3466: } {
3467: %% It is not array.
3468: gg (array) dc /ans set
3469: } ifelse
3470: /toVectors.LLL
3471: /arg1 ans def
3472: ] pop
3473: popVariables
3474: arg1
3475: } def
3476: /@@@.toVectors2 {
3477: /arg1 set
3478: [/in-@@@.toVectors2 /gg /ans /n /tmp /notarray] pushVariables
3479: [
3480: /gg arg1 def
3481: /ans gg 1 get @@@.toVectors def
3482: /n gg 0 get def
3483: gg 1 get isArray not {
3484: /ans [ans] def
3485: /notarray 1 def
3486: }{ /notarray 0 def} ifelse
3487: ans {
3488: /tmp set
3489: tmp length n lt {
3490: tmp
3491: [1 1 n tmp length sub { pop (0). } for ]
3492: join /tmp set
3493: } { } ifelse
3494: tmp
3495: } map
3496: /ans set
3497: notarray { ans 0 get /ans set } { } ifelse
3498: /arg1 ans def
3499: ] pop
3500: popVariables
3501: arg1
3502: } def
3503:
3504: /@@@.toVectors {
3505: /arg1 set
3506: [/in-@@@.toVectors /gg ] pushVariables
3507: [
3508: /gg arg1 def
3509: gg isArray {
3510: gg { $array$ data_conversion } map
3511: } {
3512: gg (array) data_conversion
3513: }ifelse
3514: /arg1 set
3515: ] pop
3516: popVariables
3517: arg1
3518: } def
3519:
3520: /toVectors2 { toVectors } def
3521:
3522: /fromVectors { { fromVectors.aux } map } def
3523: /fromVectors.aux {
3524: /arg1 set
3525: [/in-fromVector.aux /vv /mm /ans /i /ee] pushVariables
3526: [(CurrentRingp)] pushEnv
3527: [
3528: /vv arg1 def
3529: /mm vv length def
3530: /ans (0). def
3531: /ee (0). def
3532: 0 1 mm 1 sub {
3533: /i set
3534: vv i get (0). eq {
3535: } {
3536: [(CurrentRingp) vv i get (ring) dc] system_variable
3537: [(x) (var) [(N)] system_variable 1 sub] system_variable . /ee set
3538: /fromVector.LLL goto
3539: } ifelse
3540: } for
3541: /fromVector.LLL
3542: %% vv message
3543: 0 1 mm 1 sub {
3544: /i set
3545: vv i get (0). eq {
3546: } {
3547: /ans ans
3548: << vv i get >> << ee i npower >> mul
3549: add def
3550: } ifelse
3551: %% [i ans] message
3552: } for
3553: /arg1 ans def
3554: ] pop
3555: popEnv
3556: popVariables
3557: arg1
3558: } def
3559: [(fromVectors)
3560: [
3561: ([v1 v2 ...] fromVectors [s1 s2 ...])
3562: (array of poly : v1, v2, ... ; poly : s1, s2 ....)
3563: (cf. toVectors. <<e_>> varaible is assumed to be the last )
3564: ( variable in x. @@@.esymbol)
3565: $Example: [(x,y) ring_of_differential_operators 0] define_ring$
3566: $ [(x). (y).] /ff set $
3567: $ [ff ff] fromVectors :: $
3568: ]] putUsages
3569:
3570: /getOrderMatrix {
3571: /arg1 set
3572: [/in-getOrderMatrix /obj /rr /ans /ans2 /i] pushVariables
3573: [(CurrentRingp)] pushEnv
3574: [
3575: /obj arg1 def
3576: obj isArray {
3577: obj { getOrderMatrix } map /ans set
3578: ans length 0 {
3579: /ans null def
3580: } {
3581: /ans2 null def
3582: 0 1 ans length 1 sub {
3583: /i set
3584: ans i get tag 0 eq
3585: { }
3586: { /ans2 ans i get def } ifelse
3587: } for
3588: /ans ans2 def
3589: } ifelse
3590: /getOrderMatrix.LLL goto
3591: } { } ifelse
3592: obj tag 14 eq {
3593: [(CurrentRingp) obj] system_variable
3594: [(orderMatrix)] system_variable /ans set
3595: /getOrderMatrix.LLL goto
3596: } { } ifelse
3597: obj isPolynomial {
3598: obj (0). eq
3599: { /ans null def
3600: } { obj getRing /rr set
3601: [(CurrentRingp) rr] system_variable
3602: [(orderMatrix)] system_variable /ans set
3603: } ifelse
3604: /getOrderMatrix.LLL goto
3605: } { (getOrderMatrix: wrong argument.) error } ifelse
3606: /getOrderMatrix.LLL
3607: /arg1 ans def
3608: ] pop
3609: popEnv
3610: popVariables
3611: arg1
3612: } def
3613:
3614:
3615: [(getOrderMatrix)
3616: [(obj getOrderMatrix m)
3617: (array m)
3618: (getOrderMatrix obtains the order matrix from obj.)
3619: (If obj is a polynomial, it returns the order matrix associated to)
3620: (the polynomial.)
3621: (If obj is an array, it returns an order matrix of an element.)
3622: ]] putUsages
3623:
3624: /nl {
3625: 10 $string$ data_conversion
3626: } def
3627: [(nl)
3628: [(nl is the newline character.)
3629: $Example: [(You can break line) nl (here.)] cat message$
1.4 takayama 3630: ]] putUsages
3631:
3632: /to_int {
3633: /arg1 set
3634: [/to-int /ob /ans] pushVariables
3635: [
3636: /ob arg1 def
3637: /ans ob def
3638: ob isArray {
3639: ob {to_int} map /ans set
3640: /LLL.to_int goto
3641: } { } ifelse
3642: ob isInteger {
3643: ob (universalNumber) dc /ans set
3644: /LLL.to_int goto
3645: } { } ifelse
3646: /LLL.to_int
3647: /arg1 ans def
3648: ] pop
3649: popVariables
3650: arg1
3651: } def
3652: [(to_int)
3653: [(obj to_int obj2)
3654: (All integers in obj are changed to universalNumber.)
3655: (Example: /ff [1 2 [(hello) (0).]] def ff { tag } map ::)
3656: ( ff to_int { tag } map :: )
1.5 takayama 3657: ]] putUsages
3658:
3659: /define_ring_variables {
1.6 takayama 3660: [/in-define_ring_variables /drv._v /drv._p /drv._v0] pushVariables
3661: %% You cannot use these names for names for polynomials.
1.5 takayama 3662: [
1.6 takayama 3663: /drv._v getVariableNames def
3664: /drv._v0 drv._v def
3665: drv._v { dup /drv._p set (/) 2 1 roll ( $) drv._p ($. def ) } map cat
3666: /drv._v set
3667: % drv._v message
3668: [(parse) drv._v] extension
1.5 takayama 3669: ] pop
3670: popVariables
3671: } def
3672: [(define_ring_variables)
3673: [(It binds a variable <<a>> in the current ring to the sm1 variable <<a>>.)
3674: (For example, if x is a variable in the current ring, it defines the sm1)
3675: (variable x by /x (x) def)
3676: ]] putUsages
3677:
3678: /boundp {
3679: /arg1 set
3680: [/a /ans] pushVariables
3681: [
3682: /a arg1 def
3683: [(parse) [(/) a ( load tag 0 eq { /ans 0 def } )
3684: ( { /ans 1 def } ifelse )] cat ] extension
3685: /arg1 ans def
3686: ] pop
3687: popVariables
3688: arg1
3689: } def
3690: [(boundp)
3691: [( a boundp b)
3692: (string a, b is 0 or 1.)
3693: (If the variable named << a >> is bounded to a value,)
3694: (it returns 1 else it returns 0.)
3695: $Example: (hoge) boundp ::$
1.1 maekawa 3696: ]] putUsages
1.10 takayama 3697: [(isSubstr)
3698: [
3699: (s1 s2 isSubstr pos)
3700: (If s1 is a substring of s2, isSubstr returns the position in s2 from which)
3701: (s1 is contained in s2.)
3702: (If s1 is not a substring of s2, then isSubstr returns -1.)
3703: ]
3704: ] putUsages
3705: /isSubstr {
3706: /arg2 set /arg1 set
3707: [/in-isSubstr /s1 /s2 /i1 /i2 /n1 /n2
3708: /ans /flg
3709: ] pushVariables
3710: [
3711: /s1 arg1 def
3712: /s2 arg2 def
3713: s1 (array) dc /s1 set
3714: s2 (array) dc /s2 set
3715: /n1 s1 length def
3716: /n2 s2 length def
3717: /ans -1 def
3718: 0 1 n2 n1 sub {
3719: /i2 set
3720: /flg 1 def
3721: 0 1 n1 1 sub {
3722: /i1 set
3723: s1 i1 get s2 i2 i1 add get eq {
3724: } {
3725: /flg 0 def exit
3726: } ifelse
3727: } for
3728: flg {
3729: /ans i2 def
3730: /isSubstr.L2 goto
3731: } { /ans -1 def } ifelse
3732: } for
3733: /isSubstr.L2
3734: /arg1 ans def
3735: ] pop
3736: popVariables
3737: arg1
1.14 takayama 3738: } def
3739:
3740: [(execve)
3741: [
3742: (command execve)
3743: ([arg0 arg1 arg2 ...] execve )
3744: (It executes the command by the system call execve.)
3745: (cf. system, forkExec)
3746: ]
3747: ] putUsages
3748:
3749: /execve {
3750: /execve.arg set
3751: [(forkExec) execve.arg [ ] 1] extension
1.15 takayama 3752: } def
3753:
3754: [(beginEcart)
3755: [
3756: (beginEcart)
3757: (Set the environments for the ecart division algorithm.)
3758: ]
3759: ] putUsages
3760:
1.23 takayama 3761: /ecart.debug_reduction1 0 def
1.15 takayama 3762: /beginEcart {
3763: (red@) (ecart) switch_function
3764: [(Ecart) 1] system_variable
1.16 takayama 3765: [(CheckHomogenization) 0] system_variable
3766: [(ReduceLowerTerms) 0] system_variable
3767: [(AutoReduce) 0] system_variable
1.17 takayama 3768: [(EcartAutomaticHomogenization) 0] system_variable
1.23 takayama 3769: ecart.debug_reduction1 {
3770: (red@) (debug) switch_function
3771: } { } ifelse
1.15 takayama 3772: } def
3773:
3774: [(endEcart)
3775: [
3776: (endEcart)
3777: (End of using the ecart division algorithm.)
3778: ]
3779: ] putUsages
3780:
3781: /endEcart {
3782: (red@) (standard) switch_function
3783: [(Ecart) 0] system_variable
1.21 takayama 3784: [(degreeShift) (reset)] homogenize pop
1.10 takayama 3785: } def
1.19 takayama 3786:
3787: /ord_ws_all {
3788: /arg2 set /arg1 set
3789: [(ord_ws_all) arg1 arg2] gbext
3790: } def
3791: [(ord_ws_all)
3792: [
3793: (fv wv ord_ws_all degree)
3794: ( ord_ws_all returns the ord with respect to the weight vector wv.)
3795: $Example: [(x,y) ring_of_differential_operators 0] define_ring $
3796: $ (Dx^2+x*Dx*Dy+2). [(Dx) 1 (Dy) 1] weightv ord_ws_all :: $
3797: ( )
3798: (fv [wv shiftv] ord_ws_all degree)
3799: ( ord_ws_all returns the ord with respect to the weight vector wv and)
3800: ( the shift vector shiftv.)
3801: $Example: [(x,y) ring_of_differential_operators 0] define_ring $
3802: $ [(Dx^2+x*Dx*Dy+2). (Dx).] [[(Dx) 1 (Dy) 1] weightv [0 2]] ord_ws_all ::$
3803: ( )
3804: (cf: init, gbext. Obsolete: ord_w, ord_w_all)
3805: ]
3806: ] putUsages
1.22 takayama 3807:
3808: [(newVector)
3809: [( n newVector vec)
3810: ]] putUsages
3811: /newVector {
3812: /arg1 set
3813: [/in-newVector /n] pushVariables
3814: [
3815: /n arg1 def
3816: [(newVector) n] extension /arg1 set
3817: ] pop
3818: popVariables
3819: arg1
3820: } def
3821:
3822: [(newMatrix)
3823: [( [m n] newMatrix mat)
3824: ]] putUsages
3825: /newMatrix {
3826: /arg1 set
3827: [/in-newMatrix /n] pushVariables
3828: [
3829: /n arg1 def
3830: [(newMatrix) n 0 get n 1 get] extension /arg1 set
3831: ] pop
3832: popVariables
3833: arg1
1.25 takayama 3834: } def
3835:
3836: /addStdoutStderr {
3837: [(>) (stringOut://@@@stdout) (2>) (stringOut://@@@stderr)] join
1.27 ! takayama 3838: } def
! 3839:
! 3840: [(,,,)
! 3841: [(reparse a polynomial or polynomials)]
! 3842: ] putUsages
! 3843: /,,, {
! 3844: /arg1 set
! 3845: [/in-reparse /ff] pushVariables
! 3846: [
! 3847: /ff arg1 def
! 3848: ff tag 6 eq {
! 3849: ff { ,,, } map /arg1 set
! 3850: } {
! 3851: ff toString . /arg1 set
! 3852: } ifelse
! 3853: ] pop
! 3854: popVariables
! 3855: arg1
1.22 takayama 3856: } def
3857:
1.24 takayama 3858: /usages {
3859: /arg1 set
3860: [/name /flag /n /k /slist /m /i /sss] pushVariables
3861: [
3862: /name arg1 def
3863: /flag true def
3864:
3865: %BUG: should use regular expression in a future.
3866: name tag 1 eq {
3867: @.usages { 0 get } map shell { (, ) nl } map /sss set
3868: } {
3869:
3870: /sss [ ] def
3871: @.usages length /n set
3872: 0 1 << n 1 sub >>
3873: {
3874: /k set
3875: name << @.usages k get 0 get >> eq
3876: {
3877: /slist @.usages k get 1 get def
3878: /m slist length def
3879: 0 1 << m 1 sub >> {
3880: /i set
3881: sss slist i get append nl append /sss set
3882: } for
3883: /flag false def
3884: }
3885: { }
3886: ifelse
3887: } for
3888:
3889: %BUG: cannot get usages of primitives.
3890: flag
3891: {name Usage /sss [(Usage of ) name ( could not obtained.) nl ] def}
3892: { }
3893: ifelse
3894: } ifelse
3895: /arg1 sss cat def
3896: ] pop
3897: popVariables
3898: arg1
3899: } def
3900: [(usages)
3901: [(key usages usages-as-a-string)
3902: (num usages list-of-key-words)
3903: ]] putUsages
1.1 maekawa 3904:
3905: ;
3906:
3907:
3908:
3909:
3910:
3911:
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>