[BACK]Return to Diff-ja.texi CVS log [TXT][DIR] Up to [local] / OpenXM / src / asir-contrib / packages / doc

Annotation of OpenXM/src/asir-contrib/packages/doc/Diff-ja.texi, Revision 1.3

1.3     ! takayama    1: @c $OpenXM: OpenXM/src/asir-contrib/packages/doc/Diff-ja.texi,v 1.2 2002/08/04 07:37:46 takayama Exp $
1.1       takayama    2: @node Differential equations (library by Okutani),,, Top
                      3: @chapter Differential equations (library by Okutani)
1.2       takayama    4: $B%U%!%$%k(B @file{gr}, @file{Matrix}, @file{Diff} $B$,I,MW$G$9(B.
1.3     ! takayama    5:
        !             6: OpenXM/Risa/Asir $B$G$NMxMQ$K$"$?$C$F$O(B,
        !             7: @example
        !             8: load("Diff")$
        !             9: @end example
        !            10: $B$,;O$a$KI,MW(B.
        !            11:
1.1       takayama   12:
                     13: Yukio Okutani $B;a$K$h$k(B Risa/Asir $B8@8l$G=q$+$l$?O"N)@~7AJPHyJ,J}Dx<0MQ(B
                     14: $B$N%i%$%V%i%j$G$9(B.
                     15: $B$9$Y$F$N4X?tL>$O(B odiff_ $B$G;O$^$j$^$9(B.
                     16:
                     17: @tex
                     18: $B$3$N@a$G>R2p$5$l$k4X?t$G$OHyJ,:nMQAG$O%j%9%H$^$?$OB?9`<0$GI=8=$5$l$^$9(B.
                     19: $B%j%9%H$K$h$kI=8=$O<!$N$h$&$K$J$j$^$9(B.
                     20: $$ [ [f_{\alpha},[\alpha_{1},\ldots,\alpha_{n}]],\ldots ] $$
                     21: $B$3$l$O(B
                     22: $$ \sum_{\alpha}f_{\alpha}\partial^{\alpha} $$
                     23: $B$H$$$&0UL#$G$9(B. $B@~7?JPHyJ,J}Dx<07O(B
                     24: $$ (\sum_{\alpha^{(i)}}f_{\alpha^{(i)}}\partial^{\alpha^{(i)}})\bullet u = 0 \quad (i = 1,\ldots,s) $$
                     25: $B$J$I$N$h$&$KJ#?t$NHyJ,:nMQAG$rI=8=$9$k$H$-$OHyJ,:nMQAG$N%j%9%H$r;H$$$^$9(B.
                     26: $$ [ [ [f_{\alpha^{(1)}},[\alpha_{1}^{(1)},\ldots,\alpha_{n}^{(1)}]],\ldots ],\ldots,[ [f_{\alpha^{(s)}},[\alpha_{1}^{(s)},\ldots,\alpha_{n}^{(s)}]],\ldots ] ] $$
                     27: $BNc$($PHyJ,:nMQAG(B$x \partial_{x} + y \partial_{y} + 1$$B$N>l9g$O(B
                     28: $$ [ [x,[1,0]],[y,[0,1]],[1,[0,0]] ] $$
                     29: $B$H$J$j$^$9(B. $B$^$?HyJ,:nMQAG$N%j%9%H$G(B$x \partial_{x} + y \partial_{y} + 1, {\partial_{x}}^{2} + {\partial_{y}}^{2}$$B$rI=$9$H(B
                     30: $$ [ [ [x,[1,0]],[y,[0,1]],[1,[0,0]] ],[ [1,[2,0]],[1,[0,2]] ] ] $$
                     31: $B$H$J$j$^$9(B. $B$^$?$3$NI=8=K!$r;H$&$H$-$OJQ?t%j%9%H$r>o$K0U<1$7$F$$$kI,MW$,$"$j$^$9(B.
                     32: $B<!$KB?9`<0$K$h$kI=8=$K$D$$$F=R$Y$^$9(B. $BJQ?t(B$x$$B$KBP$9$kHyJ,$O(B$dx$$B$GI=8=$5$l$^$9(B.
                     33: $BNc$($P(B$x \partial_{x} + y \partial_{y} + 1$$B$K$D$$$F$O(B
                     34: $$ x*dx+y*dy+1 $$
                     35: $B$HI=8=$5$l$^$9(B.
                     36: @end tex
                     37: @menu
                     38: @c * odiff_op_hg1::
                     39: @c * odiff_op_appell1::
                     40: @c * odiff_op_appell2::
                     41: @c * odiff_op_appell3::
                     42: * odiff_op_appell4::
                     43: @c * odiff_op_selberg2::
                     44: @c * odiff_op_gkz::
                     45: * odiff_op_tosm1::
                     46: * odiff_op_toasir::
                     47: * odiff_op_fromasir::
                     48: * odiff_act::
                     49: @c * odiff_act_hg1::
                     50: @c * odiff_act_appell1::
                     51: @c * odiff_act_appell2::
                     52: @c * odiff_act_appell3::
                     53: * odiff_act_appell4::
                     54: @c * odiff_act_selberg2::
                     55: @c * odiff_act_gkz::
                     56: * odiff_poly_solve::
                     57: * odiff_poly_solve_hg1::
                     58: @c * odiff_poly_solve_appell1::
                     59: @c * odiff_poly_solve_appell2::
                     60: @c * odiff_poly_solve_appell3::
                     61: * odiff_poly_solve_appell4::
                     62: @c * odiff_poly_solve_selberg2::
                     63: @c * odiff_poly_solve_gkz::
                     64: * odiff_rat_solve::
                     65: @c * odiff_pseries_appell4::
                     66: @end menu
                     67:
                     68: @node odiff_op_appell4,,, Differential equations (library by Okutani)
                     69: @subsection @code{odiff_op_appell4}
                     70: @findex odiff_op_appell4
                     71: @table @t
                     72: @item odiff_op_appell4(@var{a},@var{b},@var{c1},@var{c2},@var{V})
                     73: ::  appell $B$N(B F_4 $B$rNm2=$9$kHyJ,:nMQAG$r@8@.$7$^$9(B.
                     74: @end table
                     75: @table @var
                     76: @item return
                     77: $B%j%9%H(B
                     78: @item a, b, c1, c2
                     79: $BM-M}<0(B
                     80: @item V
                     81: $B%j%9%H(B
                     82: @end table
                     83: @itemize @bullet
                     84: @item  @code{odiff_op_appell4}$B$NNc(B.
                     85: @end itemize
                     86: @example
                     87: [298] odiff_op_appell4(a,b,c1,c2,[x,y]);
                     88: [ [ [-x^2+x,[2,0]], [-2*y*x,[1,1]], [-y^2,[0,2]],
                     89:     [(-a-b-1)*x+c1,[1,0]], [(-a-b-1)*y,[0,1]], [-b*a,[0,0]] ],
                     90:   [ [-y^2+y,[0,2]], [-2*y*x,[1,1]], [-x^2,[2,0]],
                     91:     [(-a-b-1)*y+c2,[0,1]], [(-a-b-1)*x,[1,0]], [-b*a,[0,0]] ] ]
                     92: @end example
                     93:
                     94: @node odiff_op_tosm1,,, Differential equations (library by Okutani)
                     95: @subsection @code{odiff_op_tosm1}
                     96: @findex odiff_op_tosm1
                     97: @table @t
                     98: @item odiff_op_tosm1(@var{LL},@var{V})
                     99: ::  $B%j%9%H7A<0$NHyJ,:nMQAG%j%9%H$r(B sm1 $B7A<0$KJQ49$7$^$9(B.
                    100: @end table
                    101: @table @var
                    102: @item return
                    103: $B%j%9%H(B
                    104: @item LL
                    105: $B%j%9%H(B
                    106: @item V
                    107: $B%j%9%H(B
                    108: @end table
                    109: @itemize @bullet
                    110: @item  $BHyJ,:nMQAG$N78?t$O@0?tB?9`<0$KJQ49$5$l$^$9(B.
                    111: @item  @code{odiff_op_tosm1}$B$NNc(B
                    112: @end itemize
                    113: @example
                    114: [299] odiff_op_tosm1([[[x,[2,0]],[-1,[0,0]]],
                    115:                           [[y,[0,2]],[-1,[0,0]]]],[x,y]);
                    116: [ + ( + (1) x) dx^2 + ( + (-1)), + ( + (1) y) dy^2 + ( + (-1))]
                    117:
                    118: [300] odiff_op_tosm1([[[x,[1,0]],[y,[0,1]],[1,[0,0]]],
                    119:                           [[1,[2,0]],[1,[0,2]]]],[x,y]);
                    120: [ + ( + (1) x) dx + ( + (1) y) dy + ( + (1)), + ( + (1)) dx^2 + ( + (1)) dy^2]
                    121:
                    122: [301] odiff_op_tosm1([[[1/2,[1,0]],[1,[0,0]]],
                    123:                           [[1/3,[0,1]],[1/4,[0,0]]]],[x,y]);
                    124: [ + ( + (6)) dx + ( + (12)), + ( + (4)) dy + ( + (3))]
                    125:
                    126: [302] odiff_op_tosm1([[[1/2*x,[1,0]],[1,[0,0]]],
                    127:                           [[1/3*y,[0,1]],[1/4,[0,0]]]],[x,y]);
                    128: [ + ( + (6) x) dx + ( + (12)), + ( + (4) y) dy + ( + (3))]
                    129: @end example
                    130:
                    131: @node odiff_op_toasir,,, Differential equations (library by Okutani)
                    132: @subsection @code{odiff_op_toasir}
                    133: @findex odiff_op_toasir
                    134: @table @t
                    135: @item odiff_op_toasir(@var{LL},@var{V})
                    136: ::  $B%j%9%H7A<0$NHyJ,:nMQAG%j%9%H(B @var{LL} $B$r(B @code{asir} $B$NB?9`<0$KJQ49$7$^$9(B.
                    137: @end table
                    138: @table @var
                    139: @item return
                    140: $B%j%9%H(B
                    141: @item LL
                    142: $B%j%9%H(B
                    143: @item V
                    144: $B%j%9%H(B
                    145: @end table
                    146: @itemize @bullet
                    147: @item  @code{odiff_op_toasir}$B$NNc(B
                    148: @end itemize
                    149: @example
                    150: [303] odiff_op_toasir([[[1/2*x,[1,0]],[1,[0,0]]],
                    151:                            [[1/3*y,[0,1]],[1/4,[0,0]]]],[x,y]);
                    152: [1/2*x*dx+1,1/3*y*dy+1/4]
                    153:
                    154: [304] odiff_op_toasir([[[x,[1,0]],[y,[0,1]],[1,[0,0]]],
                    155:                            [[1,[2,0]],[1,[0,2]]]],[x,y]);
                    156: [x*dx+y*dy+1,dx^2+dy^2]
                    157: @end example
                    158:
                    159: @node odiff_op_fromasir,,, Differential equations (library by Okutani)
                    160: @subsection @code{odiff_op_fromasir}
                    161: @findex odiff_op_fromasir
                    162: @table @t
                    163: @item odiff_op_fromasir(@var{D_list},@var{V})
                    164: ::  @code{asir} $B$NB?9`<0$+$i%j%9%H7A<0$NHyJ,:nMQAG%j%9%H$KJQ49$7$^$9(B.
                    165: @end table
                    166: @table @var
                    167: @item return
                    168: $B%j%9%H(B
                    169: @item D_list
                    170: $B%j%9%H(B
                    171: @item V
                    172: $B%j%9%H(B
                    173: @end table
                    174: @itemize @bullet
                    175: @item  @code{odiff_op_fromasir}$B$NNc(B
                    176: @end itemize
                    177: @example
                    178: [305] odiff_op_fromasir([1/2*x*dx+1,1/3*y*dy+1/4],[x,y]);
                    179: [[[1/2*x,[1,0]],[1,[0,0]]],[[1/3*y,[0,1]],[1/4,[0,0]]]]
                    180:
                    181: [306] odiff_op_fromasir([x*dx+y*dy+1,dx^2+dy^2],[x,y]);
                    182: [[[x,[1,0]],[y,[0,1]],[1,[0,0]]],[[1,[2,0]],[1,[0,2]]]]
                    183: @end example
                    184:
                    185: @node odiff_act,,, Differential equations (library by Okutani)
                    186: @subsection @code{odiff_act}
                    187: @findex odiff_act
                    188: @table @t
                    189: @item odiff_act(@var{L},@var{F},@var{V})
                    190: ::  $BHyJ,:nMQAG(B @var{L} $B$rM-M}<0(B @var{F} $B$K:nMQ$5$;$k(B. @var{V} $B$OJQ?t%j%9%H(B.
                    191: @end table
                    192: @table @var
                    193: @item return
                    194: $BM-M}<0(B
                    195: @item L
                    196: $B%j%9%H(B or $BB?9`<0(B
                    197: @item F
                    198: $BM-M}<0(B
                    199: @item V
                    200: $B%j%9%H(B
                    201: @end table
                    202: @itemize @bullet
                    203: @item  @code{odiff_act}$B$NNc(B
                    204: @end itemize
                    205: @example
                    206: [302] odiff_act([[1,[2]]],x^3+x^2+x+1,[x]);
                    207: 6*x+2
                    208:
                    209: [303] odiff_act([[1,[1,0]],[1,[0,1]]],x^2+y^2,[x,y]);
                    210: 2*x+2*y
                    211:
                    212: [349] odiff_act(x*dx+y*dy, x^2+x*y+y^2, [x,y]);
                    213: 2*x^2+2*y*x+2*y^2
                    214: @end example
                    215:
                    216: @node odiff_act_appell4,,, Differential equations (library by Okutani)
                    217: @subsection @code{odiff_act_appell4}
                    218: @findex odiff_act_appell4
                    219: @table @t
                    220: @item odiff_act_appell4(@var{a},@var{b},@var{c1},@var{c2},@var{F},@var{V})
                    221: ::  $BHyJ,:nMQAG(B @code{odiff_op_appell4} $B$rM-M}<0(B @var{F} $B$K:nMQ$5$;$k(B.
                    222: @end table
                    223: @table @var
                    224: @item return
                    225: $B%j%9%H(B
                    226: @item a, b, c1, c2
                    227: $BM-M}<0(B
                    228: @item F
                    229: $BM-M}<0(B
                    230: @item V
                    231: $B%j%9%H(B
                    232: @end table
                    233: @itemize @bullet
                    234: @item  @code{odiff_act_appell4}$B$NNc(B
                    235: @end itemize
                    236: @example
                    237: [303] odiff_act_appell4(1,0,1,1,x^2+y^2,[x,y]);
                    238: [-6*x^2+4*x-6*y^2,-6*x^2-6*y^2+4*y]
                    239:
                    240: [304] odiff_act_appell4(0,0,1,1,x^2+y^2,[x,y]);
                    241: [-4*x^2+4*x-4*y^2,-4*x^2-4*y^2+4*y]
                    242:
                    243: [305] odiff_act_appell4(-2,-2,-1,-1,x^2+y^2,[x,y]);
                    244: [0,0]
                    245: @end example
                    246:
                    247: @node odiff_poly_solve,,, Differential equations (library by Okutani)
                    248: @subsection @code{odiff_poly_solve}
                    249: @findex odiff_poly_solve
                    250: @table @t
                    251: @item odiff_poly_solve(@var{LL},@var{N},@var{V})
                    252: ::  $BM?$($i$l$?@~7?HyJ,J}Dx<07O$N(B @var{N} $B<!0J2<$NB?9`<02r$r5a$a$k(B.
                    253: @end table
                    254: @table @var
                    255: @item return
                    256: $B%j%9%H(B
                    257: @item LL
                    258: $B%j%9%H(B
                    259: @item N
                    260: $B@0?t(B
                    261: @item V
                    262: $B%j%9%H(B
                    263: @end table
                    264: @itemize @bullet
                    265: @item  @code{odiff_poly_solve}$B$NNc(B.
                    266: @end itemize
                    267: @example
                    268: [297] odiff_poly_solve([[[x,[1,0]],[-1,[0,0]]],[[y,[0,1]],[-1,[0,0]]]],5,[x,y]);
                    269: [_4*y*x,[_4]]
                    270:
                    271: [298] odiff_poly_solve([[[x,[1,0]],[-2,[0,0]]],[[y,[0,1]],[-2,[0,0]]]],5,[x,y]);
                    272: [_33*y^2*x^2,[_33]]
                    273:
                    274: [356] odiff_poly_solve([x*dx+y*dy-3,dx+dy],4,[x,y]);
                    275: [-_126*x^3+3*_126*y*x^2-3*_126*y^2*x+_126*y^3,[_126]]
                    276: @end example
                    277:
                    278: @node odiff_poly_solve_hg1,,, Differential equations (library by Okutani)
                    279: @subsection @code{odiff_poly_solve_hg1}
                    280: @findex odiff_poly_solve_hg1
                    281: @table @t
                    282: @item odiff_poly_solve_hg1(@var{a},@var{b},@var{c},@var{V})
                    283: ::  $B%,%&%9$ND64v2?HyJ,J}Dx<0$NB?9`<02r$r5a$a$k(B.
                    284: @end table
                    285: @table @var
                    286: @item return
                    287: $B%j%9%H(B
                    288: @item a, b, c
                    289: $BM-M}<0(B
                    290: @item V
                    291: $B%j%9%H(B
                    292: @end table
                    293: @itemize @bullet
                    294: @item  @code{odiff_poly_solve_hg1}$B$NNc(B.
                    295: @end itemize
                    296: @example
                    297: [334] odiff_poly_solve_hg1(-3,-6,-5,[x]);
                    298: [_1*x^6-2*_0*x^3+9/2*_0*x^2-18/5*_0*x+_0,[_0,_1]]
                    299:
                    300: [335] odiff_poly_solve_hg1(-3,-6,-7,[x]);
                    301: [-4/7*_2*x^3+15/7*_2*x^2-18/7*_2*x+_2,[_2]]
                    302: @end example
                    303:
                    304: @node odiff_poly_solve_appell4,,, Differential equations (library by Okutani)
                    305: @subsection @code{odiff_poly_solve_appell4}
                    306: @findex odiff_poly_solve_appell4
                    307: @table @t
                    308: @item odiff_poly_solve_appell4(@var{a},@var{b},@var{c1},@var{c2},@var{V})
                    309: ::  F_4$B$,$_$?$9@~7?HyJ,J}Dx<07O$NB?9`<02r$r5a$a$k(B.
                    310: @end table
                    311: @table @var
                    312: @item return
                    313: $B%j%9%H(B
                    314: @item a, b, c1, c2
                    315: $BM-M}<0(B
                    316: @item V
                    317: $B%j%9%H(B
                    318: @end table
                    319: @itemize @bullet
                    320: @item  @code{odiff_poly_solve_appell4}$B$NNc(B.
                    321: @end itemize
                    322: @example
                    323: [299] odiff_poly_solve_appell4(-3,1,-1,-1,[x,y]);
                    324: [-_26*x^3+(3*_26*y+_26)*x^2+3*_24*y^2*x-_24*y^3+_24*y^2,[_24,_26]]
                    325:
                    326: [300] odiff_poly_solve_appell4(-3,1,1,-1,[x,y]);
                    327: [-3*_45*y^2*x-_45*y^3+_45*y^2,[_45]]
                    328: @end example
                    329:
                    330: @node odiff_rat_solve,,, Differential equations (library by Okutani)
                    331: @subsection @code{odiff_rat_solve}
                    332: @findex odiff_rat_solve
                    333: @table @t
                    334: @item odiff_rat_solve(@var{LL},@var{Dn},@var{N},@var{V})
                    335: ::  $BM?$($i$l$?@~7?HyJ,J}Dx<07O$NJ,Jl$,(B @var{Dn}, $BJ,;R$,(B @var{N} $B<!0J2<$NB?9`<0$G$"$k$h$&$J2r$r5a$a$k(B.
                    336: @end table
                    337: @table @var
                    338: @item return
                    339: $B%j%9%H(B
                    340: @item LL
                    341: $B%j%9%H(B
                    342: @item Dn
                    343: $BM-M}<0(B
                    344: @item N
                    345: $B@0?t(B
                    346: @item V
                    347: $B%j%9%H(B
                    348: @end table
                    349: @itemize @bullet
                    350: @item  @code{odiff_rat_solve}$B$NNc(B.
                    351: @end itemize
                    352: @example
                    353: [333] odiff_rat_solve([[[x,[1]],[1,[0]]]],x,1,[x]);
                    354: [(_8)/(x),[_8]]
                    355:
                    356: [361] odiff_rat_solve([x*(1-x)*dx^2+(1-3*x)*dx-1],1-x,2,[x]);
                    357: [(_180)/(-x+1),[_180]]
                    358:
                    359: [350] D = odiff_op_appell4(0,0,3,0,[x,y])$
                    360: [351] odiff_rat_solve(D,x^2,2,[x,y]);
                    361: [(_118*x^2-_114*y*x+1/2*_114*y^2+_114*y)/(x^2),[_114,_118]]
                    362: @end example

FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>