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