Annotation of OpenXM/src/kan96xx/Doc/oxasir.sm1, Revision 1.1.1.1
1.1 maekawa 1: %% kxx/oxasir.sm1 1998, 2/12 (this version is at Old/oxasir.sm1.19980212
2: %% 3/1, 1995, 11/5, 11/21
3: %% This file is error clean.
4: %%%%%%% How to install.
5: %%% Set ASIR_LIBDIR if necessary. Ex. /u/nobuki/lib/asir
6: %%% write ~/.asirrc : load("gr")$ load("primdec")$ end$
7: %%% oxasir.asir must be in
8: %%% LOAD_SM1_PATH or oxasirpath.asirlib
9: %%% Edit below
10: %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
11: %%% /usr/local/lib/sm1, SM1_LOAD_PATH, /usr/local/lib/asir, ASIR_LOAD_PATH
12: /oxasirpath.oxasir (ox_asir) def %% loadmethod is 1
13: /oxasirpath.asirlib (oxasir.asir) def
14:
15: /ox_asirConnectMethod { asirconnectr /oxasir.ccc set } def
16: %/ox_asirConnectMethod { asirconnect2 } def
17:
18: %% Old path
19: %/oxasirpath.oxasir (/home/nobuki/kxx/ox_asir) def %% loadmethod is 1
20: %/oxasirpath.asirlib (/home/nobuki/kxx/oxasir.asir) def
21: %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
22: /oxasir.loadmethod 1 def %% "..." oxsendcmo (load) ox...
23: %/oxasir.loadmethod 0 def %% load("..."); %% at MSRI
24: %%%%%%%%%%%%%%%% end of configuration.
25: /initializePathNamesForOxAsir {
26: [oxasirpath.oxasir] getPathNameAsir /oxasirpath.oxasir set
27: [oxasirpath.asirlib] getPathNameSm1 /oxasirpath.asirlib set
28: } def
29:
30:
31: /oxasir.verbose 0 def
32: /oxasir.version (2.981105) def
33: oxasir.version [(Version)] system_variable gt
34: { [(This package requires the latest version of kan/sm1) nl
35: (Please get it from http://www.math.kobe-u.ac.jp/KAN) ] cat
36: error
37: } { } ifelse
38: (oxasir.sm1, --- open asir protocol module 3/1 1998, 6/5 1999) message-quiet
39: ( asirconnect, asir, fctr, primadec, (C) M.Noro, N.Takayama ) message-quiet
40:
41: /oxasir.ccc load isArray
42: { }
43: { /oxasir.ccc [ ] def } ifelse
44:
45: [(parse) (ox.sm1) pushfile] extension pop
46: oxasir.verbose {
47: (type in asirconnect to connect, asir is used to execute asir command. )
48: message
49: (type in asirconnect2 to open a new window for ox_asir, connect, asir is used to execute asir command [you need to edit asirconnect2 to tell the path to load ox_asir] )
50: message
51: } { } ifelse
52:
53: /loadAsirFile {
54: /arg1 set
55: [/in-loadAsirFile /peer /fname] pushVariables
56: [
57: /peer arg1 0 get def
58: /fname arg1 1 get def
59: oxasir.loadmethod {
60: peer fname oxsendcmo peer 1 oxsendcmo
61: peer (load) oxexec
62: }{
63: peer [$load("$ fname $");$] cat oxsubmit
64: }ifelse
65: ] pop
66: popVariables
67: } def
68: [(loadAsirFile)
69: [$[client fname] loadAsirFile (ox_asir function)$
70: $Load a file into the client$
71: ]] putUsages
72:
73: /asirinit {
74: %% gr and primdec are loaded by .asirrc
75: /asirinit.peer set
76: [asirinit.peer oxasirpath.asirlib] loadAsirFile
77: } def
78: /asirconnect {
79: [(localhost) 1300 1200] oxconnect /oxasir.ccc set
80: /ccc oxasir.ccc def %% for compatibility.
81: oxasir.ccc asirinit
82: } def
83: /asirconnect2 {
84: [oxpath.oxlog.xterm oxpath.ox ( -ox ) oxasirpath.oxasir
85: oxpath.null
86: ( & )] cat system
87: % (xterm -e /home/nobuki/kxx/ox -ox /home/nobuki/kxx/ox_asir &) system
88: % (kterm -iconic -e /home/nobuki/kxx/ox -ox /home/nobuki/kxx/ox_asir &) system
89: % For MSRI
90: % Eterm is also nice (including kanji). rxvt is also nice.
91: %(xterm -icon -e /u/nobuki/tmp/kxx/ox -ox /u/nobuki/tmp/Ox/ox_asir2 &) system
92: %(kterm2 -e /u/nobuki/tmp/kxx/ox -ox /u/nobuki/tmp/Ox/ox_asir2 &) system
93: % (If you start the server automatically, you may have a trouble to) message
94: % (oxreset. In order to avoid this trouble, start the server by hand.) message
95: (sleep 5) system
96: [(localhost) 1300 1200] oxconnect /oxasir.ccc set
97: /ccc oxasir.ccc def %% for compatibility.
98: oxasir.ccc asirinit
99: } def
100:
101: [(asirconnect2)
102: [(asirconnect2 starts ox_asir server. (ox_asir function))
103: (Open xxx protocol is used for the communication between sm1 and ox_asir.)
104: (cf. oxhelp, asir.)
105: (You need to install ox_asir server to use this function. cf. oxasir)
106: ]] putUsages
107:
108: /asirconnect3 {
109: [oxpath.oxlog.xterm oxpath.ox ( -ox ) oxasirpath.oxasir
110: ( -data 2300 -control 2200) oxpath.null
111: ( & )] cat system
112: % (If you start the server automatically, you may have a trouble to) message
113: % (oxreset. In order to avoid this trouble, start the server by hand.) message
114: (sleep 5) system
115: [(localhost) 2300 2200] oxconnect /oxasir.ccc2 set
116: /ccc2 oxasir.ccc2 def %% for compatibility.
117: oxasir.ccc2 asirinit
118: (The client is stored in oxasir.ccc2.) message
119: } def
120:
121: [(asir)
122: [(pid [asir-command, asir-arg1, asir-arg2, ...] asir result (ox_asir function))
123: (Call open asir server. You need to install ox_asir on your system)
124: (to use this function. cf. primadec, fctr, asirconnect2, asirconnectr.)
125: (If you interrupted the computation by typing ctrl-C, type in )
126: ( oxasir.ccc oxreset ; )
127: (to interrupt the ox_asir server.)
128: (Example: oxasir.ccc [(fctr) (x^10-1).] asir )
129: ( )
130: (This function requires plugins cmo, socket and ox_asir server. cf. oxasir)
131: (See, ftp://endeavor.fujitsu.co.jp/pub/isis/asir on asir)
132: ]
133: ] putUsages
134:
135: /asir {
136: /arg2 set
137: /arg1 set
138: [/pid /asir-comm /comm /n /i /rr] pushVariables
139: [(CurrentRingp)] pushEnv
140: [
141: /pid arg1 def
142: /asir-comm arg2 def
143: pid tag 6 eq { } { (Invalid pid. See asir.) error } ifelse
144: pid 0 get (client) eq { } { (Invalid pid. See asir.) error } ifelse
145: asir-comm tag 6 eq { } { (Invalid argument asir-comm. See asir) error } ifelse
146:
147: [ %% Change the current ring if necessary to send a correct OxVlist.
148: asir-comm oxasir.changeRing
149: ] pop
150: %%% Setting OxVlist to tell asir a way to change dist-poly <==> poly.
151: (OxVlist=) getVlist2 toString (;) 3 cat_n /comm set
152: %% comm message
153: pid comm oxsubmit
154: pid (print(OxVlist);) oxsubmit
155:
156:
157: /n asir-comm length def
158: n 1 sub -1 1 {
159: /i set
160: pid asir-comm i get oxsendcmo
161: pid 1 oxsendcmo pid (ox_dtop) oxexec
162: } for
163: pid n 1 sub oxsendcmo
164: pid asir-comm 0 get oxexec
165:
166: pid 1 oxsendcmo pid (ox_ptod) oxexec
167: pid oxpopcmo /arg1 set
168:
169:
170: ] pop
171: popEnv
172: popVariables
173: arg1
174: } def
175:
176: /oxasir.changeRing {
177: /arg1 set
178: [/in-oxasir.changeRing /f /rr] pushVariables
179: [
180: /f arg1 def
181: f isArray {
182: f {oxasir.changeRing} map
183: }{
184: f isPolynomial {
185: f (0). eq { }
186: { f (ring) dc /rr set [(CurrentRingp) rr] system_variable } ifelse
187: } { } ifelse
188: } ifelse
189: ] pop
190: popVariables
191: } def
192:
193: /fctr {
194: /arg1 set
195: [/f /comm /vv] pushVariables
196: [(CurrentRingp)] pushEnv
197: [
198: /f arg1 def
199: oxasir.ccc [ ] eq {
200: (Starting ox_asir server.) message
201: ox_asirConnectMethod
202: } { } ifelse
203:
204: f isPolynomial not {
205: /vv f 1 get def
206: vv isArray { /vv vv from_records def } { } ifelse
207: /f f 0 get def
208: [vv ring_of_polynomials 0] define_ring
209: f . /f set
210: }{ } ifelse
211: oxasir.ccc [(fctr) f] asir /arg1 set
212: ] pop
213: popEnv
214: popVariables
215: arg1
216: } def
217:
218: [(fctr)
219: [(You need to install ox_asir server to use this function. (ox_asir function))
220: (f fctr g)
221: (poly f; array g;)
222: ([f v] fctr g ; string f, string or array of string v)
223: (This function factors the polynomial f over Q.)
224: ( )
225: (Example 1: [(x^10-y^10) (x,y)] fctr ::)
226: (Example 2: (x^10-1). fctr ::)
227: ( )
228: (If you interrupted the computation by typing ctrl-C, type in )
229: ( oxasir.ccc oxreset ; )
230: (to interrupt the ox_asir server.)
231: ( )
232: (This function requires plugins cmo, socket and ox_asir server. cf.oxasir)
233: ]] putUsages
234:
235:
236: [(primadec)
237: [(You need to install ox_asir server to use this function. (ox_asir function))
238: ([ ii ] primadec [[q1 p1] [q2 p2] ... ] )
239: ( array of poly ii; array of poly q1, p1, q2, p2 ...;)
240: ( q1, q2, ... are primary components of the primary ideal decomposition)
241: ( of the ideal generated by << ii >>.)
242: ( )
243: ([ ii v ] primadec [[q1 p1] [q2 p2] ... ] )
244: ( array of poly or string ii; array of string v; array of poly q1, p1, q2, p2 ...;)
245: (<< v >> is an array of independent variables.)
246: ( )
247: ([ ii v ] primadec [[q1 p1] [q2 p2] ... ] )
248: ( array of poly or string ii; array of string v; array of poly q1, p1, q2, p2 ...;)
249: ( v is a string of variables separated by , )
250: ( )
251: (Example: [(x,y) ring_of_polynomials 0] define_ring)
252: ( [ [(x^2-1). (x y).] ] primadec pmat ;)
253: ( )
254: (Example: [ [(x^2-1) (x y)] [(x) (y)]] primadec pmat ;)
255: ( )
256: (If you interrupted the computation by typing ctrl-C, type in )
257: ( oxasir.ccc oxreset ; )
258: (to interrupt the ox_asir server.)
259: ( )
260: (This function requires plugins cmo, socket and ox_asir server. cf.oxasir)
261: ]] putUsages
262:
263: /primadec {
264: /arg1 set
265: [/in-primadec /aa /f /comm /vvv /r /setarg] pushVariables
266: [(CurrentRingp)] pushEnv
267: [
268: /aa arg1 def
269: aa isArray { } { (<<array>> primadec) error } ifelse
270: /setarg 0 def
271: oxasir.ccc [ ] eq {
272: (Starting ox_asir server.) message
273: ox_asirConnectMethod
274: } { } ifelse
275: aa { tag } map /typev set
276: typev [ ArrayP ] eq
277: { /f aa 0 get def
278: f 0 get (ring) dc /r set
279: [(CurrentRingp) r] system_variable
280: /vvv getVariableNames def
281: /setarg 1 def
282: } { } ifelse
283: typev [ArrayP StringP] eq
284: { /f aa 0 get def
285: /vvv [ aa 1 get to_records pop ] def
286: /setarg 1 def
287: } { } ifelse
288: typev [ArrayP ArrayP] eq
289: { /f aa 0 get def
290: /vvv aa 1 get {toString} map def
291: /setarg 1 def
292: } { } ifelse
293: setarg { } { (primadec : Argument mismatch) error } ifelse
294:
295: f 0 get isPolynomial {
296: /r f 0 get (ring) dc def
297: /vvv vvv { r ,, } map def
298: }
299: {
300: [vvv from_records ring_of_polynomials 0] define_ring
301: f { toString . } map /f set
302: vvv { . } map /vvv set
303: } ifelse
304: oxasir.ccc [(primadec) f vvv] asir /arg1 set
305: ] pop
306: popEnv
307: popVariables
308: arg1
309: } def
310:
311:
312: /getVlist2 {
313: [/n /i ] pushVariables
314: [
315: /n [(N)] system_variable def
316: [
317: 0 1 n 1 sub { /i set (x) i (dollar) dc 2 cat_n } for
318: 0 1 n 1 sub { /i set (d) i (dollar) dc 2 cat_n } for
319: ] /arg1 set
320: ] pop
321: popVariables
322: arg1
323: } def
324:
325: %%%%%%%%%%%%%%%%%%%
326: /getVlist {
327: [/n /i ] pushVariables
328: [
329: /n [(N)] system_variable def
330: [
331: 0 1 n 1 sub { /i set [(x) (var) i] system_variable } for
332: 0 1 n 1 sub { /i set [(D) (var) i] system_variable } for
333: ] /arg1 set
334: ] pop
335: popVariables
336: arg1
337: } def
338:
339: %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
340: [(chattr) 0 /findIntegralRoots] extension pop
341: oxasir.verbose {
342: (Overloaded on findIntegralRoots.) message
343: } { } ifelse
344: /findIntegralRoots {
345: /arg1 set
346: [/in-findIntegralRoots /pp ] pushVariables
347: [
348: /pp arg1 def
349: oxasir.ccc [ ] eq {
350: (Starting ox_asir server.) message
351: ox_asirConnectMethod
352: } { } ifelse
353: oxasir.ccc oxIsServerReady
354: { pp findIntegralRoots.oxasir /arg1 set}
355: { pp findIntegralRoots.slow /arg1 set} ifelse
356: ] pop
357: popVariables
358: arg1
359: } def
360:
361: /findIntegralRoots.oxasir {
362: /arg1 set
363: [/in-findIntegralRoots /f /r /g /aa /rlist] pushVariables
364: [(CurrentRingp) (KanGBmessage)] pushEnv
365: [
366: /f arg1 def
367: [(s) ring_of_polynomials 0] define_ring
368: f toString . /f set
369: f fctr rest /g set
370: g {
371: 0 get /aa set
372: aa (s). degree 1 eq {
373: aa (s). coeff 1 get /aa set
374: aa length 1 eq { 0 }
375: { aa 0 get (1). eq {
376: 0 << aa 1 get (integer) dc >> sub
377: } { } ifelse
378: } ifelse
379: }{ } ifelse
380: } map
381: /rlist set
382: %% rlist ::
383: [-1000000] rlist join shell rest /arg1 set
384: ] pop
385: popEnv
386: popVariables
387: arg1
388: } def
389:
390:
391: %%%%%%%%%%%%%%%%%%%%%%%%%%
392:
393: /asirconnectr {
394: [/in-asirconnectr /pass /peer /data /control /oxasir] pushVariables
395: [
396: /pass [(oxGenPass)] extension def
397: /peer [(oxGetPort) (localhost)] extension def
398: /data peer 1 get toString def
399: /control peer 3 get toString def
400: peer message
401: [oxpath.oxlog.xterm oxpath.ox ( -reverse -ox ) oxasirpath.oxasir
402: ( -data ) data ( -control ) control ( -pass ) pass
403: oxpath.null
404: ( &)] cat system
405: [(oxCreateClient2) peer 0 pass] extension /oxasir set
406: %% 0 means connect from only localhost.
407: oxasir asirinit
408: /arg1 oxasir def
409: ] pop
410: popVariables
411: arg1
412: } def
413: [(asirconnectr)
414: [(asirconnectr server (ox_asir function))
415: (array server;)
416: (Example: asirconnectr /oxasir.ccc set)
417: ]] putUsages
418:
419:
420: %%%%%%%%%%%%% From gbhg3/Int/intw.sm1
421: %% This function needs solv1.asir and ox_asir.
422: %% See solv1.asir for the usage of this function.
423: /rationalRoots2 {
424: /arg1 set
425: [/in-rationalRoots2 /aa /f /comm /vvv /r /setarg
426: /w /ans
427: ] pushVariables
428: [(CurrentRingp) (KanGBmessage)] pushEnv
429: [
430: /aa arg1 def
431: aa isArray { } { (<<array>> rationalRoots2) error } ifelse
432: /setarg 0 def
433: oxasir.ccc [ ] eq {
434: (Starting ox_asir server.) message
435: ox_asirConnectMethod
436: } { } ifelse
437: aa { tag } map /typev set
438: typev [ArrayP StringP ArrayP] eq
439: { /f aa 0 get def
440: /vvv [ aa 1 get to_records pop ] def
441: /w aa 2 get def
442: /setarg 1 def
443: } { } ifelse
444: typev [ArrayP ArrayP ArrayP] eq
445: { /f aa 0 get def
446: /vvv aa 1 get {toString} map def
447: /setarg 1 def
448: /w aa 2 get def
449: } { } ifelse
450: setarg { } { (rationalRoots2 : Argument mismatch) error } ifelse
451:
452:
453: [vvv from_records ring_of_polynomials 0] define_ring
454: f { toString . } map /f set
455: vvv { . } map /vvv set
456: w { toString . } map /w set
457:
458: (rationalRoots2 -- f = ) messagen f messagen
459: ( , vvv= ) messagen vvv messagen ( , w = ) messagen w message
460:
461: vvv length 1 eq w 0 get (1). eq and
462: {
463: [(KanGBmessage) 0] system_variable
464: [f] groebner_sugar 0 get /f set
465: vvv 0 get toString (s) eq {
466: }{ [[vvv 0 get toString (s)] from_records ring_of_polynomials 0] define_ring}
467: ifelse
468: f 0 get toString . [[vvv 0 get toString . (s).]] replace
469: findIntegralRoots /ans set
470: }
471: {
472: oxasir.ccc [(sm1_rationalRoots2) f vvv w] asir
473: {(integer) dc} map
474: /ans set
475: } ifelse
476:
477: /arg1 ans def
478: ] pop
479: popEnv
480: popVariables
481: arg1
482: } def
483: [(rationalRoots2)
484: [(rationalRoots2 (ox_asir function) called from intw.sm1 to analyze integral)
485: (roots.)
486: ]] putUsages
487:
488: /ptozp_subst {
489: /arg1 set
490: [/in-ptozp_subst /aaa /fff /xxx /vvv /vlist] pushVariables
491: [(CurrentRingp)] pushEnv
492: [
493: /aaa arg1 def
494: /fff aaa 0 get def
495: /xxx aaa 1 get toString def
496: /vvv aaa 2 get {toString ..} map def
497: aaa length 4 eq {
498: /vlist aaa 3 get def
499: } {
500: /vlist 0 def
501: } ifelse
502: oxasir.ccc [ ] eq {
503: (Starting ox_asir server.) message
504: ox_asirConnectMethod
505: } { } ifelse
506: fff isPolynomial {
507: fff (ring) dc ring_def
508: fff toString /fff set
509: }
510: { vlist isInteger { (ptozp_subst: need variable names.) error } { } ifelse
511: [vlist ring_of_differential_operators 0] define_ring
512: } ifelse
513: oxasir.ccc [(sm1_ptozp_subst) fff . xxx . vvv] asir
514: /arg1 set
515: ] pop
516: popEnv
517: popVariables
518: arg1
519: } def
520:
521: [(ptozp_subst)
522: [$[f s [p q] v] ptozp_subst g (ox_asir function)$
523: $It returns ptozp(subst(f,s,p/q))$
524: $Example 1: [ (x Dx - s) (s) [2 3] (x,s)] ptozp_subst $
525: $ ===> 3 x Dx - 2 $
526: ]] putUsages
527:
528: /reduceByAsir {
529: /arg1 set
530: [/in-reduceByAsir /aaa /fff /fff0 /fff1 /vlist] pushVariables
531: [(CurrentRingp)] pushEnv
532: [
533: /aaa arg1 def
534: /fff aaa 0 get def
535: aaa length 2 eq {
536: /vlist aaa 1 get def
537: } {
538: /vlist 0 def
539: } ifelse
540: oxasir.ccc [ ] eq {
541: (Starting ox_asir server.) message
542: ox_asirConnectMethod
543: } { } ifelse
544: fff isArray {
545: fff length 2 eq {
546: /fff0 fff 0 get def
547: /fff1 fff 1 get def
548: } {
549: ([ << [f g] >> vlist ] reduceByAsir ) error
550: } ifelse
551: } {
552: ([ << [f g] >> vlist ] reduceByAsir ) error
553: } ifelse
554: fff0 isPolynomial fff1 isPolynomial and {
555: fff0 (ring) dc ring_def
556: fff0 toString . /fff0 set
557: fff1 (ring) dc ring_def
558: fff1 toString . /fff1 set
559: }
560: { vlist isInteger { (reduceByAsir: need variable names.) error } { } ifelse
561: [vlist ring_of_differential_operators 0] define_ring
562: fff0 toString . /fff0 set
563: fff1 toString . /fff1 set
564: } ifelse
565: oxasir.ccc [(sm1_rat2plist2) [fff0 fff1]] asir
566: /arg1 set
567: ] pop
568: popEnv
569: popVariables
570: arg1
571: } def
572:
573: [(reduceByAsir)
574: [$ [[f g] v] reduceByAsir [ff gg] (ox_asir function)$
575: $ [[f g]] reduceByAsir [ff gg] $
576: $Example 1: [[(2 x -2) (4 x - 8)] (x)] reduceByAsir $
577: (Note that there may be a gcd that is more than 1 among the coefficients.)
578: ]] putUsages
579:
580: /oxasir.sm1.loaded 1 def
581: initializePathNamesForOxAsir %% This should be the last.
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>