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