[BACK]Return to poly.texi CVS log [TXT][DIR] Up to [local] / OpenXM / src / asir-doc / parts / builtin

Annotation of OpenXM/src/asir-doc/parts/builtin/poly.texi, Revision 1.5

1.5     ! noro        1: @comment $OpenXM: OpenXM/src/asir-doc/parts/builtin/poly.texi,v 1.4 2003/04/19 15:44:59 noro Exp $
1.2       noro        2: \BJP
1.1       noro        3: @node $BB?9`<0$*$h$SM-M}<0$N1i;;(B,,, $BAH$_9~$_H!?t(B
                      4: @section $BB?9`<0(B, $BM-M}<0$N1i;;(B
1.2       noro        5: \E
                      6: \BEG
                      7: @node Polynomials and rational expressions,,, Built-in Function
                      8: @section operations with polynomials and rational expressions
                      9: \E
1.1       noro       10:
                     11: @menu
                     12: * var::
                     13: * vars::
                     14: * uc::
                     15: * coef::
                     16: * deg mindeg::
                     17: * nmono::
                     18: * ord::
                     19: * sdiv sdivm srem sremm sqr sqrm::
                     20: * tdiv::
                     21: * %::
                     22: * subst psubst::
                     23: * diff::
                     24: * res::
                     25: * fctr sqfr::
                     26: * modfctr::
                     27: * ufctrhint::
                     28: * ptozp::
                     29: * prim cont::
                     30: * gcd gcdz::
                     31: * red::
                     32: @end menu
                     33:
1.2       noro       34: \JP @node var,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                     35: \EG @node var,,, Polynomials and rational expressions
1.1       noro       36: @subsection @code{var}
                     37: @findex var
                     38:
                     39: @table @t
                     40: @item var(@var{rat})
1.2       noro       41: \JP :: @var{rat} $B$N<gJQ?t(B.
                     42: \EG :: Main variable (indeterminate) of @var{rat}.
1.1       noro       43: @end table
                     44:
                     45: @table @var
                     46: @item return
1.2       noro       47: \JP $BITDj85(B
                     48: \EG indeterminate
1.1       noro       49: @item rat
1.2       noro       50: \JP $BM-M}<0(B
                     51: \EG rational expression
1.1       noro       52: @end table
                     53:
                     54: @itemize @bullet
1.2       noro       55: \BJP
1.1       noro       56: @item
                     57: $B<gJQ?t$K4X$7$F$O(B, @xref{Asir $B$G;HMQ2DG=$J7?(B}.
                     58: @item
                     59: $B%G%U%)%k%H$NJQ?t=g=x$O<!$N$h$&$K$J$C$F$$$k(B.
                     60:
                     61: @code{x}, @code{y}, @code{z}, @code{u}, @code{v}, @code{w}, @code{p}, @code{q}, @code{r}, @code{s}, @code{t}, @code{a}, @code{b}, @code{c}, @code{d}, @code{e},
                     62: @code{f}, @code{g}, @code{h}, @code{i}, @code{j}, @code{k}, @code{l}, @code{m}, @code{n}, @code{o},$B0J8e$OJQ?t$N8=$l$?=g(B.
1.2       noro       63: \E
                     64: \BEG
                     65: @item
1.3       noro       66: See @ref{Types in Asir} for main variable.
1.2       noro       67: @item
                     68: Indeterminates (variables) are ordered by default as follows.
                     69:
                     70: @code{x}, @code{y}, @code{z}, @code{u}, @code{v}, @code{w}, @code{p}, @code{q},
                     71: @code{r}, @code{s}, @code{t}, @code{a}, @code{b}, @code{c}, @code{d}, @code{e},
                     72: @code{f}, @code{g}, @code{h}, @code{i}, @code{j}, @code{k}, @code{l}, @code{m},
                     73: @code{n}, @code{o}. The other variables will be ordered after the above noted variables
                     74: so that the first comer will be ordered prior to the followers.
                     75: \E
1.1       noro       76: @end itemize
                     77:
                     78: @example
                     79: [0] var(x^2+y^2+a^2);
                     80: x
                     81: [1] var(a*b*c*d*e);
                     82: a
                     83: [2] var(3/abc+2*xy/efg);
                     84: abc
                     85: @end example
                     86:
                     87: @table @t
1.2       noro       88: \JP @item $B;2>H(B
                     89: \EG @item References
1.1       noro       90: @fref{ord}, @fref{vars}.
                     91: @end table
                     92:
1.2       noro       93: \JP @node vars,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                     94: \EG @node vars,,, Polynomials and rational expressions
1.1       noro       95: @subsection @code{vars}
                     96: @findex vars
                     97:
                     98: @table @t
                     99: @item vars(@var{obj})
1.2       noro      100: \JP :: @var{obj} $B$K4^$^$l$kJQ?t$N%j%9%H(B.
                    101: \EG :: A list of variables (indeterminates) in an expression @var{obj}.
1.1       noro      102: @end table
                    103:
                    104: @table @var
                    105: @item return
1.2       noro      106: \JP $B%j%9%H(B
                    107: \EG list
1.1       noro      108: @item obj
1.2       noro      109: \JP $BG$0U(B
                    110: \EG arbitrary
1.1       noro      111: @end table
                    112:
                    113: @itemize @bullet
1.2       noro      114: \BJP
1.1       noro      115: @item
                    116: $BM?$($i$l$?<0$K4^$^$l$kJQ?t$N%j%9%H$rJV$9(B.
                    117: @item
                    118: $BJQ?t=g=x$N9b$$$b$N$+$i=g$KJB$Y$k(B.
1.2       noro      119: \E
                    120: \BEG
                    121: @item
                    122: Returns a list of variables (indeterminates) contained in a given expression.
                    123: @item
                    124: Lists variables according to the variable ordering.
                    125: \E
1.1       noro      126: @end itemize
                    127:
                    128: @example
                    129: [0] vars(x^2+y^2+a^2);
                    130: [x,y,a]
                    131: [1] vars(3/abc+2*xy/efg);
                    132: [abc,xy,efg]
                    133: [2] vars([x,y,z]);
                    134: [x,y,z]
                    135: @end example
                    136:
                    137: @table @t
1.2       noro      138: \JP @item $B;2>H(B
                    139: \EG @item References
1.1       noro      140: @fref{var}, @fref{uc}, @fref{ord}.
                    141: @end table
                    142:
1.2       noro      143: \JP @node uc,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    144: \EG @node uc,,, Polynomials and rational expressions
1.1       noro      145: @subsection @code{uc}
                    146: @findex uc
                    147:
                    148: @table @t
                    149: @item uc()
1.2       noro      150: \JP :: $BL$Dj78?tK!$N$?$a$NITDj85$r@8@.$9$k(B.
                    151: \EG :: Create a new indeterminate for an undermined coeficient.
1.1       noro      152: @end table
                    153:
                    154: @table @var
                    155: @item return
1.2       noro      156: \JP @code{vtype} $B$,(B 1 $B$NITDj85(B
                    157: \EG indeterminate with its @code{vtype} 1.
1.1       noro      158: @end table
                    159:
                    160: @itemize @bullet
1.2       noro      161: \BJP
1.1       noro      162: @item
                    163: @code{uc()} $B$r<B9T$9$k$?$S$K(B, @code{_0}, @code{_1}, @code{_2},... $B$H$$$&(B
                    164: $BITDj85$r@8@.$9$k(B.
                    165: @item
                    166: @code{uc()} $B$G@8@.$5$l$?ITDj85$O(B, $BD>@\%-!<%\!<%I$+$iF~NO$9$k$3$H$,$G$-$J$$(B.
                    167: $B$3$l$O(B, $B%W%m%0%i%`Cf$GL$Dj78?t$r<+F0@8@.$9$k>l9g(B, $BF~NO$J$I$K4^$^$l$k(B
                    168: $BITDj85$HF10l$N$b$N$,@8@.$5$l$k$3$H$rKI$0$?$a$G$"$k(B.
                    169: @item
                    170: $BDL>o$NITDj85(B (@code{vtype} $B$,(B 0) $B$N<+F0@8@.$K$O(B @code{rtostr()},
                    171: @code{strtov()} $B$rMQ$$$k(B.
                    172: @item
                    173: @code{uc()} $B$G@8@.$5$l$?ITDj85$NITDj85$H$7$F$N7?(B (@code{vtype}) $B$O(B 1 $B$G$"$k(B.
1.3       noro      174: (@xref{$BITDj85$N7?(B}.)
1.2       noro      175: \E
                    176: \BEG
                    177: @item
                    178: At every evaluation of command @code{uc()}, a new indeterminate in
                    179: the sequence of indeterminates @code{_0}, @code{_1}, @code{_2}, @dots{}
                    180: is created successively.
                    181: @item
                    182: Indeterminates created by @code{uc()} cannot be input on the keyboard.
                    183: By this property, you are free, no matter how many indeterminates you
                    184: will create dynamically by a program, from collision of created names
                    185: with indeterminates input from the keyboard or from program files.
                    186: @item
                    187: Functions, @code{rtostr()} and @code{strtov()}, are used to create
                    188: ordinary indeterminates (indeterminates having 0 for their @code{vtype}).
                    189: @item
                    190: Kernel sub-type of indeterminates created by @code{uc()} is 1.
                    191: (@code{vtype(uc())}=1)
                    192: \E
1.1       noro      193: @end itemize
                    194:
                    195: @example
                    196: [0] A=uc();
                    197: _0
                    198: [1] B=uc();
                    199: _1
                    200: [2] (uc()+uc())^2;
                    201: _2^2+2*_3*_2+_3^2
                    202: [3] (A+B)^2;
                    203: _0^2+2*_1*_0+_1^2
                    204: @end example
                    205:
                    206: @table @t
1.2       noro      207: \JP @item $B;2>H(B
                    208: \EG @item References
1.1       noro      209: @fref{vtype}, @fref{rtostr}, @fref{strtov}.
                    210: @end table
                    211:
1.2       noro      212: \JP @node coef,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    213: \EG @node coef,,, Polynomials and rational expressions
1.1       noro      214: @subsection @code{coef}
                    215: @findex coef
                    216:
                    217: @table @t
                    218: @item coef(@var{poly},@var{deg}[,@var{var}])
1.2       noro      219: \JP :: @var{poly} $B$N(B @var{var} ($B>JN,;~$O<gJQ?t(B) $B$K4X$9$k(B @var{deg} $B<!$N78?t(B.
                    220: \BEG
                    221: :: The coefficient of a polynomial @var{poly} at degree @var{deg}
                    222: with respect to the variable @var{var} (main variable if unspecified).
                    223: \E
1.1       noro      224: @end table
                    225:
                    226: @table @var
                    227: @item return
1.2       noro      228: \JP $BB?9`<0(B
                    229: \EG polynomial
1.1       noro      230: @item poly
1.2       noro      231: \JP $BB?9`<0(B
                    232: \EG polynomial
1.1       noro      233: @item var
1.2       noro      234: \JP $BITDj85(B
                    235: \EG indeterminate
1.1       noro      236: @item deg
1.2       noro      237: \JP $B<+A3?t(B
                    238: \EG non-negative integer
1.1       noro      239: @end table
                    240:
                    241: @itemize @bullet
1.2       noro      242: \BJP
1.1       noro      243: @item
                    244: @var{poly} $B$N(B @var{var} $B$K4X$9$k(B @var{deg} $B<!$N78?t$r=PNO$9$k(B.
                    245: @item
                    246: @var{var} $B$O(B, $B>JN,$9$k$H<gJQ?t(B @t{var}(@var{poly}) $B$@$H$_$J$5$l$k(B.
                    247: @item
                    248: @var{var} $B$,<gJQ?t$G$J$$;~(B, @var{var} $B$,<gJQ?t$N>l9g$KHf3S$7$F(B
                    249: $B8zN($,Mn$A$k(B.
1.2       noro      250: \E
                    251: \BEG
                    252: @item
                    253: The coefficient of a polynomial @var{poly} at degree @var{deg}
                    254: with respect to the variable @var{var}.
                    255: @item
                    256: The default value for @var{var} is the main variable, i.e.,
                    257: @t{var(@var{poly})}.
                    258: @item
                    259: For multi-variate polynomials, access to coefficients depends on
                    260: the specified indeterminates.  For example, taking coef for the main
                    261: variable is much faster than for other variables.
                    262: \E
1.1       noro      263: @end itemize
                    264:
                    265: @example
                    266: [0] A = (x+y+z)^3;
                    267: x^3+(3*y+3*z)*x^2+(3*y^2+6*z*y+3*z^2)*x+y^3+3*z*y^2+3*z^2*y+z^3
                    268: [1] coef(A,1,y);
                    269: 3*x^2+6*z*x+3*z^2
                    270: [2] coef(A,0);
                    271: y^3+3*z*y^2+3*z^2*y+z^3
                    272: @end example
                    273:
                    274: @table @t
1.2       noro      275: \JP @item $B;2>H(B
                    276: \EG @item References
1.1       noro      277: @fref{var}, @fref{deg mindeg}.
                    278: @end table
                    279:
1.2       noro      280: \JP @node deg mindeg,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    281: \EG @node deg mindeg,,, Polynomials and rational expressions
1.1       noro      282: @subsection @code{deg}, @code{mindeg}
                    283: @findex deg
                    284: @findex mindeg
                    285:
                    286: @table @t
                    287: @item deg(@var{poly},@var{var})
1.2       noro      288: \JP :: @var{poly} $B$N(B, $BJQ?t(B @var{var} $B$K4X$9$k:G9b<!?t(B.
                    289: \EG :: The degree of a polynomial @var{poly} with respect to variable.
1.1       noro      290: @item mindeg(@var{poly},@var{var})
1.2       noro      291: \JP :: @var{poly} $B$N(B, $BJQ?t(B @var{var} $B$K4X$9$k:GDc<!?t(B.
                    292: \BEG
                    293: :: The least exponent of the terms with non-zero coefficients in
                    294: a polynomial @var{poly} with respect to the variable @var{var}.
                    295: In this manual, this quantity is sometimes referred to the minimum
                    296: degree of a polynomial for short.
                    297: \E
1.1       noro      298: @end table
                    299:
                    300: @table @var
                    301: @item return
1.2       noro      302: \JP $B<+A3?t(B
                    303: \EG non-negative integer
1.1       noro      304: @item poly
1.2       noro      305: \JP $BB?9`<0(B
                    306: \EG polynomial
1.1       noro      307: @item var
1.2       noro      308: \JP $BITDj85(B
                    309: \EG indeterminate
1.1       noro      310: @end table
                    311:
                    312: @itemize @bullet
1.2       noro      313: \BJP
1.1       noro      314: @item
                    315: $BM?$($i$l$?B?9`<0$NJQ?t(B @var{var} $B$K4X$9$k:G9b<!?t(B, $B:GDc<!?t$r=PNO$9$k(B.
                    316: @item
                    317: $BJQ?t(B @var{var} $B$r>JN,$9$k$3$H$O=PMh$J$$(B.
1.2       noro      318: \E
                    319: \BEG
                    320: @item
                    321: The least exponent of the terms with non-zero coefficients in
                    322: a polynomial @var{poly} with respect to the variable @var{var}.
                    323: In this manual, this quantity is sometimes referred to the minimum
                    324: degree of a polynomial for short.
                    325: @item
                    326: Variable @var{var} must be specified.
                    327: \E
1.1       noro      328: @end itemize
                    329:
                    330: @example
                    331: [0] deg((x+y+z)^10,x);
                    332: 10
                    333: [1] deg((x+y+z)^10,w);
                    334: 0
                    335: [75] mindeg(x^2+3*x*y,x);
                    336: 1
                    337: @end example
                    338:
1.2       noro      339: \JP @node nmono,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    340: \EG @node nmono,,,Polynomials and rational expressions
1.1       noro      341: @subsection @code{nmono}
                    342: @findex nmono
                    343:
                    344: @table @t
                    345: @item nmono(@var{rat})
1.2       noro      346: \JP :: @var{rat} $B$NC19`<0$N9`?t(B.
                    347: \EG :: Number of monomials in rational expression @var{rat}.
1.1       noro      348: @end table
                    349:
                    350: @table @var
                    351: @item return
1.2       noro      352: \JP $B<+A3?t(B
                    353: \EG non-negative integer
1.1       noro      354: @item rat
1.2       noro      355: \JP $BM-M}<0(B
                    356: \EG rational expression
1.1       noro      357: @end table
                    358:
                    359: @itemize @bullet
1.2       noro      360: \BJP
1.1       noro      361: @item
                    362: $BB?9`<0$rE83+$7$?>uBV$G$N(B 0 $B$G$J$$78?t$r;}$DC19`<0$N9`?t$r5a$a$k(B.
                    363: @item
                    364: $BM-M}<0$N>l9g$O(B, $BJ,;R$HJ,Jl$N9`?t$NOB$,JV$5$l$k(B.
                    365: @item
1.3       noro      366: $BH!?t7A<0(B (@ref{$BITDj85$N7?(B}) $B$O(B, $B0z?t$,2?$G$"$C$F$bC19`$H$_$J$5$l$k(B. (1 $B8D$NITDj85$HF1$8(B. )
1.2       noro      367: \E
                    368: \BEG
                    369: @item
                    370: Number of monomials with non-zero number coefficients in the full
                    371: expanded form of the given polynomial.
                    372: @item
                    373: For a rational expression, the sum of the numbers of monomials
                    374: of the numerator and denominator.
                    375: @item
                    376: A function form is regarded as a single indeterminate no matter how
                    377: complex arguments it has.
                    378: \E
1.1       noro      379: @end itemize
                    380:
                    381: @example
                    382: [0] nmono((x+y)^10);
                    383: 11
                    384: [1] nmono((x+y)^10/(x+z)^10);
                    385: 22
                    386: [2] nmono(sin((x+y)^10));
                    387: 1
                    388: @end example
                    389:
                    390: @table @t
1.2       noro      391: \JP @item $B;2>H(B
                    392: \EG @item References
1.1       noro      393: @fref{vtype}.
                    394: @end table
                    395:
1.2       noro      396: \JP @node ord,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    397: \EG @node ord,,, Polynomials and rational expressions
1.1       noro      398: @subsection @code{ord}
                    399: @findex ord
                    400:
                    401: @table @t
                    402: @item ord([@var{varlist}])
1.2       noro      403: \JP :: $BJQ?t=g=x$N@_Dj(B
                    404: \EG :: It sets the ordering of indeterminates (variables).
1.1       noro      405: @end table
                    406:
                    407: @table @var
                    408: @item return
1.2       noro      409: \JP $BJQ?t$N%j%9%H(B
                    410: \EG list of indeterminates
1.1       noro      411: @item varlist
1.2       noro      412: \JP $BJQ?t$N%j%9%H(B
                    413: \EG list of indeterminates
1.1       noro      414: @end table
                    415:
                    416: @itemize @bullet
1.2       noro      417: \BJP
1.1       noro      418: @item
                    419: $B0z?t$,$"$k$H$-(B, $B0z?t$NJQ?t%j%9%H$r@hF,$K=P$7(B, $B;D$j$NJQ?t$,$=$N8e$K(B
                    420: $BB3$/$h$&$KJQ?t=g=x$r@_Dj$9$k(B. $B0z?t$N$"$k$J$7$K4X$o$i$:(B, @code{ord()}
                    421: $B$N=*N;;~$K$*$1$kJQ?t=g=x%j%9%H$rJV$9(B.
                    422:
                    423: @item
                    424: $B$3$NH!?t$K$h$kJQ?t=g=x$NJQ99$r9T$C$F$b(B, $B4{$K%W%m%0%i%`JQ?t$J$I$K(B
                    425: $BBeF~$5$l$F$$$k<0$NFbIt7A<0$O?7$7$$=g=x$K=>$C$F$OJQ99$5$l$J$$(B.
                    426: $B=>$C$F(B, $B$3$NH!?t$K$h$k=g=x$NJQ99$O(B, @b{Asir} $B$N5/F0D>8e(B,
                    427: $B$"$k$$$O(B, $B?7$?$JJQ?t$,8=$l$?;~E@$K9T$o$l$k(B
                    428: $B$Y$-$G$"$k(B. $B0[$J$kJQ?t=g=x$N$b$H$G@8@.$5$l$?<0$I$&$7$N1i;;(B
                    429: $B$,9T$o$l$?>l9g(B, $BM=4|$;$L7k2L$,@8$:$k$3$H$b$"$jF@$k(B.
1.2       noro      430: \E
                    431: \BEG
                    432: @item
                    433: When an argument is given,
                    434: this function rearranges the ordering of variables (indeterminates)
                    435: so that the indeterminates in the argument @var{varlist} precede
                    436: and the other indeterminates follow in the system's variable ordering.
                    437: Regardless of the existence of an argument, it always returns the
                    438: final variable ordering.
                    439:
                    440: @item
                    441: Note that no change will be made to the variable ordering of internal
                    442: forms of objects which already exists in the system, no matter what
                    443: reordering you specify.  Therefore, the reordering should be limited to
                    444: the time just after starting @b{Asir}, or to the time when one has
                    445: decided himself to start a totally new computation which has no relation
                    446: with the previous results.
                    447: Note that unexpected results may be obtained from operations between
                    448: objects which are created under different variable ordering.
                    449: \E
1.1       noro      450: @end itemize
                    451:
                    452: @example
                    453: [0] ord();
1.5     ! noro      454: [x,y,z,u,v,w,p,q,r,s,t,a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,_x,_y,_z,_u,_v,
        !           455: _w,_p,_q,_r,_s,_t,_a,_b,_c,_d,_e,_f,_g,_h,_i,_j,_k,_l,_m,_n,_o,
        !           456: exp(_x),(_x)^(_y),log(_x),(_x)^(_y-1),cos(_x),sin(_x),tan(_x),
        !           457: (-_x^2+1)^(-1/2),cosh(_x),sinh(_x),tanh(_x),
        !           458: (_x^2+1)^(-1/2),(_x^2-1)^(-1/2)]
1.1       noro      459: [1] ord([dx,dy,dz,a,b,c]);
1.5     ! noro      460: [dx,dy,dz,a,b,c,x,y,z,u,v,w,p,q,r,s,t,d,e,f,g,h,i,j,k,l,m,n,o,_x,_y,
        !           461: _z,_u,_v,_w,_p,_q,_r,_s,_t,_a,_b,_c,_d,_e,_f,_g,_h,_i,_j,_k,_l,_m,_n,
        !           462: _o,exp(_x),(_x)^(_y),log(_x),(_x)^(_y-1),cos(_x),sin(_x),tan(_x),
        !           463: (-_x^2+1)^(-1/2),cosh(_x),sinh(_x),tanh(_x),
        !           464: (_x^2+1)^(-1/2),(_x^2-1)^(-1/2)]
1.1       noro      465: @end example
                    466:
1.2       noro      467: \JP @node sdiv sdivm srem sremm sqr sqrm,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    468: \EG @node sdiv sdivm srem sremm sqr sqrm,,, Polynomials and rational expressions
1.1       noro      469: @subsection @code{sdiv}, @code{sdivm}, @code{srem}, @code{sremm}, @code{sqr}, @code{sqrm}
                    470: @findex sdiv
                    471: @findex sdivm
                    472: @findex srem
                    473: @findex sremm
                    474: @findex sqr
                    475: @findex sqrm
                    476:
                    477: @table @t
                    478: @item sdiv(@var{poly1},@var{poly2}[,@var{v}])
                    479: @itemx sdivm(@var{poly1},@var{poly2},@var{mod}[,@var{v}])
1.2       noro      480: \JP :: @var{poly1} $B$r(B @var{poly2} $B$G3d$k=|;;$,:G8e$^$G<B9T$G$-$k>l9g$K>&$r5a$a$k(B.
                    481: \BEG
                    482: :: Quotient of @var{poly1} divided by @var{poly2} provided that the
                    483: division can be performed within polynomial arithmetic over the
                    484: rationals.
                    485: \E
1.1       noro      486: @item srem(@var{poly1},@var{poly2}[,@var{v}])
                    487: @item sremm(@var{poly1},@var{poly2},@var{mod}[,@var{v}])
1.2       noro      488: \JP :: @var{poly1} $B$r(B @var{poly2} $B$G3d$k=|;;$,:G8e$^$G<B9T$G$-$k>l9g$K>jM>$r5a$a$k(B.
                    489: \BEG
                    490: :: Remainder of @var{poly1} divided by @var{poly2} provided that the
                    491: division can be performed within polynomial arithmetic over the
                    492: rationals.
                    493: \E
1.1       noro      494: @item sqr(@var{poly1},@var{poly2}[,@var{v}])
                    495: @item sqrm(@var{poly1},@var{poly2},@var{mod}[,@var{v}])
1.2       noro      496: \BJP
1.1       noro      497: :: @var{poly1} $B$r(B @var{poly2} $B$G3d$k=|;;$,:G8e$^$G<B9T$G$-$k>l9g$K>&(B, $B>jM>$r(B
                    498: $B5a$a$k(B.
1.2       noro      499: \E
                    500: \BEG
                    501: :: Quotient and remainder of @var{poly1} divided by @var{poly2} provided
                    502: that the division can be performed within polynomial arithmetic over
                    503: the rationals.
                    504: \E
1.1       noro      505: @end table
                    506:
                    507: @table @var
                    508: @item return
1.2       noro      509: \JP @code{sdiv()}, @code{sdivm()}, @code{srem()}, @code{sremm()} : $BB?9`<0(B, @code{sqr()}, @code{sqrm()} : @code{[$B>&(B,$B>jM>(B]} $B$J$k%j%9%H(B
                    510: \EG @code{sdiv()}, @code{sdivm()}, @code{srem()}, @code{sremm()} : polynomial @code{sqr()}, @code{sqrm()} : a list @code{[quotient,remainder]}
1.1       noro      511: @item poly1 poly2
1.2       noro      512: \JP $BB?9`<0(B
                    513: \EG polynomial
1.1       noro      514: @item v
1.2       noro      515: \JP $BITDj85(B
                    516: \EG indeterminate
1.1       noro      517: @item mod
1.2       noro      518: \JP $BAG?t(B
                    519: \EG prime
1.1       noro      520: @end table
                    521:
                    522: @itemize @bullet
1.2       noro      523: \BJP
1.1       noro      524: @item
                    525: @var{poly1} $B$r(B @var{poly2} $B$N<gJQ?t(B @t{var}(@var{poly2})
                    526: ( $B0z?t(B @var{v} $B$,$"$k>l9g$K$O(B @var{v}) $B$K4X$9$kB?9`<0$H8+$F(B,
                    527: @var{poly2} $B$G(B, $B3d$j;;$r9T$&(B.
                    528: @item
                    529: @code{sdivm()}, @code{sremm()}, @code{sqrm()} $B$O(B GF(@var{mod}) $B>e$G7W;;$9$k(B.
                    530: @item
                    531: $BB?9`<0$N=|;;$O(B, $B<g78?t$I$&$7$N3d;;$K$h$jF@$i$l$?>&$H(B, $B<gJQ?t$NE,Ev$JQQ$N(B
                    532: $B@Q$r(B @var{poly2} $B$K3]$1$F(B, @var{poly1} $B$+$i0z$/$H$$$&A`:n$r(B
                    533: @var{poly1} $B$N<!?t$,(B @var{poly2} $B$N<!?t$h$j>.$5$/$J$k$^$G7+$jJV$7$F(B
                    534: $B9T$&(B. $B$3$NA`:n$,(B, $BB?9`<0$NHO0OFb$G9T$o$l$k$?$a$K$O(B, $B3F%9%F%C%W$K$*$$$F(B
                    535: $B<g78?t$I$&$7$N=|;;$,(B, $BB?9`<0$H$7$F$N@0=|$G$"$kI,MW$,$"$k(B. $B$3$l$,(B, $B!V=|;;(B
                    536: $B$,:G8e$^$G<B9T$G$-$k!W$3$H$N0UL#$G$"$k(B.
                    537: @item
                    538: $BE57?E*$J>l9g$H$7$F(B, @var{poly2} $B$N<g78?t$,(B, $BM-M}?t$G$"$k>l9g(B, $B$"$k$$$O(B,
                    539: @var{poly2} $B$,(B @var{poly1} $B$N0x;R$G$"$k$3$H$,$o$+$C$F$$$k>l9g$J$I(B
                    540: $B$,$"$k(B.
                    541: @item
                    542: @code{sqr()} $B$O>&$H>jM>$rF1;~$K5a$a$?$$;~$KMQ$$$k(B.
                    543: @item
                    544: $B@0?t=|;;$N>&(B, $B>jM>$O(B @code{idiv}, @code{irem} $B$rMQ$$$k(B.
                    545: @item
                    546: $B78?t$KBP$9$k>jM>1i;;$O(B @code{%} $B$rMQ$$$k(B.
1.2       noro      547: \E
                    548: \BEG
                    549: @item
                    550: Regarding @var{poly1} as an uni-variate polynomial in the main variable
                    551: of @var{poly2},
                    552: i.e. @t{var(@var{poly2})} (@var{v} if specified), @code{sdiv()} and
                    553: @code{srem()} compute
                    554: the polynomial quotient and remainder of @var{poly1} divided by @var{poly2}.
                    555: @item @code{sdivm()}, @code{sremm()}, @code{sqrm()} execute the same
                    556: operation over GF(@var{mod}).
                    557: @item
                    558: Division operation of polynomials is performed by the following steps:
                    559: (1) obtain the quotient of leading coefficients; let it be Q;
                    560: (2) remove the leading term of @var{poly1} by subtracting, from
                    561: @var{poly1}, the product of Q with some powers of main variable
                    562: and @var{poly2}; obtain a new @var{poly1};
                    563: (3) repeat the above step until the degree of @var{poly1} become smaller
                    564: than that of @var{poly2}.
                    565: For fulfillment, by operating in polynomials, of this procedure, the
                    566: divisions at step (1) in every repetition must be an exact division of
                    567: polynomials.  This is the true meaning of what we say
                    568: ``division can be performed within polynomial arithmetic
                    569: over the rationals.''
                    570: @item
                    571: There are typical cases where the division is possible:
                    572: leading coefficient of @var{poly2} is a rational number;
                    573: @var{poly2} is a factor of @var{poly1}.
                    574: @item
                    575: Use @code{sqr()} to get both the quotient and remainder at once.
                    576: @item
                    577: Use @code{idiv()}, @code{irem()} for integer quotient.
                    578: @item
                    579: For remainder operation on all integer coefficients, use @code{%}.
                    580: \E
1.1       noro      581: @end itemize
                    582:
                    583: @example
                    584: [0] sdiv((x+y+z)^3,x^2+y+a);
                    585: x+3*y+3*z
                    586: [1] srem((x+y+z)^2,x^2+y+a);
                    587: (2*y+2*z)*x+y^2+(2*z-1)*y+z^2-a
                    588: [2] X=(x+y+z)*(x-y-z)^2;
                    589: x^3+(-y-z)*x^2+(-y^2-2*z*y-z^2)*x+y^3+3*z*y^2+3*z^2*y+z^3
                    590: [3] Y=(x+y+z)^2*(x-y-z);
                    591: x^3+(y+z)*x^2+(-y^2-2*z*y-z^2)*x-y^3-3*z*y^2-3*z^2*y-z^3
                    592: [4] G=gcd(X,Y);
                    593: x^2-y^2-2*z*y-z^2
                    594: [5] sqr(X,G);
                    595: [x-y-z,0]
                    596: [6] sqr(Y,G);
                    597: [x+y+z,0]
                    598: [7] sdiv(y*x^3+x+1,y*x+1);
                    599: divsp: cannot happen
                    600: return to toplevel
                    601: @end example
                    602:
                    603: @table @t
1.2       noro      604: \JP @item $B;2>H(B
                    605: \EG @item References
1.1       noro      606: @fref{idiv irem}, @fref{%}.
                    607: @end table
                    608:
1.2       noro      609: \JP @node tdiv,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    610: \EG @node tdiv,,, Polynomials and rational expressions
1.1       noro      611: @subsection @code{tdiv}
                    612: @findex tdiv
                    613:
                    614: @table @t
                    615: @item tdiv(@var{poly1},@var{poly2})
1.2       noro      616: \JP :: @var{poly1} $B$,(B @var{poly2} $B$G3d$j@Z$l$k$+$I$&$+D4$Y$k(B.
                    617: \EG :: Tests whether @var{poly2} divides @var{poly1}.
1.1       noro      618: @end table
                    619:
                    620: @table @var
                    621: @item return
1.2       noro      622: \JP $B3d$j@Z$l$k$J$i$P>&(B, $B3d$j@Z$l$J$1$l$P(B 0
                    623: \EG Quotient if @var{poly2} divides @var{poly1}, 0 otherwise.
1.1       noro      624: @item poly1 poly2
1.2       noro      625: \JP $BB?9`<0(B
                    626: \EG polynomial
1.1       noro      627: @end table
                    628:
                    629: @itemize @bullet
1.2       noro      630: \BJP
1.1       noro      631: @item
                    632: @var{poly2} $B$,(B @var{poly1} $B$rB?9`<0$H$7$F3d$j@Z$k$+$I$&$+D4$Y$k(B.
                    633: @item
                    634: $B$"$kB?9`<0$,4{Ls0x;R$G$"$k$3$H$O$o$+$C$F$$$k$,(B, $B$=$N=EJ#EY$,$o$+$i$J$$(B
                    635: $B>l9g$K(B, @code{tdiv()} $B$r7+$jJV$78F$V$3$H$K$h$j=EJ#EY$,$o$+$k(B.
1.2       noro      636: \E
                    637: \BEG
                    638: @item
                    639: Tests whether @var{poly2} divides @var{poly1} in polynomial ring.
                    640: @item
                    641: One application of this function: Consider the case where a polynomial
                    642: is certainly an irreducible factor of the other polynomial, but
                    643: the multiplicity of the factor is unknown.  Application of @code{tdiv()}
                    644: to the polynomials repeatedly yields the multiplicity.
                    645: \E
1.1       noro      646: @end itemize
                    647:
                    648: @example
                    649: [11] Y=(x+y+z)^5*(x-y-z)^3;
1.5     ! noro      650: x^8+(2*y+2*z)*x^7+(-2*y^2-4*z*y-2*z^2)*x^6
        !           651: +(-6*y^3-18*z*y^2-18*z^2*y-6*z^3)*x^5
        !           652: +(6*y^5+30*z*y^4+60*z^2*y^3+60*z^3*y^2+30*z^4*y+6*z^5)*x^3
        !           653: +(2*y^6+12*z*y^5+30*z^2*y^4+40*z^3*y^3+30*z^4*y^2+12*z^5*y+2*z^6)*x^2
        !           654: +(-2*y^7-14*z*y^6-42*z^2*y^5-70*z^3*y^4-70*z^4*y^3-42*z^5*y^2
        !           655: -14*z^6*y-2*z^7)*x-y^8-8*z*y^7-28*z^2*y^6-56*z^3*y^5-70*z^4*y^4
        !           656: -56*z^5*y^3-28*z^6*y^2-8*z^7*y-z^8
1.1       noro      657: [12] for(I=0,F=x+y+z,T=Y; T=tdiv(T,F); I++);
                    658: [13] I;
                    659: 5
                    660: @end example
                    661:
                    662: @table @t
1.2       noro      663: \JP @item $B;2>H(B
                    664: \EG @item References
1.1       noro      665: @fref{sdiv sdivm srem sremm sqr sqrm}.
                    666: @end table
                    667:
1.2       noro      668: \JP @node %,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    669: \EG @node %,,, Polynomials and rational expressions
1.1       noro      670: @subsection @code{%}
                    671: @findex %
                    672:
                    673: @table @t
                    674: @item @var{poly} % @var{m}
1.2       noro      675: \JP :: $B@0?t$K$h$k>jM>(B
                    676: \EG :: integer remainder to all integer coefficients of the polynomial.
1.1       noro      677: @end table
                    678:
                    679: @table @var
                    680: @item return
1.2       noro      681: \JP $B@0?t$^$?$OB?9`<0(B
                    682: \EG integer or polynomial
1.1       noro      683: @item poly
1.2       noro      684: \JP $B@0?t$^$?$O@0?t78?tB?9`<0(B
                    685: \EG integer or polynomial with integer coefficients
1.1       noro      686: @item m
1.2       noro      687: \JP $B@0?t(B
                    688: \EG intger
1.1       noro      689: @end table
                    690:
                    691: @itemize @bullet
1.2       noro      692: \BJP
1.1       noro      693: @item
                    694: @var{poly} $B$N3F78?t$r(B @var{m} $B$G3d$C$?>jM>$GCV$-49$($?B?9`<0$rJV$9(B.
                    695: @item
                    696: $B7k2L$N78?t$OA4$F@5$N@0?t$H$J$k(B.
                    697: @item
                    698: @var{poly} $B$O@0?t$G$b$h$$(B. $B$3$N>l9g(B, $B7k2L$,@5$K@55,2=$5$l$k$3$H$r=|$1$P(B
                    699: @code{irem()} $B$HF1MM$KMQ$$$k$3$H$,$G$-$k(B.
                    700: @item
                    701: @var{poly} $B$N78?t(B, @var{m} $B$H$b@0?t$G$"$kI,MW$,$"$k$,(B, $B%A%'%C%/$O9T$J$o$l$J$$(B.
1.2       noro      702: \E
                    703: \BEG
                    704: @item
                    705: Returns a polynomial whose coefficients are remainders of the
                    706: coefficients of the input polynomial divided by @var{m}.
                    707: @item
                    708: The resulting coefficients are all normalized to non-negative integers.
                    709: @item
                    710: An integer is allowed for @var{poly}.  This can be used for an
                    711: alternative for @code{irem()} except that the result is normalized to
                    712: a non-negative integer.
                    713: @item
                    714: Coefficients of @var{poly} and @var{m} must all be integers, though the
                    715: type checking is not done.
                    716: \E
1.1       noro      717: @end itemize
                    718:
                    719: @example
                    720: [0] (x+2)^5 % 3;
                    721: x^5+x^4+x^3+2*x^2+2*x+2
                    722: [1] (x-2)^5 % 3;
                    723: x^5+2*x^4+x^3+x^2+2*x+1
                    724: [2] (-5) % 4;
                    725: 3
                    726: [3] irem(-5,4);
                    727: -1
                    728: @end example
                    729:
                    730: @table @t
1.2       noro      731: \JP @item $B;2>H(B
                    732: \EG @item References
1.1       noro      733: @fref{idiv irem}.
                    734: @end table
                    735:
1.2       noro      736: \JP @node subst psubst,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    737: \EG @node subst psubst,,, Polynomials and rational expressions
1.1       noro      738: @subsection @code{subst}, @code{psubst}
                    739: @findex subst
                    740: @findex psubst
                    741:
                    742: @table @t
                    743: @item subst(@var{rat}[,@var{varn},@var{ratn}]*)
                    744: @item psubst(@var{rat}[,@var{var},@var{rat}]*)
1.2       noro      745: \BJP
1.1       noro      746: :: @var{rat} $B$N(B @var{varn} $B$K(B @var{ratn} $B$rBeF~(B
1.4       noro      747: (@var{n}=1,2,... $B$G:8$+$i1&$K=g<!BeF~$9$k(B).
1.2       noro      748: \E
                    749: \BEG
                    750: :: Substitute @var{ratn} for @var{varn} in expression @var{rat}.
1.4       noro      751: (@var{n}=1,2,@dots{}.
1.2       noro      752: Substitution will be done successively from left to right
                    753: if arguments are repeated.)
                    754: \E
1.1       noro      755: @end table
                    756:
                    757: @table @var
                    758: @item return
1.2       noro      759: \JP $BM-M}<0(B
                    760: \EG rational expression
1.4       noro      761: @item rat ratn
1.2       noro      762: \JP $BM-M}<0(B
                    763: \EG rational expression
1.1       noro      764: @item varn
1.2       noro      765: \JP $BITDj85(B
                    766: \EG indeterminate
1.1       noro      767: @end table
                    768:
                    769: @itemize @bullet
1.2       noro      770: \BJP
1.1       noro      771: @item
                    772: $BM-M}<0$NFCDj$NITDj85$K(B, $BDj?t$"$k$$$OB?9`<0(B, $BM-M}<0$J$I$rBeF~$9$k$N$KMQ$$$k(B.
                    773: @item
                    774: @t{subst}(@var{rat},@var{var1},@var{rat1},@var{var2},@var{rat2},...) $B$O(B,
                    775: @t{subst}(@t{subst}(@var{rat},@var{var1},@var{rat1}),@var{var2},@var{rat2},...)
                    776: $B$HF1$80UL#$G$"$k(B.
                    777: @item
                    778: $BF~NO$N:8B&$+$i=g$KBeF~$r7+$jJV$9$?$a$K(B, $BF~NO$N=g$K$h$C$F7k2L$,JQ$o$k$3$H$,$"$k(B.
                    779: @item
                    780: @code{subst()} $B$O(B, @code{sin()} $B$J$I$NH!?t$N0z?t$KBP$7$F$bBeF~$r9T$&(B.
                    781: @code{psubst()} $B$O(B, $B$3$N$h$&$JH!?t$r0l$D$NFHN)$7$?ITDj85$H8+$J$7$F(B, $B$=(B
                    782: $B$N0z?t$K$OBeF~$O9T$o$J$$(B. (partial substitution $B$N$D$b$j(B)
                    783: @item
                    784: @b{Asir} $B$G$O(B, $BM-M}<0$NLsJ,$O<+F0E*$K$O9T$o$J$$$?$a(B,
                    785: $BM-M}<0$NBeF~$O(B, $B;W$o$L7W;;;~4V$NA}Bg$r0z$-5/$3$9>l9g$,$"$k(B.
                    786: $BM-M}<0$rBeF~$9$k>l9g$K$O(B, $BLdBj$K1~$8$?FH<+$NH!?t$r=q$$$F(B,
                    787: $B$J$k$Y$/J,Jl(B, $BJ,;R$,Bg$-$/$J$i$J$$$h$&$KG[N8$9$k$3$H$b$7$P$7$PI,MW$H$J$k(B.
                    788: @item
                    789: $BJ,?t$rBeF~$9$k>l9g$bF1MM$G$"$k(B.
1.2       noro      790: \E
                    791: \BEG
                    792: @item
                    793: Substitutes rational expressions for specified kernels in a rational
                    794: expression.
                    795: @item
1.5     ! noro      796: @t{subst}(@var{r},@var{v1},@var{r1},@var{v2},@var{r2},@dots{})
1.2       noro      797: has the same effect as
1.5     ! noro      798: @t{subst}(@t{subst}(@var{r},@var{v1},@var{r1}),@var{v2},@var{r2},@dots{}).
1.2       noro      799: @item
                    800: Note that repeated substitution is done from left to right successively.
                    801: You may get different result by changing the specification order.
                    802: @item
                    803: Ordinary @code{subst()} performs
                    804: substitution at all levels of a scalar algebraic expression creeping
                    805: into arguments of function forms recursively.
                    806: Function @code{psubst()} regards such a function form as an independent
                    807: indeterminate, and does not attempt to apply substitution to its
                    808: arguments.  (The name comes after Partial SUBSTitution.)
                    809: @item
                    810: Since @b{Asir} does not reduce common divisors of a rational expression
                    811: automatically, substitution of a rational expression to an expression
                    812: may cause unexpected increase of computation time.
                    813: Thus, it is often necessary to write a special function to meet the
                    814: individual problem so that the denominator and the numerator do not
                    815: become too large.
                    816: @item
                    817: The same applies to substitution by rational numbers.
                    818: \E
1.1       noro      819: @end itemize
                    820:
                    821: @example
                    822: [0] subst(x^3-3*y*x^2+3*y^2*x-y^3,y,2);
                    823: x^3-6*x^2+12*x-8
                    824: [1] subst(@@@@,x,-1);
                    825: -27
                    826: [2] subst(x^3-3*y*x^2+3*y^2*x-y^3,y,2,x,-1);
                    827: -27
                    828: [3] subst(x*y^3,x,y,y,x);
                    829: x^4
                    830: [4] subst(x*y^3,y,x,x,y);
                    831: y^4
                    832: [5] subst(x*y^3,x,t,y,x,t,y);
                    833: y*x^3
                    834: [6] subst(x*sin(x),x,t);
                    835: sint(t)*t
                    836: [7] psubst(x*sin(x),x,t);
                    837: sin(x)*t
                    838: @end example
                    839:
1.2       noro      840: \JP @node diff,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    841: \EG @node diff,,, Polynomials and rational expressions
1.1       noro      842: @subsection @code{diff}
                    843: @findex diff
                    844:
                    845: @table @t
                    846: @item diff(@var{rat}[,@var{varn}]*)
                    847: @item diff(@var{rat},@var{varlist})
1.2       noro      848: \JP :: @var{rat} $B$r(B @var{varn} $B$"$k$$$O(B @var{varlist} $B$NCf$NJQ?t$G=g<!HyJ,$9$k(B.
                    849: \BEG
                    850: :: Differentiate @var{rat} successively by @var{var}'s for the first
                    851: form, or by variables in @var{varlist} for the second form.
                    852: \E
1.1       noro      853: @end table
                    854:
                    855: @table @var
                    856: @item return
1.2       noro      857: \JP $B<0(B
                    858: \EG expression
1.1       noro      859: @item rat
1.2       noro      860: \JP $BM-M}<0(B ($B=iEyH!?t$r4^$s$G$b$h$$(B)
                    861: \EG rational expression which contains elementary functions.
1.1       noro      862: @item varn
1.2       noro      863: \JP $BITDj85(B
                    864: \EG indeterminate
1.1       noro      865: @item varlist
1.2       noro      866: \JP $BITDj85$N%j%9%H(B
                    867: \EG list of indeterminates
1.1       noro      868: @end table
                    869:
                    870: @itemize @bullet
1.2       noro      871: \BJP
1.1       noro      872: @item
                    873: $BM?$($i$l$?=iEyH!?t$r(B @var{varn} $B$"$k$$$O(B @var{varlist} $B$NCf$NJQ?t$G(B
                    874: $B=g<!HyJ,$9$k(B.
                    875: @item
                    876: $B:8B&$NITDj85$h$j(B, $B=g$KHyJ,$7$F$$$/(B. $B$D$^$j(B, @t{diff}(@var{rat},@t{x,y}) $B$O(B,
                    877: @t{diff}(@t{diff}(@var{rat},@t{x}),@t{y}) $B$HF1$8$G$"$k(B.
1.2       noro      878: \E
                    879: \BEG
                    880: @item
                    881: Differentiate @var{rat} successively by @var{var}'s for the first
                    882: form, or by variables in @var{varlist} for the second form.
                    883: @item
                    884: differentiation is performed by the specified indeterminates (variables)
                    885: from left to right.
                    886: @t{diff}(@var{rat},@t{x,y}) is the same as
                    887: @t{diff}(@t{diff}(@var{rat},@t{x}),@t{y}).
                    888: \E
1.1       noro      889: @end itemize
                    890:
                    891: @example
                    892: [0] diff((x+2*y)^2,x);
                    893: 2*x+4*y
                    894: [1] diff((x+2*y)^2,x,y);
                    895: 4
                    896: [2] diff(x/sin(log(x)+1),x);
                    897: (sin(log(x)+1)-cos(log(x)+1))/(sin(log(x)+1)^2)
                    898: [3] diff(sin(x),[x,x,x,x]);
                    899: sin(x)
                    900: @end example
                    901:
1.2       noro      902: \JP @node res,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    903: \EG @node res,,, Polynomials and rational expressions
1.1       noro      904: @subsection @code{res}
                    905: @findex res
                    906:
                    907: @table @t
                    908: @item res(@var{var},@var{poly1},@var{poly2}[,@var{mod}])
1.2       noro      909: \JP :: @var{var} $B$K4X$9$k(B @var{poly1} $B$H(B @var{poly2} $B$N=*7k<0(B.
                    910: \EG :: Resultant of @var{poly1} and @var{poly2} with respect to @var{var}.
1.1       noro      911: @end table
                    912:
                    913: @table @var
                    914: @item return
1.2       noro      915: \JP $BB?9`<0(B
                    916: \EG polynomial
1.1       noro      917: @item var
1.2       noro      918: \JP $BITDj85(B
                    919: \EG indeterminate
1.4       noro      920: @item poly1 poly2
1.2       noro      921: \JP $BB?9`<0(B
                    922: \EG polynomial
1.1       noro      923: @item mod
1.2       noro      924: \JP $BAG?t(B
                    925: \EG prime
1.1       noro      926: @end table
                    927:
                    928: @itemize @bullet
1.2       noro      929: \BJP
1.1       noro      930: @item
                    931: $BFs$D$NB?9`<0(B @var{poly1} $B$H(B @var{poly2} $B$N(B, $BJQ?t(B @var{var} $B$K4X$9$k(B
                    932: $B=*7k<0$r5a$a$k(B.
                    933: @item
                    934: $BItJ,=*7k<0%"%k%4%j%:%`$K$h$k(B.
                    935: @item
                    936: $B0z?t(B @var{mod} $B$,$"$k;~(B, GF(@var{mod}) $B>e$G$N7W;;$r9T$&(B.
1.2       noro      937: \E
                    938: \BEG
                    939: @item
                    940: Resultant of two polynomials @var{poly1} and @var{poly2}
                    941: with respect to @var{var}.
                    942: @item
                    943: Sub-resultant algorithm is used to compute the resultant.
                    944: @item
                    945: The computation is done over GF(@var{mod}) if @var{mod} is specified.
                    946: \E
1.1       noro      947: @end itemize
                    948:
                    949: @example
                    950: [0] res(t,(t^3+1)*x+1,(t^3+1)*y+t);
                    951: -x^3-x^2-y^3
                    952: @end example
                    953:
1.2       noro      954: \JP @node fctr sqfr,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                    955: \EG @node fctr sqfr,,, Polynomials and rational expressions
1.1       noro      956: @subsection @code{fctr}, @code{sqfr}
                    957: @findex fctr
                    958: @findex sqfr
                    959:
                    960: @table @t
                    961: @item fctr(@var{poly})
1.2       noro      962: \JP :: @var{poly} $B$r4{Ls0x;R$KJ,2r$9$k(B.
                    963: \EG :: Factorize polynomial @var{poly} over the rationals.
1.1       noro      964: @item sqfr(@var{poly})
1.2       noro      965: \JP :: @var{poly} $B$rL5J?J}J,2r$9$k(B.
                    966: \EG :: Gets a square-free factorization of polynomial @var{poly}.
1.1       noro      967: @end table
                    968:
                    969: @table @var
                    970: @item return
1.2       noro      971: \JP $B%j%9%H(B
                    972: \EG list
1.1       noro      973: @item poly
1.2       noro      974: \JP $BM-M}?t78?t$NB?9`<0(B
                    975: \EG polynomial with rational coefficients
1.1       noro      976: @end table
                    977:
                    978: @itemize @bullet
1.2       noro      979: \BJP
1.1       noro      980: @item
                    981: $BM-M}?t78?t$NB?9`<0(B @var{poly} $B$r0x?tJ,2r$9$k(B. @code{fctr()} $B$O4{Ls0x;RJ,2r(B,
                    982: @code{sqfr()} $B$OL5J?J}0x;RJ,2r(B.
                    983: @item
                    984: $B7k2L$O(B [[@b{$B?t78?t(B},1],[@b{$B0x;R(B},@b{$B=EJ#EY(B}],...] $B$J$k%j%9%H(B.
                    985: @item
                    986: @b{$B?t78?t(B} $B$H(B $BA4$F$N(B @b{$B0x;R(B}^@b{$B=EJ#EY(B} $B$N@Q$,(B @var{poly} $B$HEy$7$$(B.
                    987: @item
                    988: @b{$B?t78?t(B} $B$O(B, (@var{poly}/@b{$B?t78?t(B}) $B$,(B, $B@0?t78?t$G(B, $B78?t$N(B GCD $B$,(B 1 $B$H$J$k(B
                    989: $B$h$&$JB?9`<0$K$J$k$h$&$KA*$P$l$F$$$k(B. (@code{ptozp()} $B;2>H(B)
1.2       noro      990: \E
                    991: \BEG
                    992: @item
                    993: Factorizes polynomial @var{poly} over the rationals.
                    994: @code{fctr()} for irreducible factorization;
                    995: @code{sqfr()} for square-free factorization.
                    996: @item
                    997: The result is represented by a list, whose elements are a pair
                    998: represented as
                    999:
                   1000: [[@b{num},1],[@b{factor},@b{multiplicity}],...].
                   1001: @item
                   1002: Products of all @b{factor}^@b{multiplicity} and @b{num} is equal to
                   1003: @var{poly}.
                   1004: @item
                   1005: The number @b{num} is determined so that (@var{poly}/@b{num}) is an
                   1006: integral polynomial and its content (GCD of all coefficients) is 1.
                   1007: (@xref{ptozp}.)
                   1008: \E
1.1       noro     1009: @end itemize
                   1010:
                   1011: @example
                   1012: [0] fctr(x^10-1);
                   1013: [[1,1],[x-1,1],[x+1,1],[x^4+x^3+x^2+x+1,1],[x^4-x^3+x^2-x+1,1]]
                   1014: [1] fctr(x^3+y^3+(z/3)^3-x*y*z);
                   1015: [[1/27,1],[9*x^2+(-9*y-3*z)*x+9*y^2-3*z*y+z^2,1],[3*x+3*y+z,1]]
                   1016: [2] A=(a+b+c+d)^2;
                   1017: a^2+(2*b+2*c+2*d)*a+b^2+(2*c+2*d)*b+c^2+2*d*c+d^2
                   1018: [3] fctr(A);
                   1019: [[1,1],[a+b+c+d,2]]
                   1020: [4] A=(x+1)*(x^2-y^2)^2;
                   1021: x^5+x^4-2*y^2*x^3-2*y^2*x^2+y^4*x+y^4
                   1022: [5] sqfr(A);
                   1023: [[1,1],[x+1,1],[-x^2+y^2,2]]
                   1024: [6] fctr(A);
                   1025: [[1,1],[x+1,1],[-x-y,2],[x-y,2]]
                   1026: @end example
                   1027:
                   1028: @table @t
1.2       noro     1029: \JP @item $B;2>H(B
                   1030: \EG @item References
1.1       noro     1031: @fref{ufctrhint}.
                   1032: @end table
                   1033:
1.2       noro     1034: \JP @node ufctrhint,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                   1035: \EG @node ufctrhint,,, Polynomials and rational expressions
1.1       noro     1036: @subsection @code{ufctrhint}
                   1037: @findex ufctrhint
                   1038:
                   1039: @table @t
                   1040: @item ufctrhint(@var{poly},@var{hint})
1.2       noro     1041: \JP :: $B<!?t>pJs$rMQ$$$?(B 1 $BJQ?tB?9`<0$N0x?tJ,2r(B
                   1042: \BEG
                   1043: :: Factorizes uni-variate polynomial @var{poly} over the rational number
                   1044: field when the degrees of its factors are known to be some integer
                   1045: multiples of @var{hint}.
                   1046: \E
1.1       noro     1047: @end table
                   1048:
                   1049: @table @var
                   1050: @item return
1.2       noro     1051: \JP $B%j%9%H(B
                   1052: \EG list
1.1       noro     1053: @item poly
1.2       noro     1054: \JP $BM-M}?t78?t$N(B 1 $BJQ?tB?9`<0(B
                   1055: \EG uni-variate polynomial with rational coefficients
1.1       noro     1056: @item hint
1.2       noro     1057: \JP $B<+A3?t(B
                   1058: \EG non-negative integer
1.1       noro     1059: @end table
                   1060:
                   1061: @itemize @bullet
1.2       noro     1062: \BJP
1.1       noro     1063: @item
                   1064: $B3F4{Ls0x;R$N<!?t$,(B @var{hint} $B$NG\?t$G$"$k$3$H$,$o$+$C$F$$$k>l9g$K(B
                   1065: @var{poly} $B$N4{Ls0x;RJ,2r$r(B @code{fctr()} $B$h$j8zN(NI$/9T$&(B.
                   1066: @var{poly} $B$,(B, @var{d} $B<!$N3HBgBN>e$K$*$1$k(B
1.3       noro     1067: $B$"$kB?9`<0$N%N%k%`(B (@ref{$BBe?tE*?t$K4X$9$k1i;;(B}) $B$GL5J?J}$G$"$k>l9g(B,
1.1       noro     1068: $B3F4{Ls0x;R$N<!?t$O(B @var{d} $B$NG\?t$H$J$k(B. $B$3$N$h$&$J>l9g$K(B
                   1069: $BMQ$$$i$l$k(B.
1.2       noro     1070: \E
                   1071: \BEG
                   1072: @item
                   1073: By any reason, if the degree of all the irreducible factors of @var{poly}
                   1074: is known to be some multiples of @var{hint}, factors can be computed
                   1075: more efficiently by the knowledge than @code{fctr()}.
                   1076: @item
                   1077: When @var{hint} is 1, @code{ufctrhint()} is the same as @code{fctr()} for
                   1078: uni-variate polynomials.
                   1079: An typical application where @code{ufctrhint()} is effective:
1.3       noro     1080: Consider the case where @var{poly} is a norm (@ref{Algebraic numbers})
1.2       noro     1081: of a certain polynomial over an extension field with its extension
                   1082: degree @var{d}, and it is square free;  Then, every irreducible factor
                   1083: has a degree that is a multiple of @var{d}.
                   1084: \E
1.1       noro     1085: @end itemize
                   1086:
                   1087: @example
                   1088: [10] A=t^9-15*t^6-87*t^3-125;
                   1089: t^9-15*t^6-87*t^3-125
                   1090: 0msec
                   1091: [11] N=res(t,subst(A,t,x-2*t),A);
1.5     ! noro     1092: -x^81+1215*x^78-567405*x^75+139519665*x^72-19360343142*x^69
        !          1093: +1720634125410*x^66-88249977024390*x^63-4856095669551930*x^60
        !          1094: +1999385245240571421*x^57-15579689952590251515*x^54
        !          1095: +15956967531741971462865*x^51
1.1       noro     1096: ...
                   1097: +140395588720353973535526123612661444550659875*x^6
                   1098: +10122324287343155430042768923500799484375*x^3
                   1099: +139262743444407310133459021182733314453125
                   1100: 980msec + gc : 250msec
                   1101: [12] sqfr(N);
                   1102: [[-1,1],[x^81-1215*x^78+567405*x^75-139519665*x^72+19360343142*x^69
                   1103: -1720634125410*x^66+88249977024390*x^63+4856095669551930*x^60
                   1104: -1999385245240571421*x^57+15579689952590251515*x^54
                   1105: ...
                   1106: -10122324287343155430042768923500799484375*x^3
                   1107: -139262743444407310133459021182733314453125,1]]
                   1108: 20msec
                   1109: [13] fctr(N);
                   1110: [[-1,1],[x^9-405*x^6-63423*x^3-2460375,1],
                   1111: [x^18-486*x^15+98739*x^12-9316620*x^9+945468531*x^6-12368049246*x^3
                   1112: +296607516309,1],[x^18-8667*x^12+19842651*x^6+19683,1],
1.5     ! noro     1113: [x^18-324*x^15+44469*x^12-1180980*x^9+427455711*x^6+2793253896*x^3
        !          1114: +31524548679,1],
1.1       noro     1115: [x^18+10773*x^12+2784051*x^6+307546875,1]]
                   1116: 167.050sec + gc : 1.890sec
                   1117: [14] ufctrhint(N,9);
                   1118: [[-1,1],[x^9-405*x^6-63423*x^3-2460375,1],
                   1119: [x^18-486*x^15+98739*x^12-9316620*x^9+945468531*x^6-12368049246*x^3
                   1120: +296607516309,1],[x^18-8667*x^12+19842651*x^6+19683,1],
1.5     ! noro     1121: [x^18-324*x^15+44469*x^12-1180980*x^9+427455711*x^6+2793253896*x^3
        !          1122: +31524548679,1],
1.1       noro     1123: [x^18+10773*x^12+2784051*x^6+307546875,1]]
                   1124: 119.340sec + gc : 1.300sec
                   1125: @end example
                   1126:
                   1127: @table @t
1.2       noro     1128: \JP @item $B;2>H(B
                   1129: \EG @item References
1.1       noro     1130: @fref{fctr sqfr}.
                   1131: @end table
                   1132:
1.2       noro     1133: \JP @node modfctr,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                   1134: \EG @node modfctr,,, Polynomials and rational expressions
1.1       noro     1135: @subsection @code{modfctr}
                   1136: @findex modfctr
                   1137:
                   1138: @table @t
                   1139: @item modfctr(@var{poly},@var{mod})
1.5     ! noro     1140: \JP :: $BM-8BBN>e$G$NB?9`<0$N0x?tJ,2r(B
        !          1141: \EG :: Factorizer over small finite fields
1.1       noro     1142: @end table
                   1143:
                   1144: @table @var
                   1145: @item return
1.2       noro     1146: \JP $B%j%9%H(B
                   1147: \EG list
1.1       noro     1148: @item poly
1.5     ! noro     1149: \JP $B@0?t78?t$NB?9`<0(B
        !          1150: \EG Polynomial with integer coefficients
1.1       noro     1151: @item mod
1.2       noro     1152: \JP $B<+A3?t(B
                   1153: \EG non-negative integer
1.1       noro     1154: @end table
                   1155:
                   1156: @itemize @bullet
1.2       noro     1157: \BJP
1.1       noro     1158: @item
1.5     ! noro     1159: 2^29 $BL$K~$N<+A3?t(B @var{mod} $B$rI8?t$H$9$kAGBN>e$GB?9`<0(B
1.1       noro     1160: @var{poly} $B$r4{Ls0x;R$KJ,2r$9$k(B.
                   1161: @item
                   1162: $B7k2L$O(B [[@b{$B?t78?t(B},1],[@b{$B0x;R(B},@b{$B=EJ#EY(B}],...] $B$J$k%j%9%H(B.
                   1163: @item
                   1164: @b{$B?t78?t(B} $B$H(B $BA4$F$N(B @b{$B0x;R(B}^@b{$B=EJ#EY(B} $B$N@Q$,(B @var{poly} $B$HEy$7$$(B.
1.2       noro     1165: @item
                   1166: $BBg$-$J0L?t$r;}$DM-8BBN>e$N0x?tJ,2r$K$O(B @code{fctr_ff} $B$rMQ$$$k(B.
                   1167: (@ref{$BM-8BBN$K4X$9$k1i;;(B},@pxref{fctr_ff}).
                   1168: \E
                   1169: \BEG
                   1170: @item
1.5     ! noro     1171: This function factorizes a polynomial @var{poly} over
1.2       noro     1172: the finite prime field of characteristic @var{mod}, where
1.5     ! noro     1173: @var{mod} must be smaller than 2^29.
1.2       noro     1174: @item
                   1175: The result is represented by a list, whose elements are a pair
                   1176: represented as
                   1177:
                   1178: [[@b{num},1],[@b{factor},@b{multiplicity}],...].
                   1179: @item
                   1180: Products of all @b{factor}^@b{multiplicity} and @b{num} is equal to
                   1181: @var{poly}.
                   1182: @item
                   1183: To factorize polynomials over large finite fields, use
                   1184: @code{fctr_ff} (@pxref{Finite fields},@ref{fctr_ff}).
                   1185: \E
1.1       noro     1186: @end itemize
                   1187:
                   1188: @example
                   1189: [0] modfctr(x^10+x^2+1,2147483647);
                   1190: [[1,1],[x+1513477736,1],[x+2055628767,1],[x+91854880,1],
                   1191: [x+634005911,1],[x+1513477735,1],[x+634005912,1],
                   1192: [x^4+1759639395*x^2+2045307031,1]]
1.5     ! noro     1193: [1] modfctr(2*x^6+(y^2+z*y)*x^4+2*z*y^3*x^2+(2*z^2*y^2+z^3*y)*x+z^4,3);
        !          1194: [[2,1],[2*x^3+z*y*x+z^2,1],[2*x^3+y^2*x+2*z^2,1]]
1.1       noro     1195: @end example
                   1196:
                   1197: @table @t
1.2       noro     1198: \JP @item $B;2>H(B
                   1199: \EG @item References
1.1       noro     1200: @fref{fctr sqfr}.
                   1201: @end table
                   1202:
1.2       noro     1203: \JP @node ptozp,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                   1204: \EG @node ptozp,,, Polynomials and rational expressions
1.1       noro     1205: @subsection @code{ptozp}
                   1206: @findex ptozp
                   1207:
                   1208: @table @t
                   1209: @item ptozp(@var{poly})
1.2       noro     1210: \JP :: @var{poly} $B$rM-M}?tG\$7$F@0?t78?tB?9`<0$K$9$k(B.
                   1211: \BEG
                   1212: :: Converts a polynomial @var{poly} with rational coefficients into
                   1213: an integral polynomial such that GCD of all its coefficients is 1.
                   1214: \E
1.1       noro     1215: @end table
                   1216:
                   1217: @table @var
                   1218: @item return
1.2       noro     1219: \JP $BB?9`<0(B
                   1220: \EG polynomial
1.1       noro     1221: @item poly
1.2       noro     1222: \JP $BB?9`<0(B
                   1223: \EG polynomial
1.1       noro     1224: @end table
                   1225:
                   1226: @itemize @bullet
1.2       noro     1227: \BJP
1.1       noro     1228: @item
                   1229: $BM?$($i$l$?B?9`<0(B @var{poly} $B$KE,Ev$JM-M}?t$r3]$1$F(B, $B@0?t78?t$+$D(B
                   1230: $B78?t$N(B GCD $B$,(B 1 $B$K$J$k$h$&$K$9$k(B.
                   1231: @item
                   1232: $BJ,?t$N;MB'1i;;$O(B, $B@0?t$N1i;;$KHf3S$7$FCY$$$?$a(B, $B<o!9$NB?9`<01i;;(B
                   1233: $B$NA0$K(B, $BB?9`<0$r@0?t78?t$K$7$F$*$/$3$H$,K>$^$7$$(B.
                   1234: @item
                   1235: $BM-M}<0$rLsJ,$9$k(B @code{red()} $B$GJ,?t78?tM-M}<0$rLsJ,$7$F$b(B,
                   1236: $BJ,;RB?9`<0$N78?t$OM-M}?t$N$^$^$G$"$j(B, $BM-M}<0$NJ,;R$r5a$a$k(B
                   1237: @code{nm()} $B$G$O(B, $BJ,?t78?tB?9`<0$O(B, $BJ,?t78?t$N$^$^$N7A$G=PNO$5$l$k$?$a(B,
                   1238: $BD>$A$K@0?t78?tB?9`<0$rF@$k;v$O=PMh$J$$(B.
1.2       noro     1239: \E
                   1240: \BEG
                   1241: @item
                   1242: Converts the given polynomial by multiplying some rational number
                   1243: into an integral polynomial such that GCD of all its coefficients is 1.
                   1244: @item
                   1245: In general, operations on polynomials can be
                   1246: performed faster for integer coefficients than for rational number
                   1247: coefficients.  Therefore, this function is conveniently used to improve
                   1248: efficiency.
                   1249: @item
                   1250: Function @code{red} does not convert rational coefficients of the
                   1251: numerator.
                   1252: You cannot obtain an integral polynomial by direct use of the function
                   1253: @code{nm()}.  The function @code{nm()} returns the numerator of its
                   1254: argument, and a polynomial with rational coefficients is
                   1255: the numerator of itself and will be returned as it is.
                   1256: \E
1.1       noro     1257: @end itemize
                   1258:
                   1259: @example
                   1260: [0] ptozp(2*x+5/3);
                   1261: 6*x+5
                   1262: [1] nm(2*x+5/3);
                   1263: 2*x+5/3
                   1264: @end example
                   1265:
                   1266: @table @t
1.2       noro     1267: \JP @item $B;2>H(B
                   1268: \EG @item References
1.1       noro     1269: @fref{nm dn}.
                   1270: @end table
                   1271:
1.2       noro     1272: \JP @node prim cont,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                   1273: \EG @node prim cont,,, Polynomials and rational expressions
1.1       noro     1274: @subsection @code{prim}, @code{cont}
                   1275: @findex prim
                   1276:
                   1277: @table @t
                   1278: @item prim(@var{poly}[,@var{v}])
1.2       noro     1279: \JP :: @var{poly} $B$N86;OE*ItJ,(B (primitive part).
                   1280: \EG :: Primitive part of @var{poly}.
1.1       noro     1281: @item cont(@var{poly}[,@var{v}])
1.2       noro     1282: \JP :: @var{poly} $B$NMFNL(B (content).
                   1283: \EG :: Content of @var{poly}.
1.1       noro     1284: @end table
                   1285:
                   1286: @table @var
                   1287: @item return poly
1.2       noro     1288: \JP $BM-M}?t78?tB?9`<0(B
                   1289: \EG polynomial over the rationals
1.1       noro     1290: @item v
1.2       noro     1291: \JP $BITDj85(B
                   1292: \EG indeterminate
1.1       noro     1293: @end table
                   1294:
                   1295: @itemize @bullet
1.2       noro     1296: \BJP
1.1       noro     1297: @item
                   1298: @var{poly} $B$N<gJQ?t(B ($B0z?t(B @var{v} $B$,$"$k>l9g$K$O(B @var{v})
                   1299: $B$K4X$9$k86;OE*ItJ,(B, $BMFNL$r5a$a$k(B.
1.2       noro     1300: \E
                   1301: \BEG
                   1302: @item
                   1303: The primitive part and the content of a polynomial @var{poly}
                   1304: with respect to its main variable (@var{v} if specified).
                   1305: \E
1.1       noro     1306: @end itemize
                   1307:
                   1308: @example
                   1309: [0] E=(y-z)*(x+y)*(x-z)*(2*x-y);
                   1310: (2*y-2*z)*x^3+(y^2-3*z*y+2*z^2)*x^2+(-y^3+z^2*y)*x+z*y^3-z^2*y^2
                   1311: [1] prim(E);
                   1312: 2*x^3+(y-2*z)*x^2+(-y^2-z*y)*x+z*y^2
                   1313: [2] cont(E);
                   1314: y-z
                   1315: [3] prim(E,z);
                   1316: (y-z)*x-z*y+z^2
                   1317: @end example
                   1318:
                   1319: @table @t
1.2       noro     1320: \JP @item $B;2>H(B
                   1321: \EG @item References
1.1       noro     1322: @fref{var}, @fref{ord}.
                   1323: @end table
                   1324:
1.2       noro     1325: \JP @node gcd gcdz,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                   1326: \EG @node gcd gcdz,,, Polynomials and rational expressions
1.1       noro     1327: @subsection @code{gcd}, @code{gcdz}
                   1328: @findex gcd
                   1329:
                   1330: @table @t
                   1331: @item gcd(@var{poly1},@var{poly2}[,@var{mod}])
                   1332: @item gcdz(@var{poly1},@var{poly2})
1.2       noro     1333: \JP :: @var{poly1} $B$H(B @var{poly2} $B$N(B gcd.
                   1334: \EG :: The polynomial greatest common divisor of @var{poly1} and @var{poly2}.
1.1       noro     1335: @end table
                   1336:
                   1337: @table @var
                   1338: @item return
1.2       noro     1339: \JP $BB?9`<0(B
                   1340: \EG polynomial
1.4       noro     1341: @item poly1 poly2
1.2       noro     1342: \JP $BB?9`<0(B
                   1343: \EG polynomial
1.1       noro     1344: @item mod
1.2       noro     1345: \JP $BAG?t(B
                   1346: \EG prime
1.1       noro     1347: @end table
                   1348:
                   1349: @itemize @bullet
1.2       noro     1350: \BJP
1.1       noro     1351: @item
                   1352: $BFs$D$NB?9`<0$N:GBg8xLs<0(B (GCD) $B$r5a$a$k(B.
                   1353: @item
                   1354: @code{gcd()} $B$OM-M}?tBN>e$NB?9`<0$H$7$F$N(B GCD $B$rJV$9(B.
                   1355: $B$9$J$o$A(B, $B7k2L$O@0?t78?t$G(B, $B$+$D78?t$N(B GCD
                   1356: $B$,(B 1 $B$K$J$k$h$&$JB?9`<0(B, $B$^$?$O(B, $B8_$$$KAG$N>l9g$O(B 1 $B$rJV$9(B.
                   1357: @item
                   1358: @code{gcdz()} $B$O(B @var{poly1}, @var{poly2} $B$H$b$K@0?t78?t$N>l9g$K(B,
                   1359: $B@0?t4D>e$NB?9`<0$H$7$F$N(B GCD $B$rJV$9(B.
                   1360: $B$9$J$o$A(B, @code{gcd()} $B$NCM$K(B, $B78?tA4BN$N@0?t(B GCD$B$NCM$r3]$1$?$b$N$rJV$9(B.
                   1361: @item
                   1362: $B0z?t(B @var{mod} $B$,$"$k;~(B, @code{gcd()} $B$O(B GF(@var{mod}) $B>e$G$N(B GCD $B$rJV$9(B.
                   1363: @item
                   1364: @code{gcd()}, @code{gcdz()} Extended Zassenhaus $B%"%k%4%j%:%`$K$h$k(B.
                   1365: $BM-8BBN>e$N(B GCD $B$O(B PRS $B%"%k%4%j%:%`$K$h$C$F$$$k$?$a(B, $BBg$-$JLdBj(B,
                   1366: GCD $B$,(B 1 $B$N>l9g$J$I$K$*$$$F8zN($,0-$$(B.
1.2       noro     1367: \E
                   1368: \BEG
                   1369: @item
                   1370: Functions @code{gcd()} and @code{gcdz()} return the greatest common divisor
                   1371: (GCD) of the given two polynomials.
                   1372: @item
                   1373: Function @code{gcd()} returns an integral polynomial GCD over the
                   1374: rational number field.  The coefficients are normalized such that
                   1375: their GCD is 1.  It returns 1 in case that the given polynomials are
                   1376: mutually prime.
                   1377: @item
                   1378: Function @code{gcdz()} works for arguments of integral polynomials,
                   1379: and returns a polynomial GCD over the integer ring, that is,
                   1380: it returns @code{gcd()} multiplied by the contents of all coefficients
                   1381: of the two input polynomials.
                   1382: @item
                   1383: @code{gcd()} computes the GCD over GF(@var{mod}) if @var{mod} is specified.
                   1384: @item
                   1385: Polynomial GCD is computed by an improved algorithm based
                   1386: on Extended Zassenhaus algorithm.
                   1387: @item
                   1388: GCD over a finite field is computed by PRS algorithm and it may not be
                   1389: efficient for large inputs and co-prime inputs.
                   1390: \E
1.1       noro     1391: @end itemize
                   1392:
                   1393: @example
                   1394: [0] gcd(12*(x^2+2*x+1)^2,18*(x^2+(y+1)*x+y)^3);
                   1395: x^3+3*x^2+3*x+1
                   1396: [1] gcdz(12*(x^2+2*x+1)^2,18*(x^2+(y+1)*x+y)^3);
                   1397: 6*x^3+18*x^2+18*x+6
                   1398: [2] gcd((x+y)*(x-y)^2,(x+y)^2*(x-y));
                   1399: x^2-y^2
                   1400: [3] gcd((x+y)*(x-y)^2,(x+y)^2*(x-y),2);
                   1401: x^3+y*x^2+y^2*x+y^3
                   1402: @end example
                   1403:
                   1404: @table @t
1.2       noro     1405: \JP @item $B;2>H(B
                   1406: \EG @item References
1.1       noro     1407: @fref{igcd igcdcntl}.
                   1408: @end table
                   1409:
1.2       noro     1410: \JP @node red,,, $BB?9`<0$*$h$SM-M}<0$N1i;;(B
                   1411: \EG @node red,,, Polynomials and rational expressions
1.1       noro     1412: @subsection @code{red}
                   1413: @findex red
                   1414:
                   1415: @table @t
                   1416: @item red(@var{rat})
1.2       noro     1417: \JP :: @var{rat} $B$rLsJ,$7$?$b$N(B.
                   1418: \EG :: Reduced form of @var{rat} by canceling common divisors.
1.1       noro     1419: @end table
                   1420:
                   1421: @table @var
                   1422: @item return
1.2       noro     1423: \JP $BM-M}<0(B
                   1424: \EG rational expression
1.1       noro     1425: @item rat
1.2       noro     1426: \JP $BM-M}<0(B
                   1427: \EG rational expression
1.1       noro     1428: @end table
                   1429:
                   1430: @itemize @bullet
1.2       noro     1431: \BJP
1.1       noro     1432: @item
                   1433: @b{Asir} $B$OM-M}?t$NLsJ,$r>o$K<+F0E*$K9T$&(B.
                   1434: $B$7$+$7(B, $BM-M}<0$K$D$$$F$ODLJ,$O9T$&$,(B,
                   1435: $BLsJ,$O%f!<%6!<$,;XDj$7$J$$8B$j9T$o$J$$(B.
                   1436: $B$3$NLsJ,$r9T$&%3%^%s%I$,(B @t{red} $B$G$"$k(B.
                   1437: @item
                   1438: EZGCD $B$K$h$j(B @var{rat} $B$NJ,;R(B, $BJ,Jl$rLsJ,$9$k(B.
                   1439: @item
                   1440: $B=PNO$5$l$kM-M}<0$NJ,Jl$NB?9`<0$O(B, $B3F78?t$N(B GCD $B$,(B 1 $B$N(B
                   1441: $B@0?t78?tB?9`<0$G$"$k(B.
                   1442: $BJ,;R$K$D$$$F$O@0?t78?tB?9`<0$H$J$k$H$O8B$i$J$$(B.
                   1443: @item
                   1444: GCD $B$OBgJQ=E$$1i;;$J$N$G(B, $BB>$NJ}K!$G=|$1$k6&DL0x;R$O2DG=$J8B$j=|$/$N$,(B
                   1445: $BK>$^$7$$(B. $B$^$?(B, $BJ,Jl(B, $BJ,;R$,Bg$-$/$J$C$F$+$i$N$3$NH!?t$N8F$S=P$7$O(B,
                   1446: $BHs>o$K;~4V$,3]$+$k>l9g$,B?$$(B. $BM-M}<01i;;$r9T$&>l9g$O(B, $B$"$kDxEY(B
                   1447: $BIQHK$K(B, $BLsJ,$r9T$&I,MW$,$"$k(B.
1.2       noro     1448: \E
                   1449: \BEG
                   1450: @item
                   1451: @b{Asir} automatically performs cancellation of common divisors of rational numb
                   1452: ers.
                   1453: But, without an explicit command, it does not cancel common polynomial divisors
                   1454: of rational expressions.
                   1455: (Reduction of rational expressions to a common denominator will be always done.)
                   1456: Use command @t{red()} to perform this cancellation.
                   1457: @item
                   1458: Cancel the common divisors of the numerator and the denominator of
                   1459: a rational expression @var{rat} by computing their GCD.
                   1460: @item
                   1461: The denominator polynomial of the result is an integral polynomial
                   1462: which has no common divisors in its coefficients,
                   1463: while the numerator may have rational coefficients.
                   1464: @item
                   1465: Since GCD computation is a very hard operation, it is desirable to
                   1466: detect and remove by any means common divisors as far as possible.
                   1467: Furthermore, a call to this function after swelling of the denominator
                   1468: and the numerator shall usually take a very long time.  Therefore,
                   1469: often, to some extent, reduction of common divisors is inevitable for
                   1470: operations of rational expressions.
                   1471: \E
1.1       noro     1472: @end itemize
                   1473:
                   1474: @example
                   1475: [0] (x^3-1)/(x-1);
                   1476: (x^3-1)/(x-1)
                   1477: [1] red((x^3-1)/(x-1));
                   1478: x^2+x+1
                   1479: [2] red((x^3+y^3+z^3-3*x*y*z)/(x+y+z));
                   1480: x^2+(-y-z)*x+y^2-z*y+z^2
                   1481: [3] red((3*x*y)/(12*x^2+21*y^3*x));
                   1482: (y)/(4*x+7*y^3)
                   1483: [4] red((3/4*x^2+5/6*x)/(2*y*x+4/3*x));
                   1484: (9/8*x+5/4)/(3*y+2)
                   1485: @end example
                   1486:
                   1487: @table @t
1.2       noro     1488: \JP @item $B;2>H(B
                   1489: \EG @item References
1.1       noro     1490: @fref{nm dn}, @fref{gcd gcdz}, @fref{ptozp}.
                   1491: @end table
                   1492:

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