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