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