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

Annotation of OpenXM/src/asir-doc/parts/groebner.texi, Revision 1.18

1.18    ! noro        1: @comment $OpenXM: OpenXM/src/asir-doc/parts/groebner.texi,v 1.17 2006/09/06 23:53:31 noro Exp $
1.2       noro        2: \BJP
1.1       noro        3: @node $B%0%l%V%J4pDl$N7W;;(B,,, Top
                      4: @chapter $B%0%l%V%J4pDl$N7W;;(B
1.2       noro        5: \E
                      6: \BEG
                      7: @node Groebner basis computation,,, Top
                      8: @chapter Groebner basis computation
                      9: \E
1.1       noro       10:
                     11: @menu
1.2       noro       12: \BJP
1.1       noro       13: * $BJ,;6I=8=B?9`<0(B::
                     14: * $B%U%!%$%k$NFI$_9~$_(B::
                     15: * $B4pK\E*$JH!?t(B::
                     16: * $B7W;;$*$h$SI=<($N@)8f(B::
                     17: * $B9`=g=x$N@_Dj(B::
1.13      noro       18: * Weight::
1.1       noro       19: * $BM-M}<0$r78?t$H$9$k%0%l%V%J4pDl7W;;(B::
                     20: * $B4pDlJQ49(B::
1.5       noro       21: * Weyl $BBe?t(B::
1.1       noro       22: * $B%0%l%V%J4pDl$K4X$9$kH!?t(B::
1.2       noro       23: \E
                     24: \BEG
                     25: * Distributed polynomial::
                     26: * Reading files::
                     27: * Fundamental functions::
                     28: * Controlling Groebner basis computations::
                     29: * Setting term orderings::
1.13      noro       30: * Weight::
1.2       noro       31: * Groebner basis computation with rational function coefficients::
                     32: * Change of ordering::
1.5       noro       33: * Weyl algebra::
1.2       noro       34: * Functions for Groebner basis computation::
                     35: \E
1.1       noro       36: @end menu
                     37:
1.2       noro       38: \BJP
1.1       noro       39: @node $BJ,;6I=8=B?9`<0(B,,, $B%0%l%V%J4pDl$N7W;;(B
                     40: @section $BJ,;6I=8=B?9`<0(B
1.2       noro       41: \E
                     42: \BEG
                     43: @node Distributed polynomial,,, Groebner basis computation
                     44: @section Distributed polynomial
                     45: \E
1.1       noro       46:
                     47: @noindent
1.2       noro       48: \BJP
1.1       noro       49: $BJ,;6I=8=B?9`<0$H$O(B, $BB?9`<0$NFbIt7A<0$N0l$D$G$"$k(B. $BDL>o$NB?9`<0(B
                     50: (@code{type} $B$,(B 2) $B$O(B, $B:F5"I=8=$H8F$P$l$k7A<0$GI=8=$5$l$F$$$k(B. $B$9$J$o(B
                     51: $B$A(B, $BFCDj$NJQ?t$r<gJQ?t$H$9$k(B 1 $BJQ?tB?9`<0$G(B, $B$=$NB>$NJQ?t$O(B, $B$=$N(B 1 $BJQ(B
                     52: $B?tB?9`<0$N78?t$K(B, $B<gJQ?t$r4^$^$J$$B?9`<0$H$7$F8=$l$k(B. $B$3$N78?t$,(B, $B$^$?(B,
                     53: $B$"$kJQ?t$r<gJQ?t$H$9$kB?9`<0$H$J$C$F$$$k$3$H$+$i:F5"I=8=$H8F$P$l$k(B.
1.2       noro       54: \E
                     55: \BEG
                     56: A distributed polynomial is a polynomial with a special internal
                     57: representation different from the ordinary one.
                     58:
                     59: An ordinary polynomial (having @code{type} 2) is internally represented
                     60: in a format, called recursive representation.
                     61: In fact, it is represented as an uni-variate polynomial with respect to
                     62: a fixed variable, called main variable of that polynomial,
                     63: where the other variables appear in the coefficients which may again
                     64: polynomials in such variables other than the previous main variable.
                     65: A polynomial in the coefficients is again represented as
                     66: an uni-variate polynomial in a certain fixed variable,
                     67: the main variable.  Thus, by this recursive structure of polynomial
                     68: representation, it is called the `recursive representation.'
                     69: \E
1.1       noro       70:
                     71: @iftex
                     72: @tex
1.2       noro       73: \JP $(x+y+z)^2 = 1 \cdot x^2 + (2 \cdot y + (2 \cdot z)) \cdot x + ((2 \cdot z) \cdot y + (1 \cdot z^2 ))$
                     74: \EG $(x+y+z)^2 = 1 \cdot x^2 + (2 \cdot y + (2 \cdot z)) \cdot x + ((2 \cdot z) \cdot y + (1 \cdot z^2 ))$
1.1       noro       75: @end tex
                     76: @end iftex
                     77: @ifinfo
                     78: @example
                     79: (x+y+z)^2 = 1 x^2 + (2 y + (2 z)) x + ((2 z) y + (1 z^2 ))
                     80: @end example
                     81: @end ifinfo
                     82:
                     83: @noindent
1.2       noro       84: \BJP
1.1       noro       85: $B$3$l$KBP$7(B, $BB?9`<0$r(B, $BJQ?t$NQQ@Q$H78?t$N@Q$NOB$H$7$FI=8=$7$?$b$N$rJ,;6(B
                     86: $BI=8=$H8F$V(B.
1.2       noro       87: \E
                     88: \BEG
                     89: On the other hand,
                     90: we call a representation the distributed representation of a polynomial,
                     91: if a polynomial is represented, according to its original meaning,
                     92: as a sum of monomials,
                     93: where a monomial is the product of power product of variables
                     94: and a coefficient.  We call a polynomial, represented in such an
                     95: internal format, a distributed polynomial. (This naming may sounds
                     96: something strange.)
                     97: \E
1.1       noro       98:
                     99: @iftex
                    100: @tex
1.2       noro      101: \JP $(x+y+z)^2 = 1 \cdot x^2 + 2 \cdot xy + 2 \cdot xz + 1 \cdot y^2 + 2 \cdot yz +1 \cdot z^2$
                    102: \EG $(x+y+z)^2 = 1 \cdot x^2 + 2 \cdot xy + 2 \cdot xz + 1 \cdot y^2 + 2 \cdot yz +1 \cdot z^2$
1.1       noro      103: @end tex
                    104: @end iftex
                    105: @ifinfo
                    106: @example
                    107: (x+y+z)^2 = 1 x^2 + 2 xy + 2 xz + 1 y^2 + 2 yz +1 z^2$
                    108: @end example
                    109: @end ifinfo
                    110:
                    111: @noindent
1.2       noro      112: \BJP
1.1       noro      113: $B%0%l%V%J4pDl7W;;$K$*$$$F$O(B, $BC19`<0$KCmL\$7$FA`:n$r9T$&$?$aB?9`<0$,J,;6I=8=(B
                    114: $B$5$l$F$$$kJ}$,$h$j8zN($N$h$$1i;;$,2DG=$K$J$k(B. $B$3$N$?$a(B, $BJ,;6I=8=B?9`<0$,(B,
                    115: $B<1JL;R(B 9 $B$N7?$H$7$F(B @b{Asir} $B$N%H%C%W%l%Y%k$+$iMxMQ2DG=$H$J$C$F$$$k(B.
                    116: $B$3$3$G(B, $B8e$N@bL@$N$?$a$K(B, $B$$$/$D$+$N8@MU$rDj5A$7$F$*$/(B.
1.2       noro      117: \E
                    118: \BEG
                    119: For computation of Groebner basis, efficient operation is expected if
                    120: polynomials are represented in a distributed representation,
                    121: because major operations for Groebner basis are performed with respect
                    122: to monomials.
                    123: From this view point, we provide the object type distributed polynomial
                    124: with its object identification number 9, and objects having such a type
                    125: are available by @b{Asir} language.
                    126:
                    127: Here, we provide several definitions for the later description.
                    128: \E
1.1       noro      129:
                    130: @table @b
1.2       noro      131: \BJP
1.1       noro      132: @item $B9`(B (term)
                    133: $BJQ?t$NQQ@Q(B. $B$9$J$o$A(B, $B78?t(B 1 $B$NC19`<0$N$3$H(B. @b{Asir} $B$K$*$$$F$O(B,
1.2       noro      134: \E
                    135: \BEG
                    136: @item term
                    137: The power product of variables, i.e., a monomial with coefficient 1.
                    138: In an @b{Asir} session, it is displayed in the form like
                    139: \E
1.1       noro      140:
                    141: @example
                    142: <<0,1,2,3,4>>
                    143: @end example
                    144:
1.2       noro      145: \BJP
1.1       noro      146: $B$H$$$&7A$GI=<($5$l(B, $B$^$?(B, $B$3$N7A$GF~NO2DG=$G$"$k(B. $B$3$NNc$O(B, 5 $BJQ?t$N9`(B
                    147: $B$r<($9(B. $B3FJQ?t$r(B @code{a}, @code{b}, @code{c}, @code{d}, @code{e} $B$H$9$k$H(B
                    148: $B$3$N9`$O(B @code{b*c^2*d^3*e^4} $B$rI=$9(B.
1.2       noro      149: \E
                    150: \BEG
                    151: and also can be input in such a form.
                    152: This example shows a term in 5 variables.  If we assume the 5 variables
                    153: as @code{a}, @code{b}, @code{c}, @code{d}, and @code{e},
                    154: the term represents @code{b*c^2*d^3*e^4} in the ordinary expression.
                    155: \E
1.1       noro      156:
1.2       noro      157: \BJP
1.1       noro      158: @item $B9`=g=x(B (term order)
                    159: $BJ,;6I=8=B?9`<0$K$*$1$k9`$O(B, $B<!$N@-<A$rK~$?$9A4=g=x$K$h$j@0Ns$5$l$k(B.
1.2       noro      160: \E
                    161: \BEG
                    162: @item term order
                    163: Terms are ordered according to a total order with the following properties.
                    164: \E
1.1       noro      165:
                    166: @enumerate
                    167: @item
1.2       noro      168: \JP $BG$0U$N9`(B @code{t} $B$KBP$7(B @code{t} > 1
                    169: \EG For all @code{t} @code{t} > 1.
1.1       noro      170:
                    171: @item
1.2       noro      172: \JP @code{t}, @code{s}, @code{u} $B$r9`$H$9$k;~(B, @code{t} > @code{s} $B$J$i$P(B @code{tu} > @code{su}
                    173: \EG For all @code{t}, @code{s}, @code{u} @code{t} > @code{s} implies @code{tu} > @code{su}.
1.1       noro      174: @end enumerate
                    175:
1.2       noro      176: \BJP
1.1       noro      177: $B$3$N@-<A$rK~$?$9A4=g=x$r9`=g=x$H8F$V(B. $B$3$N=g=x$OJQ?t=g=x(B ($BJQ?t$N%j%9%H(B)
                    178: $B$H9`=g=x7?(B ($B?t(B, $B%j%9%H$^$?$O9TNs(B) $B$K$h$j;XDj$5$l$k(B.
1.2       noro      179: \E
                    180: \BEG
                    181: Such a total order is called a term ordering. A term ordering is specified
                    182: by a variable ordering (a list of variables) and a type of term ordering
                    183: (an integer, a list or a matrix).
                    184: \E
1.1       noro      185:
1.2       noro      186: \BJP
1.1       noro      187: @item $BC19`<0(B (monomial)
                    188: $B9`$H78?t$N@Q(B.
1.2       noro      189: \E
                    190: \BEG
                    191: @item monomial
                    192: The product of a term and a coefficient.
                    193: In an @b{Asir} session, it is displayed in the form like
                    194: \E
1.1       noro      195:
                    196: @example
                    197: 2*<<0,1,2,3,4>>
                    198: @end example
                    199:
1.2       noro      200: \JP $B$H$$$&7A$GI=<($5$l(B, $B$^$?(B, $B$3$N7A$GF~NO2DG=$G$"$k(B.
                    201: \EG and also can be input in such a form.
1.1       noro      202:
1.2       noro      203: \BJP
1.1       noro      204: @itemx $BF,C19`<0(B (head monomial)
                    205: @item $BF,9`(B (head term)
                    206: @itemx $BF,78?t(B (head coefficient)
                    207: $BJ,;6I=8=B?9`<0$K$*$1$k3FC19`<0$O(B, $B9`=g=x$K$h$j@0Ns$5$l$k(B. $B$3$N;~=g(B
                    208: $B=x:GBg$NC19`<0$rF,C19`<0(B, $B$=$l$K8=$l$k9`(B, $B78?t$r$=$l$>$lF,9`(B, $BF,78?t(B
                    209: $B$H8F$V(B.
1.2       noro      210: \E
                    211: \BEG
                    212: @itemx head monomial
                    213: @item head term
                    214: @itemx head coefficient
                    215:
                    216: Monomials in a distributed polynomial is sorted by a total order.
                    217: In such representation, we call the monomial that is maximum
                    218: with respect to the order the head monomial, and its term and coefficient
                    219: the head term and the head coefficient respectively.
                    220: \E
1.1       noro      221: @end table
                    222:
1.2       noro      223: \BJP
1.1       noro      224: @node $B%U%!%$%k$NFI$_9~$_(B,,, $B%0%l%V%J4pDl$N7W;;(B
                    225: @section $B%U%!%$%k$NFI$_9~$_(B
1.2       noro      226: \E
                    227: \BEG
                    228: @node Reading files,,, Groebner basis computation
                    229: @section Reading files
                    230: \E
1.1       noro      231:
                    232: @noindent
1.2       noro      233: \BJP
1.1       noro      234: $B%0%l%V%J4pDl$r7W;;$9$k$?$a$N4pK\E*$JH!?t$O(B @code{dp_gr_main()} $B$*$h$S(B
1.5       noro      235: @code{dp_gr_mod_main()}, @code{dp_gr_f_main()}
                    236:  $B$J$k(B 3 $B$D$NAH$_9~$_H!?t$G$"$k$,(B, $BDL>o$O(B, $B%Q%i%a%?(B
1.1       noro      237: $B@_Dj$J$I$r9T$C$?$N$A$3$l$i$r8F$S=P$9%f!<%6H!?t$rMQ$$$k$N$,JXMx$G$"$k(B.
                    238: $B$3$l$i$N%f!<%6H!?t$O(B, $B%U%!%$%k(B @samp{gr} $B$r(B @code{load()} $B$K$h$jFI(B
                    239: $B$_9~$`$3$H$K$h$j;HMQ2DG=$H$J$k(B. @samp{gr} $B$O(B, @b{Asir} $B$NI8=`(B
1.5       noro      240: $B%i%$%V%i%j%G%#%l%/%H%j$KCV$+$l$F$$$k(B.
1.2       noro      241: \E
                    242: \BEG
1.5       noro      243: Facilities for computing Groebner bases are
                    244: @code{dp_gr_main()}, @code{dp_gr_mod_main()}and @code{dp_gr_f_main()}.
                    245: To call these functions,
                    246: it is necessary to set several parameters correctly and it is convenient
                    247: to use a set of interface functions provided in the library file
                    248: @samp{gr}.
1.2       noro      249: The facilities will be ready to use after you load the package by
                    250: @code{load()}.  The package @samp{gr} is placed in the standard library
1.5       noro      251: directory of @b{Asir}.
1.2       noro      252: \E
1.1       noro      253:
                    254: @example
                    255: [0] load("gr")$
                    256: @end example
                    257:
1.2       noro      258: \BJP
1.1       noro      259: @node $B4pK\E*$JH!?t(B,,, $B%0%l%V%J4pDl$N7W;;(B
                    260: @section $B4pK\E*$JH!?t(B
1.2       noro      261: \E
                    262: \BEG
                    263: @node Fundamental functions,,, Groebner basis computation
                    264: @section Fundamental functions
                    265: \E
1.1       noro      266:
                    267: @noindent
1.2       noro      268: \BJP
1.1       noro      269: @samp{gr} $B$G$O?tB?$/$NH!?t$,Dj5A$5$l$F$$$k$,(B, $BD>@\(B
                    270: $B%0%l%V%J4pDl$r7W;;$9$k$?$a$N%H%C%W%l%Y%k$O<!$N(B 3 $B$D$G$"$k(B.
                    271: $B0J2<$G(B, @var{plist} $B$OB?9`<0$N%j%9%H(B, @var{vlist} $B$OJQ?t(B ($BITDj85(B) $B$N%j%9%H(B,
                    272: @var{order} $B$OJQ?t=g=x7?(B, @var{p} $B$O(B @code{2^27} $BL$K~$NAG?t$G$"$k(B.
1.2       noro      273: \E
                    274: \BEG
                    275: There are many functions and options defined in the package @samp{gr}.
                    276: Usually not so many of them are used.  Top level functions for Groebner
                    277: basis computation are the following three functions.
                    278:
                    279: In the following description, @var{plist}, @var{vlist}, @var{order}
                    280: and @var{p} stand for  a list of polynomials,  a list of variables
                    281: (indeterminates), a type of term ordering and a prime less than
                    282: @code{2^27} respectively.
                    283: \E
1.1       noro      284:
                    285: @table @code
                    286: @item gr(@var{plist},@var{vlist},@var{order})
                    287:
1.2       noro      288: \BJP
1.1       noro      289: Gebauer-Moeller $B$K$h$k(B useless pair elimination criteria, sugar
                    290: strategy $B$*$h$S(B Traverso $B$K$h$k(B trace-lifting $B$rMQ$$$?(B Buchberger $B%"%k(B
                    291: $B%4%j%:%`$K$h$kM-M}?t78?t%0%l%V%J4pDl7W;;H!?t(B. $B0lHL$K$O$3$NH!?t$rMQ$$$k(B.
1.2       noro      292: \E
                    293: \BEG
                    294: Function that computes Groebner bases over the rationals. The
                    295: algorithm is Buchberger algorithm with useless pair elimination
                    296: criteria by Gebauer-Moeller, sugar strategy and trace-lifting by
                    297: Traverso. For ordinary computation, this function is used.
                    298: \E
1.1       noro      299:
                    300: @item hgr(@var{plist},@var{vlist},@var{order})
                    301:
1.2       noro      302: \BJP
1.1       noro      303: $BF~NOB?9`<0$r@F<!2=$7$?8e(B @code{gr()} $B$N%0%l%V%J4pDl8uJd@8@.It$K$h$j8u(B
                    304: $BJd@8@.$7(B, $BHs@F<!2=(B, interreduce $B$7$?$b$N$r(B @code{gr()} $B$N%0%l%V%J4pDl(B
                    305: $B%A%'%C%/It$G%A%'%C%/$9$k(B. 0 $B<!85%7%9%F%`(B ($B2r$N8D?t$,M-8B8D$NJ}Dx<07O(B)
                    306: $B$N>l9g(B, sugar strategy $B$,78?tKDD%$r0z$-5/$3$9>l9g$,$"$k(B. $B$3$N$h$&$J>l(B
                    307: $B9g(B, strategy $B$r@F<!2=$K$h$k(B strategy $B$KCV$-49$($k$3$H$K$h$j78?tKDD%$r(B
                    308: $BM^@)$9$k$3$H$,$G$-$k>l9g$,B?$$(B.
1.2       noro      309: \E
                    310: \BEG
                    311: After homogenizing the input polynomials a candidate of the \gr basis
                    312: is computed by trace-lifting. Then the candidate is dehomogenized and
                    313: checked whether it is indeed a Groebner basis of the input.  Sugar
                    314: strategy often causes intermediate coefficient swells.  It is
                    315: empirically known that the combination of homogenization and supresses
                    316: the swells for such cases.
                    317: \E
1.1       noro      318:
                    319: @item gr_mod(@var{plist},@var{vlist},@var{order},@var{p})
                    320:
1.2       noro      321: \BJP
1.1       noro      322: Gebauer-Moeller $B$K$h$k(B useless pair elimination criteria, sugar
                    323: strategy $B$*$h$S(B Buchberger $B%"%k%4%j%:%`$K$h$k(B GF(p) $B78?t%0%l%V%J4pDl7W(B
                    324: $B;;H!?t(B.
1.2       noro      325: \E
                    326: \BEG
                    327: Function that computes Groebner bases over GF(@var{p}). The same
                    328: algorithm as @code{gr()} is used.
                    329: \E
1.1       noro      330:
                    331: @end table
                    332:
1.2       noro      333: \BJP
1.1       noro      334: @node $B7W;;$*$h$SI=<($N@)8f(B,,, $B%0%l%V%J4pDl$N7W;;(B
                    335: @section $B7W;;$*$h$SI=<($N@)8f(B
1.2       noro      336: \E
                    337: \BEG
                    338: @node Controlling Groebner basis computations,,, Groebner basis computation
                    339: @section Controlling Groebner basis computations
                    340: \E
1.1       noro      341:
                    342: @noindent
1.2       noro      343: \BJP
1.1       noro      344: $B%0%l%V%J4pDl$N7W;;$K$*$$$F(B, $B$5$^$6$^$J%Q%i%a%?@_Dj$r9T$&$3$H$K$h$j7W;;(B,
                    345: $BI=<($r@)8f$9$k$3$H$,$G$-$k(B. $B$3$l$i$O(B, $BAH$_9~$_H!?t(B @code{dp_gr_flags()}
                    346: $B$K$h$j@_Dj;2>H$9$k$3$H$,$G$-$k(B. $BL50z?t$G(B @code{dp_gr_flags()} $B$r<B9T$9$k(B
                    347: $B$H(B, $B8=:_@_Dj$5$l$F$$$k%Q%i%a%?$,(B, $BL>A0$HCM$N%j%9%H$GJV$5$l$k(B.
1.2       noro      348: \E
                    349: \BEG
                    350: One can cotrol a Groebner basis computation by setting various parameters.
                    351: These parameters can be set and examined by a built-in function
                    352: @code{dp_gr_flags()}. Without argument it returns the current settings.
                    353: \E
1.1       noro      354:
                    355: @example
                    356: [100] dp_gr_flags();
1.5       noro      357: [Demand,0,NoSugar,0,NoCriB,0,NoGC,0,NoMC,0,NoRA,0,NoGCD,0,Top,0,
                    358: ShowMag,1,Print,1,Stat,0,Reverse,0,InterReduce,0,Multiple,0]
1.1       noro      359: [101]
                    360: @end example
                    361:
1.2       noro      362: \BJP
1.1       noro      363: $B0J2<$G(B, $B3F%Q%i%a%?$N0UL#$r@bL@$9$k(B. on $B$N>l9g$H$O(B, $B%Q%i%a%?$,(B 0 $B$G$J$$>l9g$r(B
                    364: $B$$$&(B. $B$3$l$i$N%Q%i%a%?$N=i4|CM$OA4$F(B 0 (off) $B$G$"$k(B.
1.2       noro      365: \E
                    366: \BEG
                    367: The return value is a list which contains the names of parameters and their
                    368: values. The meaning of the parameters are as follows. `on' means that the
                    369: parameter is not zero.
                    370: \E
1.1       noro      371:
                    372: @table @code
                    373: @item NoSugar
1.2       noro      374: \BJP
1.1       noro      375: on $B$N>l9g(B, sugar strategy $B$NBe$o$j$K(B Buchberger$B$N(B normal strategy $B$,MQ(B
                    376: $B$$$i$l$k(B.
1.2       noro      377: \E
                    378: \BEG
                    379: If `on', Buchberger's normal strategy is used instead of sugar strategy.
                    380: \E
1.1       noro      381:
                    382: @item NoCriB
1.2       noro      383: \JP on $B$N>l9g(B, $BITI,MWBP8!=P5,=`$N$&$A(B, $B5,=`(B B $B$rE,MQ$7$J$$(B.
                    384: \EG If `on', criterion B among the Gebauer-Moeller's criteria is not applied.
1.1       noro      385:
                    386: @item NoGC
1.2       noro      387: \JP on $B$N>l9g(B, $B7k2L$,%0%l%V%J4pDl$K$J$C$F$$$k$+$I$&$+$N%A%'%C%/$r9T$o$J$$(B.
                    388: \BEG
                    389: If `on', the check that a Groebner basis candidate is indeed a Groebner basis,
                    390: is not executed.
                    391: \E
1.1       noro      392:
                    393: @item NoMC
1.2       noro      394: \BJP
1.1       noro      395: on $B$N>l9g(B, $B7k2L$,F~NO%$%G%"%k$HF1Ey$N%$%G%"%k$G$"$k$+$I$&$+$N%A%'%C%/(B
                    396: $B$r9T$o$J$$(B.
1.2       noro      397: \E
                    398: \BEG
                    399: If `on', the check that the resulting polynomials generates the same ideal as
                    400: the ideal generated by the input, is not executed.
                    401: \E
1.1       noro      402:
                    403: @item NoRA
1.2       noro      404: \BJP
1.1       noro      405: on $B$N>l9g(B, $B7k2L$r(B reduced $B%0%l%V%J4pDl$K$9$k$?$a$N(B
                    406: interreduce $B$r9T$o$J$$(B.
1.2       noro      407: \E
                    408: \BEG
                    409: If `on', the interreduction, which makes the Groebner basis reduced, is not
                    410: executed.
                    411: \E
1.1       noro      412:
                    413: @item NoGCD
1.2       noro      414: \BJP
1.1       noro      415: on $B$N>l9g(B, $BM-M}<078?t$N%0%l%V%J4pDl7W;;$K$*$$$F(B, $B@8@.$5$l$?B?9`<0$N(B,
                    416: $B78?t$N(B content $B$r$H$i$J$$(B.
1.2       noro      417: \E
                    418: \BEG
                    419: If `on', content removals are not executed during a Groebner basis computation
                    420: over a rational function field.
                    421: \E
1.1       noro      422:
                    423: @item Top
1.2       noro      424: \JP on $B$N>l9g(B, normal form $B7W;;$K$*$$$FF,9`>C5n$N$_$r9T$&(B.
                    425: \EG If `on', Only the head term of the polynomial being reduced is reduced.
1.1       noro      426:
1.2       noro      427: @comment @item Interreduce
                    428: @comment \BJP
                    429: @comment on $B$N>l9g(B, $BB?9`<0$r@8@.$9$kKh$K(B, $B$=$l$^$G@8@.$5$l$?4pDl$r$=$NB?9`<0$K(B
                    430: @comment $B$h$k(B normal form $B$GCV$-49$($k(B.
                    431: @comment \E
                    432: @comment \BEG
                    433: @comment If `on', intermediate basis elements are reduced by using a newly generated
                    434: @comment basis element.
                    435: @comment \E
1.1       noro      436:
                    437: @item Reverse
1.2       noro      438: \BJP
1.1       noro      439: on $B$N>l9g(B, normal form $B7W;;$N:]$N(B reducer $B$r(B, $B?7$7$/@8@.$5$l$?$b$N$rM%(B
                    440: $B@h$7$FA*$V(B.
1.2       noro      441: \E
                    442: \BEG
                    443: If `on', the selection strategy of reducer in a normal form computation
                    444: is such that a newer reducer is used first.
                    445: \E
1.1       noro      446:
                    447: @item Print
1.2       noro      448: \JP on $B$N>l9g(B, $B%0%l%V%J4pDl7W;;$NESCf$K$*$1$k$5$^$6$^$J>pJs$rI=<($9$k(B.
                    449: \BEG
                    450: If `on', various informations during a Groebner basis computation is
                    451: displayed.
                    452: \E
1.1       noro      453:
1.7       noro      454: @item PrintShort
                    455: \JP on $B$G!"(BPrint $B$,(B off $B$N>l9g(B, $B%0%l%V%J4pDl7W;;$NESCf$N>pJs$rC;=L7A$GI=<($9$k(B.
                    456: \BEG
                    457: If `on' and Print is `off', short information during a Groebner basis computation is
                    458: displayed.
                    459: \E
                    460:
1.1       noro      461: @item Stat
1.2       noro      462: \BJP
1.1       noro      463: on $B$G(B @code{Print} $B$,(B off $B$J$i$P(B, @code{Print} $B$,(B on $B$N$H$-I=<($5(B
                    464: $B$l$k%G!<%?$NFb(B, $B=87W%G!<%?$N$_$,I=<($5$l$k(B.
1.2       noro      465: \E
                    466: \BEG
                    467: If `on', a summary of informations is shown after a Groebner basis
                    468: computation. Note that the summary is always shown if @code{Print} is `on'.
                    469: \E
1.1       noro      470:
                    471: @item ShowMag
1.2       noro      472: \BJP
1.1       noro      473: on $B$G(B @code{Print} $B$,(B on $B$J$i$P(B, $B@8@.$,@8@.$5$l$kKh$K(B, $B$=$NB?9`<0$N(B
                    474: $B78?t$N%S%C%HD9$NOB$rI=<($7(B, $B:G8e$K(B, $B$=$l$i$NOB$N:GBgCM$rI=<($9$k(B.
1.2       noro      475: \E
                    476: \BEG
                    477: If `on' and @code{Print} is `on', the sum of bit length of
                    478: coefficients of a generated basis element, which we call @var{magnitude},
                    479: is shown after every normal computation.  After comleting the
                    480: computation the maximal value among the sums is shown.
                    481: \E
1.1       noro      482:
1.7       noro      483: @item Content
                    484: @itemx Multiple
1.2       noro      485: \BJP
1.7       noro      486: 0 $B$G$J$$M-M}?t$N;~(B, $BM-M}?t>e$N@55,7A7W;;$K$*$$$F(B, $B78?t$N%S%C%HD9$NOB$,(B
                    487: @code{Content} $BG\$K$J$k$4$H$K78?tA4BN$N(B GCD $B$,7W;;$5$l(B, $B$=$N(B GCD $B$G(B
                    488: $B3d$C$?B?9`<0$r4JLs$9$k(B. @code{Content} $B$,(B 1 $B$J$i$P(B, $B4JLs$9$k$4$H$K(B
                    489: GCD $B7W;;$,9T$o$l0lHL$K$O8zN($,0-$/$J$k$,(B, @code{Content} $B$r(B 2 $BDxEY(B
1.1       noro      490: $B$H$9$k$H(B, $B5pBg$J@0?t$,78?t$K8=$l$k>l9g(B, $B8zN($,NI$/$J$k>l9g$,$"$k(B.
1.7       noro      491: backward compatibility $B$N$?$a!"(B@code{Multiple} $B$G@0?tCM$r;XDj$G$-$k(B.
1.2       noro      492: \E
                    493: \BEG
1.7       noro      494: If a non-zero rational number, in a normal form computation
1.2       noro      495: over the rationals, the integer content of the polynomial being
1.7       noro      496: reduced is removed when its magnitude becomes @code{Content} times
1.2       noro      497: larger than a registered value, which is set to the magnitude of the
                    498: input polynomial. After each content removal the registered value is
1.7       noro      499: set to the magnitude of the resulting polynomial. @code{Content} is
1.2       noro      500: equal to 1, the simiplification is done after every normal form computation.
1.7       noro      501: It is empirically known that it is often efficient to set @code{Content} to 2
1.2       noro      502: for the case where large integers appear during the computation.
1.7       noro      503: An integer value can be set by the keyword @code{Multiple} for
                    504: backward compatibility.
1.2       noro      505: \E
1.1       noro      506:
                    507: @item Demand
1.2       noro      508:
                    509: \BJP
1.1       noro      510: $B@5Ev$J%G%#%l%/%H%jL>(B ($BJ8;zNs(B) $B$rCM$K;}$D$H$-(B, $B@8@.$5$l$?B?9`<0$O%a%b%j(B
                    511: $BCf$K$*$+$l$:(B, $B$=$N%G%#%l%/%H%jCf$K%P%$%J%j%G!<%?$H$7$FCV$+$l(B, $B$=$NB?9`(B
                    512: $B<0$rMQ$$$k(B normal form $B7W;;$N:](B, $B<+F0E*$K%a%b%jCf$K%m!<%I$5$l$k(B. $B3FB?(B
                    513: $B9`<0$O(B, $BFbIt$G$N%$%s%G%C%/%9$r%U%!%$%kL>$K;}$D%U%!%$%k$K3JG<$5$l$k(B.
                    514: $B$3$3$G;XDj$5$l$?%G%#%l%/%H%j$K=q$+$l$?%U%!%$%k$O<+F0E*$K$O>C5n$5$l$J$$(B
                    515: $B$?$a(B, $B%f!<%6$,@UG$$r;}$C$F>C5n$9$kI,MW$,$"$k(B.
1.2       noro      516: \E
                    517: \BEG
                    518: If the value (a character string) is a valid directory name, then
                    519: generated basis elements are put in the directory and are loaded on
                    520: demand during normal form computations.  Each elements is saved in the
                    521: binary form and its name coincides with the index internally used in
                    522: the computation. These binary files are not removed automatically
                    523: and one should remove them by hand.
                    524: \E
1.1       noro      525: @end table
                    526:
                    527: @noindent
1.2       noro      528: \JP @code{Print} $B$,(B 0 $B$G$J$$>l9g<!$N$h$&$J%G!<%?$,I=<($5$l$k(B.
                    529: \EG If @code{Print} is `on', the following informations are shown.
1.1       noro      530:
                    531: @example
                    532: [93] gr(cyclic(4),[c0,c1,c2,c3],0)$
                    533: mod= 99999989, eval = []
                    534: (0)(0)<<0,2,0,0>>(2,3),nb=2,nab=5,rp=2,sugar=2,mag=4
                    535: (0)(0)<<0,1,2,0>>(1,2),nb=3,nab=6,rp=2,sugar=3,mag=4
                    536: (0)(0)<<0,1,1,2>>(0,1),nb=4,nab=7,rp=3,sugar=4,mag=6
                    537: .
                    538: (0)(0)<<0,0,3,2>>(5,6),nb=5,nab=8,rp=2,sugar=5,mag=4
                    539: (0)(0)<<0,1,0,4>>(4,6),nb=6,nab=9,rp=3,sugar=5,mag=4
                    540: (0)(0)<<0,0,2,4>>(6,8),nb=7,nab=10,rp=4,sugar=6,mag=6
                    541: ....gb done
                    542: reduceall
                    543: .......
                    544: membercheck
                    545: (0,0)(0,0)(0,0)(0,0)
                    546: gbcheck total 8 pairs
                    547: ........
1.5       noro      548: UP=(0,0)SP=(0,0)SPM=(0,0)NF=(0,0)NFM=(0.010002,0)ZNFM=(0.010002,0)
                    549: PZ=(0,0)NP=(0,0)MP=(0,0)RA=(0,0)MC=(0,0)GC=(0,0)T=40,B=0 M=8 F=6
                    550: D=12 ZR=5 NZR=6 Max_mag=6
1.1       noro      551: [94]
                    552: @end example
                    553:
                    554: @noindent
1.2       noro      555: \BJP
1.1       noro      556: $B:G=i$KI=<($5$l$k(B @code{mod}, @code{eval} $B$O(B, trace-lifting $B$GMQ$$$i$l$kK!(B
                    557: $B$G$"$k(B. @code{mod} $B$OAG?t(B, @code{eval} $B$OM-M}<078?t$N>l9g$KMQ$$$i$l$k(B
                    558: $B?t$N%j%9%H$G$"$k(B.
1.2       noro      559: \E
                    560: \BEG
                    561: In this example @code{mod} and @code{eval} indicate moduli used in
                    562: trace-lifting. @code{mod} is a prime and @code{eval} is a list of integers
                    563: used for evaluation when the ground field is a field of rational functions.
                    564: \E
1.1       noro      565:
                    566: @noindent
1.2       noro      567: \JP $B7W;;ESCf$GB?9`<0$,@8@.$5$l$kKh$K<!$N7A$N%G!<%?$,I=<($5$l$k(B.
                    568: \EG The following information is shown after every normal form computation.
1.1       noro      569:
                    570: @example
                    571: (TNF)(TCONT)HT(INDEX),nb=NB,nab=NAB,rp=RP,sugar=S,mag=M
                    572: @end example
                    573:
                    574: @noindent
1.2       noro      575: \JP $B$=$l$i$N0UL#$O<!$NDL$j(B.
                    576: \EG Meaning of each component is as follows.
1.1       noro      577:
                    578: @table @code
1.2       noro      579: \BJP
1.1       noro      580: @item TNF
1.2       noro      581:
1.1       noro      582: normal form $B7W;;;~4V(B ($BIC(B)
                    583:
                    584: @item TCONT
1.2       noro      585:
1.1       noro      586: content $B7W;;;~4V(B ($BIC(B)
                    587:
                    588: @item HT
1.2       noro      589:
1.1       noro      590: $B@8@.$5$l$?B?9`<0$NF,9`(B
                    591:
                    592: @item INDEX
1.2       noro      593:
1.1       noro      594: S-$BB?9`<0$r9=@.$9$kB?9`<0$N%$%s%G%C%/%9$N%Z%"(B
                    595:
                    596: @item NB
1.2       noro      597:
1.1       noro      598: $B8=:_$N(B, $B>iD9@-$r=|$$$?4pDl$N?t(B
                    599:
                    600: @item NAB
1.2       noro      601:
1.1       noro      602: $B8=:_$^$G$K@8@.$5$l$?4pDl$N?t(B
                    603:
                    604: @item RP
1.2       noro      605:
1.1       noro      606: $B;D$j$N%Z%"$N?t(B
                    607:
                    608: @item S
1.2       noro      609:
1.1       noro      610: $B@8@.$5$l$?B?9`<0$N(B sugar $B$NCM(B
                    611:
                    612: @item M
1.2       noro      613:
1.1       noro      614: $B@8@.$5$l$?B?9`<0$N78?t$N%S%C%HD9$NOB(B (@code{ShowMag} $B$,(B on $B$N;~$KI=<($5$l$k(B. )
1.2       noro      615: \E
                    616: \BEG
                    617: @item TNF
                    618:
                    619: CPU time for normal form computation (second)
                    620:
                    621: @item TCONT
                    622:
                    623: CPU time for content removal(second)
                    624:
                    625: @item HT
                    626:
                    627: Head term of the generated basis element
                    628:
                    629: @item INDEX
                    630:
                    631: Pair of indices which corresponds to the reduced S-polynomial
                    632:
                    633: @item NB
                    634:
                    635: Number of basis elements after removing redundancy
                    636:
                    637: @item NAB
                    638:
                    639: Number of all the basis elements
                    640:
                    641: @item RP
                    642:
                    643: Number of remaining pairs
                    644:
                    645: @item S
                    646:
                    647: Sugar of the generated basis element
                    648:
                    649: @item M
                    650:
                    651: Magnitude of the genrated basis element (shown if @code{ShowMag} is `on'.)
                    652: \E
1.1       noro      653: @end table
                    654:
                    655: @noindent
1.2       noro      656: \BJP
1.1       noro      657: $B:G8e$K(B, $B=87W%G!<%?$,I=<($5$l$k(B. $B0UL#$O<!$NDL$j(B.
                    658: ($B;~4V$NI=<($K$*$$$F(B, $B?t;z$,(B 2 $B$D$"$k$b$N$O(B, $B7W;;;~4V$H(B GC $B;~4V$N%Z%"$G$"$k(B.)
1.2       noro      659: \E
                    660: \BEG
                    661: The summary of the informations shown after a Groebner basis
                    662: computation is as follows.  If a component shows timings and it
                    663: contains two numbers, they are a pair of time for computation and time
                    664: for garbage colection.
                    665: \E
1.1       noro      666:
                    667: @table @code
1.2       noro      668: \BJP
1.1       noro      669: @item UP
1.2       noro      670:
1.1       noro      671: $B%Z%"$N%j%9%H$NA`:n$K$+$+$C$?;~4V(B
                    672:
                    673: @item SP
1.2       noro      674:
1.1       noro      675: $BM-M}?t>e$N(B S-$BB?9`<07W;;;~4V(B
                    676:
                    677: @item SPM
1.2       noro      678:
1.1       noro      679: $BM-8BBN>e$N(B S-$BB?9`<07W;;;~4V(B
                    680:
                    681: @item NF
1.2       noro      682:
1.1       noro      683: $BM-M}?t>e$N(B normal form $B7W;;;~4V(B
                    684:
                    685: @item NFM
1.2       noro      686:
1.1       noro      687: $BM-8BBN>e$N(B normal form $B7W;;;~4V(B
                    688:
                    689: @item ZNFM
1.2       noro      690:
1.1       noro      691: @code{NFM} $B$NFb(B, 0 $B$X$N(B reduction $B$K$+$+$C$?;~4V(B
                    692:
                    693: @item PZ
1.2       noro      694:
1.1       noro      695: content $B7W;;;~4V(B
                    696:
                    697: @item NP
1.2       noro      698:
1.1       noro      699: $BM-M}?t78?tB?9`<0$N78?t$KBP$9$k>jM>1i;;$N7W;;;~4V(B
                    700:
                    701: @item MP
1.2       noro      702:
1.1       noro      703: S-$BB?9`<0$r@8@.$9$k%Z%"$NA*Br$K$+$+$C$?;~4V(B
                    704:
                    705: @item RA
1.2       noro      706:
1.1       noro      707: interreduce $B7W;;;~4V(B
                    708:
                    709: @item MC
1.2       noro      710:
1.1       noro      711: trace-lifting $B$K$*$1$k(B, $BF~NOB?9`<0$N%a%s%P%7%C%W7W;;;~4V(B
                    712:
                    713: @item GC
1.2       noro      714:
1.1       noro      715: $B7k2L$N%0%l%V%J4pDl8uJd$N%0%l%V%J4pDl%A%'%C%/;~4V(B
                    716:
                    717: @item T
1.2       noro      718:
1.1       noro      719: $B@8@.$5$l$?%Z%"$N?t(B
                    720:
                    721: @item B, M, F, D
1.2       noro      722:
1.1       noro      723: $B3F(B criterion $B$K$h$j=|$+$l$?%Z%"$N?t(B
                    724:
                    725: @item ZR
1.2       noro      726:
1.1       noro      727: 0 $B$K(B reduce $B$5$l$?%Z%"$N?t(B
                    728:
                    729: @item NZR
1.2       noro      730:
1.1       noro      731: 0 $B$G$J$$B?9`<0$K(B reduce $B$5$l$?%Z%"$N?t(B
                    732:
                    733: @item Max_mag
1.2       noro      734:
1.1       noro      735: $B@8@.$5$l$?B?9`<0$N(B, $B78?t$N%S%C%HD9$NOB$N:GBgCM(B
1.2       noro      736: \E
                    737: \BEG
                    738: @item UP
                    739:
                    740: Time to manipulate the list of critical pairs
                    741:
                    742: @item SP
                    743:
                    744: Time to compute S-polynomials over the rationals
                    745:
                    746: @item SPM
                    747:
                    748: Time to compute S-polynomials over a finite field
                    749:
                    750: @item NF
                    751:
                    752: Time to compute normal forms over the rationals
                    753:
                    754: @item NFM
                    755:
                    756: Time to compute normal forms over a finite field
                    757:
                    758: @item ZNFM
                    759:
                    760: Time for zero reductions in @code{NFM}
                    761:
                    762: @item PZ
                    763:
                    764: Time to remove integer contets
                    765:
                    766: @item NP
                    767:
                    768: Time to compute remainders for coefficients of polynomials with coeffieints
                    769: in the rationals
                    770:
                    771: @item MP
                    772:
                    773: Time to select pairs from which S-polynomials are computed
                    774:
                    775: @item RA
                    776:
                    777: Time to interreduce the Groebner basis candidate
                    778:
                    779: @item MC
1.1       noro      780:
1.2       noro      781: Time to check that each input polynomial is a member of the ideal
                    782: generated by the Groebner basis candidate.
                    783:
                    784: @item GC
                    785:
                    786: Time to check that the Groebner basis candidate is a Groebner basis
                    787:
                    788: @item T
                    789:
                    790: Number of critical pairs generated
                    791:
                    792: @item B, M, F, D
                    793:
                    794: Number of critical pairs removed by using each criterion
                    795:
                    796: @item ZR
                    797:
                    798: Number of S-polynomials reduced to 0
                    799:
                    800: @item NZR
                    801:
                    802: Number of S-polynomials reduced to non-zero results
                    803:
                    804: @item Max_mag
                    805:
                    806: Maximal magnitude among all the generated polynomials
                    807: \E
1.1       noro      808: @end table
                    809:
1.2       noro      810: \BJP
1.1       noro      811: @node $B9`=g=x$N@_Dj(B,,, $B%0%l%V%J4pDl$N7W;;(B
                    812: @section $B9`=g=x$N@_Dj(B
1.2       noro      813: \E
                    814: \BEG
                    815: @node Setting term orderings,,, Groebner basis computation
                    816: @section Setting term orderings
                    817: \E
1.1       noro      818:
                    819: @noindent
1.2       noro      820: \BJP
1.1       noro      821: $B9`$OFbIt$G$O(B, $B3FJQ?t$K4X$9$k;X?t$r@.J,$H$9$k@0?t%Y%/%H%k$H$7$FI=8=$5$l(B
                    822: $B$k(B. $BB?9`<0$rJ,;6I=8=B?9`<0$KJQ49$9$k:](B, $B3FJQ?t$,$I$N@.J,$KBP1~$9$k$+$r(B
                    823: $B;XDj$9$k$N$,(B, $BJQ?t%j%9%H$G$"$k(B. $B$5$i$K(B, $B$=$l$i@0?t%Y%/%H%k$NA4=g=x$r(B
                    824: $B;XDj$9$k$N$,9`=g=x$N7?$G$"$k(B. $B9`=g=x7?$O(B, $B?t(B, $B?t$N%j%9%H$"$k$$$O(B
                    825: $B9TNs$GI=8=$5$l$k(B.
1.2       noro      826: \E
                    827: \BEG
                    828: A term is internally represented as an integer vector whose components
                    829: are exponents with respect to variables. A variable list specifies the
                    830: correspondences between variables and components. A type of term ordering
                    831: specifies a total order for integer vectors. A type of term ordering is
                    832: represented by an integer, a list of integer or matrices.
                    833: \E
1.1       noro      834:
                    835: @noindent
1.2       noro      836: \JP $B4pK\E*$J9`=g=x7?$H$7$F<!$N(B 3 $B$D$,$"$k(B.
                    837: \EG There are following three fundamental types.
1.1       noro      838:
                    839: @table @code
1.2       noro      840: \JP @item 0 (DegRevLex; @b{$BA4<!?t5U<-=q<0=g=x(B})
                    841: \EG @item 0 (DegRevLex; @b{total degree reverse lexicographic ordering})
1.1       noro      842:
1.2       noro      843: \BJP
1.1       noro      844: $B0lHL$K(B, $B$3$N=g=x$K$h$k%0%l%V%J4pDl7W;;$,:G$b9bB.$G$"$k(B. $B$?$@$7(B,
                    845: $BJ}Dx<0$r2r$/$H$$$&L\E*$KMQ$$$k$3$H$O(B, $B0lHL$K$O$G$-$J$$(B. $B$3$N(B
                    846: $B=g=x$K$h$k%0%l%V%J4pDl$O(B, $B2r$N8D?t$N7W;;(B, $B%$%G%"%k$N%a%s%P%7%C%W$d(B,
                    847: $BB>$NJQ?t=g=x$X$N4pDlJQ49$N$?$a$N%=!<%9$H$7$FMQ$$$i$l$k(B.
1.2       noro      848: \E
                    849: \BEG
                    850: In general, computation by this ordering shows the fastest speed
                    851: in most Groebner basis computations.
                    852: However, for the purpose to solve polynomial equations, this type
                    853: of ordering is, in general, not so suitable.
                    854: The Groebner bases obtained by this ordering is used for computing
                    855: the number of solutions, solving ideal membership problem and seeds
                    856: for conversion to other Groebner bases under different ordering.
                    857: \E
1.1       noro      858:
1.2       noro      859: \JP @item 1 (DegLex; @b{$BA4<!?t<-=q<0=g=x(B})
                    860: \EG @item 1 (DegLex; @b{total degree lexicographic ordering})
1.1       noro      861:
1.2       noro      862: \BJP
1.1       noro      863: $B$3$N=g=x$b(B, $B<-=q<0=g=x$KHf$Y$F9bB.$K%0%l%V%J4pDl$r5a$a$k$3$H$,$G$-$k$,(B,
                    864: @code{DegRevLex} $B$HF1MMD>@\$=$N7k2L$rMQ$$$k$3$H$O:$Fq$G$"$k(B. $B$7$+$7(B,
                    865: $B<-=q<0=g=x$N%0%l%V%J4pDl$r5a$a$k:]$K(B, $B@F<!2=8e$K$3$N=g=x$G%0%l%V%J4pDl(B
                    866: $B$r5a$a$F$$$k(B.
1.2       noro      867: \E
                    868: \BEG
                    869: By this type term ordering, Groebner bases are obtained fairly faster
                    870: than Lex (lexicographic) ordering, too.
                    871: Alike the @code{DegRevLex} ordering, the result, in general, cannot directly
                    872: be used for solving polynomial equations.
                    873: It is used, however, in such a way
                    874: that a Groebner basis is computed in this ordering after homogenization
                    875: to obtain the final lexicographic Groebner basis.
                    876: \E
1.1       noro      877:
1.2       noro      878: \JP @item 2 (Lex; @b{$B<-=q<0=g=x(B})
                    879: \EG @item 2 (Lex; @b{lexicographic ordering})
1.1       noro      880:
1.2       noro      881: \BJP
1.1       noro      882: $B$3$N=g=x$K$h$k%0%l%V%J4pDl$O(B, $BJ}Dx<0$r2r$/>l9g$K:GE,$N7A$N4pDl$rM?$($k$,(B
                    883: $B7W;;;~4V$,$+$+$j2a$.$k$N$,FqE@$G$"$k(B. $BFC$K(B, $B2r$,M-8B8D$N>l9g(B, $B7k2L$N(B
                    884: $B78?t$,6K$a$FD9Bg$JB?G\D9?t$K$J$k>l9g$,B?$$(B. $B$3$N>l9g(B, @code{gr()},
                    885: @code{hgr()} $B$K$h$k7W;;$,6K$a$FM-8z$K$J$k>l9g$,B?$$(B.
1.2       noro      886: \E
                    887: \BEG
                    888: Groebner bases computed by this ordering give the most convenient
                    889: Groebner bases for solving the polynomial equations.
                    890: The only and serious shortcoming is the enormously long computation
                    891: time.
                    892: It is often observed that the number coefficients of the result becomes
                    893: very very long integers, especially if the ideal is 0-dimensional.
                    894: For such a case, it is empirically true for many cases
                    895: that i.e., computation by
                    896: @code{gr()} and/or @code{hgr()} may be quite effective.
                    897: \E
1.1       noro      898: @end table
                    899:
                    900: @noindent
1.2       noro      901: \BJP
1.1       noro      902: $B$3$l$i$rAH$_9g$o$;$F%j%9%H$G;XDj$9$k$3$H$K$h$j(B, $BMM!9$J>C5n=g=x$,;XDj$G$-$k(B.
                    903: $B$3$l$O(B,
1.2       noro      904: \E
                    905: \BEG
                    906: By combining these fundamental orderingl into a list, one can make
                    907: various term ordering called elimination orderings.
                    908: \E
1.1       noro      909:
                    910: @code{[[O1,L1],[O2,L2],...]}
                    911:
                    912: @noindent
1.2       noro      913: \BJP
1.1       noro      914: $B$G;XDj$5$l$k(B. @code{Oi} $B$O(B 0, 1, 2 $B$N$$$:$l$+$G(B, @code{Li} $B$OJQ?t$N8D(B
                    915: $B?t$rI=$9(B. $B$3$N;XDj$O(B, $BJQ?t$r@hF,$+$i(B @code{L1}, @code{L2} , ...$B8D(B
                    916: $B$:$D$NAH$KJ,$1(B, $B$=$l$>$l$NJQ?t$K4X$7(B, $B=g$K(B @code{O1}, @code{O2},
                    917: ...$B$N9`=g=x7?$GBg>.$,7hDj$9$k$^$GHf3S$9$k$3$H$r0UL#$9$k(B. $B$3$N7?$N(B
                    918: $B=g=x$O0lHL$K>C5n=g=x$H8F$P$l$k(B.
1.2       noro      919: \E
                    920: \BEG
                    921: In this example @code{Oi} indicates 0, 1 or 2 and @code{Li} indicates
                    922: the number of variables subject to the correspoinding orderings.
                    923: This specification means the following.
                    924:
                    925: The variable list is separated into sub lists from left to right where
                    926: the @code{i}-th list contains @code{Li} members and it corresponds to
                    927: the ordering of type @code{Oi}. The result of a comparison is equal
                    928: to that for the leftmost different sub components. This type of ordering
                    929: is called an elimination ordering.
                    930: \E
1.1       noro      931:
                    932: @noindent
1.2       noro      933: \BJP
1.1       noro      934: $B$5$i$K(B, $B9TNs$K$h$j9`=g=x$r;XDj$9$k$3$H$,$G$-$k(B. $B0lHL$K(B, @code{n} $B9T(B
                    935: @code{m} $BNs$N<B?t9TNs(B @code{M} $B$,<!$N@-<A$r;}$D$H$9$k(B.
1.2       noro      936: \E
                    937: \BEG
                    938: Furthermore one can specify a term ordering by a matix.
                    939: Suppose that a real @code{n}, @code{m} matrix @code{M} has the
                    940: following properties.
                    941: \E
1.1       noro      942:
                    943: @enumerate
                    944: @item
1.2       noro      945: \JP $BD9$5(B @code{m} $B$N@0?t%Y%/%H%k(B @code{v} $B$KBP$7(B @code{Mv=0} $B$H(B @code{v=0} $B$OF1CM(B.
                    946: \BEG
                    947: For all integer verctors @code{v} of length @code{m} @code{Mv=0} is equivalent
                    948: to @code{v=0}.
                    949: \E
1.1       noro      950:
                    951: @item
1.2       noro      952: \BJP
1.1       noro      953: $BHsIi@.J,$r;}$DD9$5(B @code{m} $B$N(B 0 $B$G$J$$@0?t%Y%/%H%k(B @code{v} $B$KBP$7(B,
                    954: @code{Mv} $B$N(B 0 $B$G$J$$:G=i$N@.J,$OHsIi(B.
1.2       noro      955: \E
                    956: \BEG
                    957: For all non-negative integer vectors @code{v} the first non-zero component
                    958: of @code{Mv} is non-negative.
                    959: \E
1.1       noro      960: @end enumerate
                    961:
                    962: @noindent
1.2       noro      963: \BJP
1.1       noro      964: $B$3$N;~(B, 2 $B$D$N%Y%/%H%k(B @code{t}, @code{s} $B$KBP$7(B,
                    965: @code{t>s} $B$r(B, @code{M(t-s)} $B$N(B 0 $B$G$J$$:G=i$N@.J,$,HsIi(B,
                    966: $B$GDj5A$9$k$3$H$K$h$j9`=g=x$,Dj5A$G$-$k(B.
1.2       noro      967: \E
                    968: \BEG
                    969: Then we can define a term ordering such that, for two vectors
                    970: @code{t}, @code{s}, @code{t>s} means that the first non-zero component
                    971: of @code{M(t-s)} is non-negative.
                    972: \E
1.1       noro      973:
                    974: @noindent
1.2       noro      975: \BJP
1.1       noro      976: $B9`=g=x7?$O(B, @code{gr()} $B$J$I$N0z?t$H$7$F;XDj$5$l$kB>(B, $BAH$_9~$_H!?t(B
                    977: @code{dp_ord()} $B$G;XDj$5$l(B, $B$5$^$6$^$JH!?t$N<B9T$N:]$K;2>H$5$l$k(B.
1.2       noro      978: \E
                    979: \BEG
                    980: Types of term orderings are used as arguments of functions such as
                    981: @code{gr()}. It is also set internally by @code{dp_ord()} and is used
                    982: during executions of various functions.
                    983: \E
1.1       noro      984:
                    985: @noindent
1.2       noro      986: \BJP
1.1       noro      987: $B$3$l$i$N=g=x$N6qBNE*$JDj5A$*$h$S%0%l%V%J4pDl$K4X$9$k99$K>\$7$$2r@b$O(B
                    988: @code{[Becker,Weispfenning]} $B$J$I$r;2>H$N$3$H(B.
1.2       noro      989: \E
                    990: \BEG
                    991: For concrete definitions of term ordering and more information
                    992: about Groebner basis, refer to, for example, the book
                    993: @code{[Becker,Weispfenning]}.
                    994: \E
1.1       noro      995:
                    996: @noindent
1.2       noro      997: \JP $B9`=g=x7?$N@_Dj$NB>$K(B, $BJQ?t$N=g=x<+BN$b7W;;;~4V$KBg$-$J1F6A$rM?$($k(B.
                    998: \BEG
                    999: Note that the variable ordering have strong effects on the computation
                   1000: time as well as the choice of types of term orderings.
                   1001: \E
1.1       noro     1002:
                   1003: @example
                   1004: [90] B=[x^10-t,x^8-z,x^31-x^6-x-y]$
                   1005: [91] gr(B,[x,y,z,t],2);
                   1006: [x^2-2*y^7+(-41*t^2-13*t-1)*y^2+(2*t^17-12*t^14+42*t^12+30*t^11-168*t^9
                   1007: -40*t^8+70*t^7+252*t^6+30*t^5-140*t^4-168*t^3+2*t^2-12*t+16)*z^2*y
                   1008: +(-12*t^16+72*t^13-28*t^11-180*t^10+112*t^8+240*t^7+28*t^6-127*t^5
                   1009: -167*t^4-55*t^3+30*t^2+58*t-15)*z^4,
1.5       noro     1010: (y+t^2*z^2)*x+y^7+(20*t^2+6*t+1)*y^2+(-t^17+6*t^14-21*t^12-15*t^11
                   1011: +84*t^9+20*t^8-35*t^7-126*t^6-15*t^5+70*t^4+84*t^3-t^2+5*t-9)*z^2*y
                   1012: +(6*t^16-36*t^13+14*t^11+90*t^10-56*t^8-120*t^7-14*t^6+64*t^5+84*t^4
                   1013: +27*t^3-16*t^2-30*t+7)*z^4,
                   1014: (t^3-1)*x-y^6+(-6*t^13+24*t^10-20*t^8-36*t^7+40*t^5+24*t^4-6*t^3-20*t^2
                   1015: -6*t-1)*y+(t^17-6*t^14+9*t^12+15*t^11-36*t^9-20*t^8-5*t^7+54*t^6+15*t^5
                   1016: +10*t^4-36*t^3-11*t^2-5*t+9)*z^2,
1.1       noro     1017: -y^8-8*t*y^3+16*z^2*y^2+(-8*t^16+48*t^13-56*t^11-120*t^10+224*t^8+160*t^7
1.5       noro     1018: -56*t^6-336*t^5-112*t^4+112*t^3+224*t^2+24*t-56)*z^4*y+(t^24-8*t^21
                   1019: +20*t^19+28*t^18-120*t^16-56*t^15+14*t^14+300*t^13+70*t^12-56*t^11
                   1020: -400*t^10-84*t^9+84*t^8+268*t^7+84*t^6-56*t^5-63*t^4-36*t^3+46*t^2
                   1021: -12*t+1)*z,2*t*y^5+z*y^2+(-2*t^11+8*t^8-20*t^6-12*t^5+40*t^3+8*t^2
                   1022: -10*t-20)*z^3*y+8*t^14-32*t^11+48*t^8-t^7-32*t^5-6*t^4+9*t^2-t,
1.1       noro     1023: -z*y^3+(t^7-2*t^4+3*t^2+t)*y+(-2*t^6+4*t^3+2*t-2)*z^2,
1.5       noro     1024: 2*t^2*y^3+z^2*y^2+(-2*t^5+4*t^2-6)*z^4*y
                   1025: +(4*t^8-t^7-8*t^5+2*t^4-4*t^3+5*t^2-t)*z,
1.1       noro     1026: z^3*y^2+2*t^3*y+(-t^7+2*t^4+t^2-t)*z^2,
                   1027: -t*z*y^2-2*z^3*y+t^8-2*t^5-t^3+t^2,
1.5       noro     1028: -t^3*y^2-2*t^2*z^2*y+(t^6-2*t^3-t+1)*z^4,z^5-t^4]
1.1       noro     1029: [93] gr(B,[t,z,y,x],2);
                   1030: [x^10-t,x^8-z,x^31-x^6-x-y]
                   1031: @end example
                   1032:
                   1033: @noindent
1.2       noro     1034: \BJP
1.1       noro     1035: $BJQ?t=g=x(B @code{[x,y,z,t]} $B$K$*$1$k%0%l%V%J4pDl$O(B, $B4pDl$N?t$bB?$/(B, $B$=$l$>$l$N(B
                   1036: $B<0$bBg$-$$(B. $B$7$+$7(B, $B=g=x(B @code{[t,z,y,x]} $B$K$b$H$G$O(B, @code{B} $B$,$9$G$K(B
                   1037: $B%0%l%V%J4pDl$H$J$C$F$$$k(B. $BBg;(GD$K$$$($P(B, $B<-=q<0=g=x$G%0%l%V%J4pDl$r5a$a$k(B
                   1038: $B$3$H$O(B, $B:8B&$N(B ($B=g=x$N9b$$(B) $BJQ?t$r(B, $B1&B&$N(B ($B=g=x$NDc$$(B) $BJQ?t$G=q$-I=$9(B
                   1039: $B$3$H$G$"$j(B, $B$3$NNc$N>l9g$O(B, @code{t},  @code{z}, @code{y} $B$,4{$K(B
                   1040: @code{x} $B$GI=$5$l$F$$$k$3$H$+$i$3$N$h$&$J6KC<$J7k2L$H$J$C$?$o$1$G$"$k(B.
                   1041: $B<B:]$K8=$l$k7W;;$K$*$$$F$O(B, $B$3$N$h$&$KA*$V$Y$-JQ?t=g=x$,L@$i$+$G$"$k(B
                   1042: $B$3$H$O>/$J$/(B, $B;n9T:x8m$,I,MW$J>l9g$b$"$k(B.
1.2       noro     1043: \E
                   1044: \BEG
                   1045: As you see in the above example, the Groebner base under variable
                   1046: ordering @code{[x,y,z,t]} has a lot of bases and each base itself is
                   1047: large.  Under variable ordering @code{[t,z,y,x]}, however, @code{B} itself
                   1048: is already the Groebner basis.
                   1049: Roughly speaking, to obtain a Groebner base under the lexicographic
                   1050: ordering is to express the variables on the left (having higher order)
                   1051: in terms of variables on the right (having lower order).
                   1052: In the example, variables @code{t},  @code{z}, and @code{y} are already
                   1053: expressed by variable @code{x}, and the above explanation justifies
                   1054: such a drastic experimental results.
                   1055: In practice, however, optimum ordering for variables may not known
                   1056: beforehand, and some heuristic trial may be inevitable.
1.13      noro     1057: \E
                   1058:
                   1059: \BJP
                   1060: @node Weight ,,, $B%0%l%V%J4pDl$N7W;;(B
                   1061: @section Weight
                   1062: \E
                   1063: \BEG
                   1064: @node Weight,,, Groebner basis computation
                   1065: @section Weight
                   1066: \E
                   1067: \BJP
                   1068: $BA0@a$G>R2p$7$?9`=g=x$O(B, $B3FJQ?t$K(B weight ($B=E$_(B) $B$r@_Dj$9$k$3$H$G(B
                   1069: $B$h$j0lHLE*$J$b$N$H$J$k(B.
                   1070: \E
                   1071: \BEG
1.14      noro     1072: Term orderings introduced in the previous section can be generalized
1.13      noro     1073: by setting a weight for each variable.
                   1074: \E
                   1075: @example
                   1076: [0] dp_td(<<1,1,1>>);
                   1077: 3
                   1078: [1] dp_set_weight([1,2,3])$
                   1079: [2] dp_td(<<1,1,1>>);
                   1080: 6
                   1081: @end example
                   1082: \BJP
                   1083: $BC19`<0$NA4<!?t$r7W;;$9$k:](B, $B%G%U%)%k%H$G$O(B
                   1084: $B3FJQ?t$N;X?t$NOB$rA4<!?t$H$9$k(B. $B$3$l$O3FJQ?t$N(B weight $B$r(B 1 $B$H(B
                   1085: $B9M$($F$$$k$3$H$KAjEv$9$k(B. $B$3$NNc$G$O(B, $BBh0l(B, $BBhFs(B, $BBh;0JQ?t$N(B
                   1086: weight $B$r$=$l$>$l(B 1,2,3 $B$H;XDj$7$F$$$k(B. $B$3$N$?$a(B, @code{<<1,1,1>>}
                   1087: $B$NA4<!?t(B ($B0J2<$G$O$3$l$rC19`<0$N(B weight $B$H8F$V(B) $B$,(B @code{1*1+1*2+1*3=6} $B$H$J$k(B.
                   1088: weight $B$r@_Dj$9$k$3$H$G(B, $BF1$89`=g=x7?$N$b$H$G0[$J$k9`=g=x$,Dj5A$G$-$k(B.
                   1089: $BNc$($P(B, weight $B$r$&$^$/@_Dj$9$k$3$H$G(B, $BB?9`<0$r(B weighted homogeneous
                   1090: $B$K$9$k$3$H$,$G$-$k>l9g$,$"$k(B.
                   1091: \E
                   1092: \BEG
                   1093: By default, the total degree of a monomial is equal to
                   1094: the sum of all exponents. This means that the weight for each variable
                   1095: is set to 1.
                   1096: In this example, the weights for the first, the second and the third
                   1097: variable are set to 1, 2 and 3 respectively.
                   1098: Therefore the total degree of @code{<<1,1,1>>} under this weight,
                   1099: which is called the weight of the monomial, is @code{1*1+1*2+1*3=6}.
1.14      noro     1100: By setting weights, different term orderings can be set under a type of
                   1101: term ordeing. In some case a polynomial can
                   1102: be made weighted homogeneous by setting an appropriate weight.
1.13      noro     1103: \E
                   1104:
                   1105: \BJP
                   1106: $B3FJQ?t$KBP$9$k(B weight $B$r$^$H$a$?$b$N$r(B weight vector $B$H8F$V(B.
                   1107: $B$9$Y$F$N@.J,$,@5$G$"$j(B, $B%0%l%V%J4pDl7W;;$K$*$$$F(B, $BA4<!?t$N(B
                   1108: $BBe$o$j$KMQ$$$i$l$k$b$N$rFC$K(B sugar weight $B$H8F$V$3$H$K$9$k(B.
                   1109: sugar strategy $B$K$*$$$F(B, $BA4<!?t$NBe$o$j$K;H$o$l$k$+$i$G$"$k(B.
                   1110: $B0lJ}$G(B, $B3F@.J,$,I,$:$7$b@5$H$O8B$i$J$$(B weight vector $B$O(B,
                   1111: sugar weight $B$H$7$F@_Dj$9$k$3$H$O$G$-$J$$$,(B, $B9`=g=x$N0lHL2=$K$O(B
                   1112: $BM-MQ$G$"$k(B. $B$3$l$i$O(B, $B9TNs$K$h$k9`=g=x$N@_Dj$K$9$G$K8=$l$F(B
                   1113: $B$$$k(B. $B$9$J$o$A(B, $B9`=g=x$rDj5A$9$k9TNs$N3F9T$,(B, $B0l$D$N(B weight vector
                   1114: $B$H8+$J$5$l$k(B. $B$^$?(B, $B%V%m%C%/=g=x$O(B, $B3F%V%m%C%/$N(B
                   1115: $BJQ?t$KBP1~$9$k@.J,$N$_(B 1 $B$GB>$O(B 0 $B$N(B weight vector $B$K$h$kHf3S$r(B
                   1116: $B:G=i$K9T$C$F$+$i(B, $B3F%V%m%C%/Kh$N(B tie breaking $B$r9T$&$3$H$KAjEv$9$k(B.
                   1117: \E
                   1118:
                   1119: \BEG
                   1120: A list of weights for all variables is called a weight vector.
                   1121: A weight vector is called a sugar weight vector if
                   1122: its elements are all positive and it is used for computing
                   1123: a weighted total degree of a monomial, because such a weight
                   1124: is used instead of total degree in sugar strategy.
                   1125: On the other hand, a weight vector whose elements are not necessarily
                   1126: positive cannot be set as a sugar weight, but it is useful for
                   1127: generalizing term order. In fact, such a weight vector already
                   1128: appeared in a matrix order. That is, each row of a matrix defining
                   1129: a term order is regarded as a weight vector. A block order
                   1130: is also considered as a refinement of comparison by weight vectors.
                   1131: It compares two terms by using a weight vector whose elements
                   1132: corresponding to variables in a block is 1 and 0 otherwise,
                   1133: then it applies a tie breaker.
1.14      noro     1134: \E
                   1135:
                   1136: \BJP
                   1137: weight vector $B$N@_Dj$O(B @code{dp_set_weight()} $B$G9T$&$3$H$,$G$-$k(B
                   1138: $B$,(B, $B9`=g=x$r;XDj$9$k:]$NB>$N%Q%i%a%?(B ($B9`=g=x7?(B, $BJQ?t=g=x(B) $B$H(B
                   1139: $B$^$H$a$F@_Dj$G$-$k$3$H$,K>$^$7$$(B. $B$3$N$?$a(B, $B<!$N$h$&$J7A$G$b(B
                   1140: $B9`=g=x$,;XDj$G$-$k(B.
                   1141: \E
                   1142: \BEG
                   1143: A weight vector can be set by using @code{dp_set_weight()}.
                   1144: However it is more preferable if a weight vector can be set
                   1145: together with other parapmeters such as a type of term ordering
                   1146: and a variable order. This is realized as follows.
                   1147: \E
1.13      noro     1148:
1.14      noro     1149: @example
                   1150: [64] B=[x+y+z-6,x*y+y*z+z*x-11,x*y*z-6]$
                   1151: [65] dp_gr_main(B|v=[x,y,z],sugarweight=[3,2,1],order=0);
                   1152: [z^3-6*z^2+11*z-6,x+y+z-6,-y^2+(-z+6)*y-z^2+6*z-11]
                   1153: [66] dp_gr_main(B|v=[y,z,x],order=[[1,1,0],[0,1,0],[0,0,1]]);
                   1154: [x^3-6*x^2+11*x-6,x+y+z-6,-x^2+(-y+6)*x-y^2+6*y-11]
                   1155: [67] dp_gr_main(B|v=[y,z,x],order=[[x,1,y,2,z,3]]);
                   1156: [x+y+z-6,x^3-6*x^2+11*x-6,-x^2+(-y+6)*x-y^2+6*y-11]
                   1157: @end example
                   1158:
                   1159: \BJP
                   1160: $B$$$:$l$NNc$K$*$$$F$b(B, $B9`=g=x$O(B option $B$H$7$F;XDj$5$l$F$$$k(B.
                   1161: $B:G=i$NNc$G$O(B @code{v} $B$K$h$jJQ?t=g=x$r(B, @code{sugarweight} $B$K$h$j(B
                   1162: sugar weight vector $B$r(B, @code{order}$B$K$h$j9`=g=x7?$r;XDj$7$F$$$k(B.
                   1163: $BFs$DL\$NNc$K$*$1$k(B @code{order} $B$N;XDj$O(B matrix order $B$HF1MM$G$"$k(B.
                   1164: $B$9$J$o$A(B, $B;XDj$5$l$?(B weight vector $B$r:8$+$i=g$K;H$C$F(B weight $B$NHf3S(B
                   1165: $B$r9T$&(B. $B;0$DL\$NNc$bF1MM$G$"$k$,(B, $B$3$3$G$O(B weight vector $B$NMWAG$r(B
                   1166: $BJQ?tKh$K;XDj$7$F$$$k(B. $B;XDj$,$J$$$b$N$O(B 0 $B$H$J$k(B. $B;0$DL\$NNc$G$O(B,
                   1167: @code{order} $B$K$h$k;XDj$G$O9`=g=x$,7hDj$7$J$$(B. $B$3$N>l9g$K$O(B,
                   1168: tie breaker $B$H$7$FA4<!?t5U<-=q<0=g=x$,<+F0E*$K@_Dj$5$l$k(B.
                   1169: $B$3$N;XDjJ}K!$O(B, @code{dp_gr_main}, @code{dp_gr_mod_main} $B$J$I(B
                   1170: $B$NAH$_9~$_4X?t$G$N$_2DG=$G$"$j(B, @code{gr} $B$J$I$N%f!<%6Dj5A4X?t(B
                   1171: $B$G$OL$BP1~$G$"$k(B.
                   1172: \E
                   1173: \BEG
                   1174: In each example, a term ordering is specified as options.
                   1175: In the first example, a variable order, a sugar weight vector
                   1176: and a type of term ordering are specified by options @code{v},
                   1177: @code{sugarweight} and @code{order} respectively.
                   1178: In the second example, an option @code{order} is used
                   1179: to set a matrix ordering. That is, the specified weight vectors
                   1180: are used from left to right for comparing terms.
                   1181: The third example shows a variant of specifying a weight vector,
                   1182: where each component of a weight vector is specified variable by variable,
                   1183: and unspecified components are set to zero. In this example,
                   1184: a term order is not determined only by the specified weight vector.
                   1185: In such a case a tie breaker by the graded reverse lexicographic ordering
                   1186: is set automatically.
                   1187: This type of a term ordering specification can be applied only to builtin
                   1188: functions such as @code{dp_gr_main()}, @code{dp_gr_mod_main()}, not to
                   1189: user defined functions such as @code{gr()}.
1.2       noro     1190: \E
1.1       noro     1191:
1.2       noro     1192: \BJP
1.1       noro     1193: @node $BM-M}<0$r78?t$H$9$k%0%l%V%J4pDl7W;;(B,,, $B%0%l%V%J4pDl$N7W;;(B
                   1194: @section $BM-M}<0$r78?t$H$9$k%0%l%V%J4pDl7W;;(B
1.2       noro     1195: \E
                   1196: \BEG
                   1197: @node Groebner basis computation with rational function coefficients,,, Groebner basis computation
                   1198: @section Groebner basis computation with rational function coefficients
                   1199: \E
1.1       noro     1200:
                   1201: @noindent
1.2       noro     1202: \BJP
1.1       noro     1203: @code{gr()} $B$J$I$N%H%C%W%l%Y%kH!?t$O(B, $B$$$:$l$b(B, $BF~NOB?9`<0%j%9%H$K(B
                   1204: $B8=$l$kJQ?t(B ($BITDj85(B) $B$H(B, $BJQ?t%j%9%H$K8=$l$kJQ?t$rHf3S$7$F(B, $BJQ?t%j%9%H$K(B
                   1205: $B$J$$JQ?t$,F~NOB?9`<0$K8=$l$F$$$k>l9g$K$O(B, $B<+F0E*$K(B, $B$=$NJQ?t$r(B, $B78?t(B
                   1206: $BBN$N85$H$7$F07$&(B.
1.2       noro     1207: \E
                   1208: \BEG
                   1209: Such variables that appear within the input polynomials but
                   1210: not appearing in the input variable list are automatically treated
                   1211: as elements in the coefficient field
                   1212: by top level functions, such as @code{gr()}.
                   1213: \E
1.1       noro     1214:
                   1215: @example
                   1216: [64] gr([a*x+b*y-c,d*x+e*y-f],[x,y],2);
                   1217: [(-e*a+d*b)*x-f*b+e*c,(-e*a+d*b)*y+f*a-d*c]
                   1218: @end example
                   1219:
                   1220: @noindent
1.2       noro     1221: \BJP
1.1       noro     1222: $B$3$NNc$G$O(B, @code{a}, @code{b}, @code{c}, @code{d} $B$,78?tBN$N85$H$7$F(B
                   1223: $B07$o$l$k(B. $B$9$J$o$A(B, $BM-M}H!?tBN(B
                   1224: @b{F} = @b{Q}(@code{a},@code{b},@code{c},@code{d}) $B>e$N(B 2 $BJQ?tB?9`<04D(B
                   1225: @b{F}[@code{x},@code{y}] $B$K$*$1$k%0%l%V%J4pDl$r5a$a$k$3$H$K$J$k(B.
                   1226: $BCm0U$9$Y$-$3$H$O(B,
                   1227: $B78?t$,BN$H$7$F07$o$l$F$$$k$3$H$G$"$k(B. $B$9$J$o$A(B, $B78?t$N4V$KB?9`<0(B
                   1228: $B$H$7$F$N6&DL0x;R$,$"$C$?>l9g$K$O(B, $B7k2L$+$i$=$N0x;R$O=|$+$l$F$$$k(B
                   1229: $B$?$a(B, $BM-M}?tBN>e$NB?9`<04D>e$NLdBj$H$7$F9M$($?>l9g$N7k2L$H$O0lHL(B
                   1230: $B$K$O0[$J$k(B. $B$^$?(B, $B<g$H$7$F7W;;8zN(>e$NLdBj$N$?$a(B, $BJ,;6I=8=B?9`<0(B
                   1231: $B$N78?t$H$7$F<B:]$K5v$5$l$k$N$OB?9`<0$^$G$G$"$k(B. $B$9$J$o$A(B, $BJ,Jl$r(B
                   1232: $B;}$DM-M}<0$OJ,;6I=8=B?9`<0$N78?t$H$7$F$O5v$5$l$J$$(B.
1.2       noro     1233: \E
                   1234: \BEG
                   1235: In this example, variables @code{a}, @code{b}, @code{c}, and @code{d}
                   1236: are treated as elements in the coefficient field.
                   1237: In this case, a Groebner basis is computed
                   1238: on a bi-variate polynomial ring
                   1239: @b{F}[@code{x},@code{y}]
                   1240: over rational function field
                   1241:  @b{F} = @b{Q}(@code{a},@code{b},@code{c},@code{d}).
                   1242: Notice that coefficients are considered as a member in a field.
                   1243: As a consequence, polynomial factors common to the coefficients
                   1244: are removed so that the result, in general, is different from
                   1245: the result that would be obtained when the problem is considered
                   1246: as a computation of Groebner basis over a polynomial ring
                   1247: with rational function coefficients.
                   1248: And note that coefficients of a distributed polynomial are limited
                   1249: to numbers and polynomials because of efficiency.
                   1250: \E
1.1       noro     1251:
1.2       noro     1252: \BJP
1.1       noro     1253: @node $B4pDlJQ49(B,,, $B%0%l%V%J4pDl$N7W;;(B
                   1254: @section $B4pDlJQ49(B
1.2       noro     1255: \E
                   1256: \BEG
                   1257: @node Change of ordering,,, Groebner basis computation
                   1258: @section Change of orderng
                   1259: \E
1.1       noro     1260:
                   1261: @noindent
1.2       noro     1262: \BJP
1.1       noro     1263: $B<-=q<0=g=x$N%0%l%V%J4pDl$r5a$a$k>l9g(B, $BD>@\(B @code{gr()} $B$J$I$r5/F0$9$k(B
                   1264: $B$h$j(B, $B0lC6B>$N=g=x(B ($BNc$($PA4<!?t5U<-=q<0=g=x(B) $B$N%0%l%V%J4pDl$r7W;;$7$F(B,
                   1265: $B$=$l$rF~NO$H$7$F<-=q<0=g=x$N%0%l%V%J4pDl$r7W;;$9$kJ}$,8zN($,$h$$>l9g(B
                   1266: $B$,$"$k(B. $B$^$?(B, $BF~NO$,2?$i$+$N=g=x$G$N%0%l%V%J4pDl$K$J$C$F$$$k>l9g(B, $B4pDl(B
                   1267: $BJQ49$H8F$P$l$kJ}K!$K$h$j(B, Buchberger $B%"%k%4%j%:%`$K$h$i$:$K8zN(NI$/(B
                   1268: $B<-=q<0=g=x$N%0%l%V%J4pDl$,7W;;$G$-$k>l9g$,$"$k(B. $B$3$N$h$&$JL\E*$N$?$a$N(B
                   1269: $BH!?t$,(B, $B%f!<%6Dj5AH!?t$H$7$F(B @samp{gr} $B$K$$$/$D$+Dj5A$5$l$F$$$k(B.
                   1270: $B0J2<$N(B 2 $B$D$NH!?t$O(B, $BJQ?t=g=x(B @var{vlist1}, $B9`=g=x7?(B @var{order} $B$G(B
                   1271: $B4{$K%0%l%V%J4pDl$H$J$C$F$$$kB?9`<0%j%9%H(B @var{gbase} $B$r(B, $BJQ?t=g=x(B
                   1272: @var{vlist2} $B$K$*$1$k<-=q<0=g=x$N%0%l%V%J4pDl$KJQ49$9$kH!?t$G$"$k(B.
1.2       noro     1273: \E
                   1274: \BEG
                   1275: When we compute a lex order Groebner basis, it is often efficient to
                   1276: compute it via Groebner basis with respect to another order such as
                   1277: degree reverse lex order, rather than to compute it directory by
                   1278: @code{gr()} etc. If we know that an input is a Groebner basis with
                   1279: respect to an order, we can apply special methods called change of
                   1280: ordering for a Groebner basis computation with respect to another
                   1281: order, without using Buchberger algorithm. The following two functions
                   1282: are ones for change of ordering such that they convert a Groebner
                   1283: basis @var{gbase} with respect to the variable order @var{vlist1} and
                   1284: the order type @var{order} into a lex Groebner basis with respect
                   1285: to the variable order @var{vlist2}.
                   1286: \E
1.1       noro     1287:
                   1288: @table @code
                   1289: @item tolex(@var{gbase},@var{vlist1},@var{order},@var{vlist2})
                   1290:
1.2       noro     1291: \BJP
1.1       noro     1292: $B$3$NH!?t$O(B, @var{gbase} $B$,M-M}?tBN>e$N%7%9%F%`$N>l9g$K$N$_;HMQ2DG=$G$"$k(B.
                   1293: $B$3$NH!?t$O(B, $B<-=q<0=g=x$N%0%l%V%J4pDl$r(B, $BM-8BBN>e$G7W;;$5$l$?%0%l%V%J4pDl(B
                   1294: $B$r?w7?$H$7$F(B, $BL$Dj78?tK!$*$h$S(B Hensel $B9=@.$K$h$j5a$a$k$b$N$G$"$k(B.
1.2       noro     1295: \E
                   1296: \BEG
                   1297: This function can be used only when @var{gbase} is an ideal over the
                   1298: rationals.  The input @var{gbase} must be a Groebner basis with respect
                   1299: to the variable order @var{vlist1} and the order type @var{order}. Moreover
                   1300: the ideal generated by @var{gbase} must be zero-dimensional.
                   1301: This computes the lex Groebner basis of @var{gbase}
                   1302: by using the modular change of ordering algorithm. The algorithm first
                   1303: computes the lex Groebner basis over a finite field. Then each element
                   1304: in the lex Groebner basis over the rationals is computed with undetermined
                   1305: coefficient method and linear equation solving by Hensel lifting.
                   1306: \E
1.1       noro     1307:
                   1308: @item tolex_tl(@var{gbase},@var{vlist1},@var{order},@var{vlist2},@var{homo})
                   1309:
1.2       noro     1310: \BJP
1.1       noro     1311: $B$3$NH!?t$O(B, $B<-=q<0=g=x$N%0%l%V%J4pDl$r(B Buchberger $B%"%k%4%j%:%`$K$h$j5a(B
                   1312: $B$a$k$b$N$G$"$k$,(B, $BF~NO$,$"$k=g=x$K$*$1$k%0%l%V%J4pDl$G$"$k>l9g$N(B
                   1313: trace-lifting$B$K$*$1$k%0%l%V%J4pDl8uJd$NF,9`(B, $BF,78?t$N@-<A$rMxMQ$7$F(B,
                   1314: $B:G=*E*$J%0%l%V%J4pDl%A%'%C%/(B, $B%$%G%"%k%a%s%P%7%C%W%A%'%C%/$r>JN,$7$F$$(B
                   1315: $B$k$?$a(B, $BC1$K(BBuchberger $B%"%k%4%j%:%`$r7+$jJV$9$h$j8zN($h$/7W;;$G$-$k(B.
                   1316: $B99$K(B, $BF~NO$,(B 0 $B<!85%7%9%F%`$N>l9g(B, $B<+F0E*$K$b$&(B 1 $B$D$NCf4VE*$J9`=g=x$r(B
                   1317: $B7PM3$7$F<-=q<0=g=x$N%0%l%V%J4pDl$r7W;;$9$k(B. $BB?$/$N>l9g(B, $B$3$NJ}K!$O(B,
                   1318: $BD>@\<-=q<0=g=x$N7W;;$r9T$&$h$j8zN($,$h$$(B. ($B$b$A$m$sNc30$"$j(B. )
                   1319: $B0z?t(B @var{homo} $B$,(B 0 $B$G$J$$;~(B, @code{hgr()} $B$HF1MM$K@F<!2=$r7PM3$7$F(B
                   1320: $B7W;;$r9T$&(B.
1.2       noro     1321: \E
                   1322: \BEG
                   1323: This function computes the lex Groebner basis of @var{gbase}.  The
                   1324: input @var{gbase} must be a Groebner basis with respect to the
                   1325: variable order @var{vlist1} and the order type @var{order}.
                   1326: Buchberger algorithm with trace lifting is used to compute the lex
                   1327: Groebner basis, however the Groebner basis check and the ideal
                   1328: membership check can be omitted by using several properties derived
                   1329: from the fact that the input is a Groebner basis. So it is more
                   1330: efficient than simple repetition of Buchberger algorithm. If the input
                   1331: is zero-dimensional, this function inserts automatically a computation
                   1332: of Groebner basis with respect to an elimination order, which makes
                   1333: the whole computation more efficient for many cases. If @var{homo} is
                   1334: not equal to 0, homogenization is used in each step.
                   1335: \E
1.1       noro     1336: @end table
                   1337:
                   1338: @noindent
1.2       noro     1339: \BJP
1.1       noro     1340: $B$=$NB>(B, 0 $B<!85%7%9%F%`$KBP$7(B, $BM?$($i$l$?B?9`<0$N:G>.B?9`<0$r5a$a$k(B
                   1341: $BH!?t(B, 0 $B<!85%7%9%F%`$N2r$r(B, $B$h$j%3%s%Q%/%H$KI=8=$9$k$?$a$NH!?t$J$I$,(B
                   1342: @samp{gr} $B$GDj5A$5$l$F$$$k(B. $B$3$l$i$K$D$$$F$O8D!9$NH!?t$N@bL@$r;2>H$N$3$H(B.
1.2       noro     1343: \E
                   1344: \BEG
                   1345: For zero-dimensional systems, there are several fuctions to
                   1346: compute the minimal polynomial of a polynomial and or a more compact
                   1347: representation for zeros of the system. They are all defined in @samp{gr}.
                   1348: Refer to the sections for each functions.
                   1349: \E
1.1       noro     1350:
1.2       noro     1351: \BJP
1.6       noro     1352: @node Weyl $BBe?t(B,,, $B%0%l%V%J4pDl$N7W;;(B
                   1353: @section Weyl $BBe?t(B
                   1354: \E
                   1355: \BEG
                   1356: @node Weyl algebra,,, Groebner basis computation
                   1357: @section Weyl algebra
                   1358: \E
                   1359:
                   1360: @noindent
                   1361:
                   1362: \BJP
                   1363: $B$3$l$^$G$O(B, $BDL>o$N2D49$JB?9`<04D$K$*$1$k%0%l%V%J4pDl7W;;$K$D$$$F(B
                   1364: $B=R$Y$F$-$?$,(B, $B%0%l%V%J4pDl$NM}O@$O(B, $B$"$k>r7o$rK~$?$9Hs2D49$J(B
                   1365: $B4D$K$b3HD%$G$-$k(B. $B$3$N$h$&$J4D$NCf$G(B, $B1~MQ>e$b=EMW$J(B,
                   1366: Weyl $BBe?t(B, $B$9$J$o$AB?9`<04D>e$NHyJ,:nMQAG4D$N1i;;$*$h$S(B
                   1367: $B%0%l%V%J4pDl7W;;$,(B Risa/Asir $B$K<BAu$5$l$F$$$k(B.
                   1368:
                   1369: $BBN(B @code{K} $B>e$N(B @code{n} $B<!85(B Weyl $BBe?t(B
                   1370: @code{D=K<x1,@dots{},xn,D1,@dots{},Dn>} $B$O(B
                   1371: \E
                   1372:
                   1373: \BEG
                   1374: So far we have explained Groebner basis computation in
                   1375: commutative polynomial rings. However Groebner basis can be
                   1376: considered in more general non-commutative rings.
                   1377: Weyl algebra is one of such rings and
                   1378: Risa/Asir implements fundamental operations
                   1379: in Weyl algebra and Groebner basis computation in Weyl algebra.
                   1380:
                   1381: The @code{n} dimensional Weyl algebra over a field @code{K},
                   1382: @code{D=K<x1,@dots{},xn,D1,@dots{},Dn>} is a non-commutative
                   1383: algebra which has the following fundamental relations:
                   1384: \E
                   1385:
                   1386: @code{xi*xj-xj*xi=0}, @code{Di*Dj-Dj*Di=0}, @code{Di*xj-xj*Di=0} (@code{i!=j}),
                   1387: @code{Di*xi-xi*Di=1}
                   1388:
                   1389: \BJP
                   1390: $B$H$$$&4pK\4X78$r;}$D4D$G$"$k(B. @code{D} $B$O(B $BB?9`<04D(B @code{K[x1,@dots{},xn]} $B$r78?t(B
                   1391: $B$H$9$kHyJ,:nMQAG4D$G(B,  @code{Di} $B$O(B @code{xi} $B$K$h$kHyJ,$rI=$9(B. $B8r494X78$K$h$j(B,
                   1392: @code{D} $B$N85$O(B, @code{x1^i1*@dots{}*xn^in*D1^j1*@dots{}*Dn^jn} $B$J$kC19`(B
                   1393: $B<0$N(B @code{K} $B@~7A7k9g$H$7$F=q$-I=$9$3$H$,$G$-$k(B.
                   1394: Risa/Asir $B$K$*$$$F$O(B, $B$3$NC19`<0$r(B, $B2D49$JB?9`<0$HF1MM$K(B
                   1395: @code{<<i1,@dots{},in,j1,@dots{},jn>>} $B$GI=$9(B. $B$9$J$o$A(B, @code{D} $B$N85$b(B
                   1396: $BJ,;6I=8=B?9`<0$H$7$FI=$5$l$k(B. $B2C8:;;$O(B, $B2D49$N>l9g$HF1MM$K(B, @code{+}, @code{-}
                   1397: $B$K$h$j(B
                   1398: $B<B9T$G$-$k$,(B, $B>h;;$O(B, $BHs2D49@-$r9MN8$7$F(B @code{dp_weyl_mul()} $B$H$$$&4X?t(B
                   1399: $B$K$h$j<B9T$9$k(B.
                   1400: \E
                   1401:
                   1402: \BEG
                   1403: @code{D} is the ring of differential operators whose coefficients
                   1404: are polynomials in @code{K[x1,@dots{},xn]} and
                   1405: @code{Di} denotes the differentiation with respect to  @code{xi}.
                   1406: According to the commutation relation,
                   1407: elements of @code{D} can be represented as a @code{K}-linear combination
                   1408: of monomials @code{x1^i1*@dots{}*xn^in*D1^j1*@dots{}*Dn^jn}.
                   1409: In Risa/Asir, this type of monomial is represented
                   1410: by @code{<<i1,@dots{},in,j1,@dots{},jn>>} as in the case of commutative
                   1411: polynomial.
                   1412: That is, elements of @code{D} are represented by distributed polynomials.
                   1413: Addition and subtraction can be done by @code{+}, @code{-},
                   1414: but multiplication is done by calling @code{dp_weyl_mul()} because of
                   1415: the non-commutativity of @code{D}.
                   1416: \E
                   1417:
                   1418: @example
                   1419: [0] A=<<1,2,2,1>>;
                   1420: (1)*<<1,2,2,1>>
                   1421: [1] B=<<2,1,1,2>>;
                   1422: (1)*<<2,1,1,2>>
                   1423: [2] A*B;
                   1424: (1)*<<3,3,3,3>>
                   1425: [3] dp_weyl_mul(A,B);
                   1426: (1)*<<3,3,3,3>>+(1)*<<3,2,3,2>>+(4)*<<2,3,2,3>>+(4)*<<2,2,2,2>>
                   1427: +(2)*<<1,3,1,3>>+(2)*<<1,2,1,2>>
                   1428: @end example
                   1429:
                   1430: \BJP
                   1431: $B%0%l%V%J4pDl7W;;$K$D$$$F$b(B, Weyl $BBe?t@lMQ$N4X?t$H$7$F(B,
                   1432: $B<!$N4X?t$,MQ0U$7$F$"$k(B.
                   1433: \E
                   1434: \BEG
                   1435: The following functions are avilable for Groebner basis computation
                   1436: in Weyl algebra:
                   1437: \E
                   1438: @code{dp_weyl_gr_main()},
                   1439: @code{dp_weyl_gr_mod_main()},
                   1440: @code{dp_weyl_gr_f_main()},
                   1441: @code{dp_weyl_f4_main()},
                   1442: @code{dp_weyl_f4_mod_main()}.
                   1443: \BJP
                   1444: $B$^$?(B, $B1~MQ$H$7$F(B, global b $B4X?t$N7W;;$,<BAu$5$l$F$$$k(B.
                   1445: \E
                   1446: \BEG
                   1447: Computation of the global b function is implemented as an application.
                   1448: \E
                   1449:
                   1450: \BJP
1.1       noro     1451: @node $B%0%l%V%J4pDl$K4X$9$kH!?t(B,,, $B%0%l%V%J4pDl$N7W;;(B
                   1452: @section $B%0%l%V%J4pDl$K4X$9$kH!?t(B
1.2       noro     1453: \E
                   1454: \BEG
                   1455: @node Functions for Groebner basis computation,,, Groebner basis computation
                   1456: @section Functions for Groebner basis computation
                   1457: \E
1.1       noro     1458:
                   1459: @menu
                   1460: * gr hgr gr_mod::
                   1461: * lex_hensel lex_tl tolex tolex_d tolex_tl::
                   1462: * lex_hensel_gsl tolex_gsl tolex_gsl_d::
                   1463: * gr_minipoly minipoly::
                   1464: * tolexm minipolym::
1.6       noro     1465: * dp_gr_main dp_gr_mod_main dp_gr_f_main dp_weyl_gr_main dp_weyl_gr_mod_main dp_weyl_gr_f_main::
                   1466: * dp_f4_main dp_f4_mod_main dp_weyl_f4_main dp_weyl_f4_mod_main::
1.17      noro     1467: * nd_gr nd_gr_trace nd_f4 nd_f4_trace nd_weyl_gr nd_weyl_gr_trace::
1.1       noro     1468: * dp_gr_flags dp_gr_print::
                   1469: * dp_ord::
1.18    ! noro     1470: * dp_set_weight dp_set_top_weight dp_weyl_set_weight::
1.1       noro     1471: * dp_ptod::
                   1472: * dp_dtop::
                   1473: * dp_mod dp_rat::
                   1474: * dp_homo dp_dehomo::
                   1475: * dp_ptozp dp_prim::
1.18    ! noro     1476: * dp_nf dp_nf_mod dp_true_nf dp_true_nf_mod dp_weyl_nf dp_weyl_nf_mod::
1.1       noro     1477: * dp_hm dp_ht dp_hc dp_rest::
                   1478: * dp_td dp_sugar::
                   1479: * dp_lcm::
                   1480: * dp_redble::
                   1481: * dp_subd::
                   1482: * dp_mbase::
                   1483: * dp_mag::
                   1484: * dp_red dp_red_mod::
                   1485: * dp_sp dp_sp_mod::
                   1486: * p_nf p_nf_mod p_true_nf p_true_nf_mod ::
                   1487: * p_terms::
                   1488: * gb_comp::
                   1489: * katsura hkatsura cyclic hcyclic::
                   1490: * dp_vtoe dp_etov::
                   1491: * lex_hensel_gsl tolex_gsl tolex_gsl_d::
1.3       noro     1492: * primadec primedec::
1.5       noro     1493: * primedec_mod::
1.10      noro     1494: * bfunction bfct generic_bfct ann ann0::
1.1       noro     1495: @end menu
                   1496:
1.2       noro     1497: \JP @node gr hgr gr_mod,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   1498: \EG @node gr hgr gr_mod,,, Functions for Groebner basis computation
1.1       noro     1499: @subsection @code{gr}, @code{hgr}, @code{gr_mod}, @code{dgr}
                   1500: @findex gr
                   1501: @findex hgr
                   1502: @findex gr_mod
                   1503: @findex dgr
                   1504:
                   1505: @table @t
                   1506: @item gr(@var{plist},@var{vlist},@var{order})
                   1507: @itemx hgr(@var{plist},@var{vlist},@var{order})
                   1508: @itemx gr_mod(@var{plist},@var{vlist},@var{order},@var{p})
                   1509: @itemx dgr(@var{plist},@var{vlist},@var{order},@var{procs})
1.2       noro     1510: \JP :: $B%0%l%V%J4pDl$N7W;;(B
                   1511: \EG :: Groebner basis computation
1.1       noro     1512: @end table
                   1513:
                   1514: @table @var
                   1515: @item return
1.2       noro     1516: \JP $B%j%9%H(B
                   1517: \EG list
1.4       noro     1518: @item plist  vlist  procs
1.2       noro     1519: \JP $B%j%9%H(B
                   1520: \EG list
1.1       noro     1521: @item order
1.2       noro     1522: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   1523: \EG number, list or matrix
1.1       noro     1524: @item p
1.2       noro     1525: \JP 2^27 $BL$K~$NAG?t(B
                   1526: \EG prime less than 2^27
1.1       noro     1527: @end table
                   1528:
                   1529: @itemize @bullet
1.2       noro     1530: \BJP
1.1       noro     1531: @item
                   1532: $BI8=`%i%$%V%i%j$N(B @samp{gr} $B$GDj5A$5$l$F$$$k(B.
                   1533: @item
                   1534: $B$$$:$l$b(B, $BB?9`<0%j%9%H(B @var{plist} $B$N(B, $BJQ?t=g=x(B @var{vlist}, $B9`=g=x7?(B
                   1535: @var{order} $B$K4X$9$k%0%l%V%J4pDl$r5a$a$k(B. @code{gr()}, @code{hgr()}
                   1536: $B$O(B $BM-M}?t78?t(B, @code{gr_mod()} $B$O(B GF(@var{p}) $B78?t$H$7$F7W;;$9$k(B.
                   1537: @item
                   1538: @var{vlist} $B$OITDj85$N%j%9%H(B. @var{vlist} $B$K8=$l$J$$ITDj85$O(B,
                   1539: $B78?tBN$KB0$9$k$H8+$J$5$l$k(B.
                   1540: @item
                   1541: @code{gr()}, trace-lifting ($B%b%8%e%i1i;;$rMQ$$$?9bB.2=(B) $B$*$h$S(B sugar
                   1542: strategy $B$K$h$k7W;;(B, @code{hgr()} $B$O(B trace-lifting $B$*$h$S(B
                   1543: $B@F<!2=$K$h$k(B $B6:@5$5$l$?(B sugar strategy $B$K$h$k7W;;$r9T$&(B.
                   1544: @item
1.16      fujiwara 1545: @code{dgr()} $B$O(B, @code{gr()}, @code{hgr()} $B$r(B
1.1       noro     1546: $B;R%W%m%;%9%j%9%H(B @var{procs} $B$N(B 2 $B$D$N%W%m%;%9$K$h$jF1;~$K7W;;$5$;(B,
                   1547: $B@h$K7k2L$rJV$7$?J}$N7k2L$rJV$9(B. $B7k2L$OF10l$G$"$k$,(B, $B$I$A$i$NJ}K!$,(B
                   1548: $B9bB.$+0lHL$K$OITL@$N$?$a(B, $B<B:]$N7P2a;~4V$rC;=L$9$k$N$KM-8z$G$"$k(B.
                   1549: @item
                   1550: @code{dgr()} $B$GI=<($5$l$k;~4V$O(B, $B$3$NH!?t$,<B9T$5$l$F$$$k%W%m%;%9$G$N(B
                   1551: CPU $B;~4V$G$"$j(B, $B$3$NH!?t$N>l9g$O$[$H$s$IDL?.$N$?$a$N;~4V$G$"$k(B.
1.12      takayama 1552: @item
                   1553: $BB?9`<0%j%9%H(B @var{plist} $B$NMWAG$,J,;6I=8=B?9`<0$N>l9g$O(B
                   1554: $B7k2L$bJ,;6I=8=B?9`<0$N%j%9%H$G$"$k(B.
                   1555: $B$3$N>l9g(B, $B0z?t$NJ,;6B?9`<0$OM?$($i$l$?=g=x$K=>$$(B @code{dp_sort} $B$G(B
                   1556: $B%=!<%H$5$l$F$+$i7W;;$5$l$k(B.
                   1557: $BB?9`<0%j%9%H$NMWAG$,J,;6I=8=B?9`<0$N>l9g$b(B
                   1558: $BJQ?t$N?tJ,$NITDj85$N%j%9%H$r(B @var{vlist} $B0z?t$H$7$FM?$($J$$$H$$$1$J$$(B
                   1559: ($B%@%_!<(B).
1.2       noro     1560: \E
                   1561: \BEG
                   1562: @item
                   1563: These functions are defined in @samp{gr} in the standard library
                   1564: directory.
                   1565: @item
                   1566: They compute a Groebner basis of a polynomial list @var{plist} with
                   1567: respect to the variable order @var{vlist} and the order type @var{order}.
                   1568: @code{gr()} and @code{hgr()} compute a Groebner basis over the rationals
                   1569: and @code{gr_mod} computes over GF(@var{p}).
                   1570: @item
                   1571: Variables not included in @var{vlist} are regarded as
                   1572: included in the ground field.
                   1573: @item
                   1574: @code{gr()} uses trace-lifting (an improvement by modular computation)
                   1575:  and sugar strategy.
                   1576: @code{hgr()} uses trace-lifting and a cured sugar strategy
                   1577: by using homogenization.
                   1578: @item
                   1579: @code{dgr()} executes @code{gr()}, @code{dgr()} simultaneously on
                   1580: two process in a child process list @var{procs} and returns
                   1581: the result obtained first. The results returned from both the process
                   1582: should be equal, but it is not known in advance which method is faster.
                   1583: Therefore this function is useful to reduce the actual elapsed time.
                   1584: @item
                   1585: The CPU time shown after an exection of @code{dgr()} indicates
                   1586: that of the master process, and most of the time corresponds to the time
                   1587: for communication.
1.12      takayama 1588: @item
                   1589: When the elements of @var{plist} are distributed polynomials,
                   1590: the result is also a list of distributed polynomials.
                   1591: In this case, firstly  the elements of @var{plist} is sorted by @code{dp_sort}
                   1592: and the Grobner basis computation is started.
                   1593: Variables must be given in @var{vlist} even in this case
                   1594: (these variables are dummy).
1.2       noro     1595: \E
1.1       noro     1596: @end itemize
                   1597:
                   1598: @example
                   1599: [0] load("gr")$
                   1600: [64] load("cyclic")$
                   1601: [74] G=gr(cyclic(5),[c0,c1,c2,c3,c4],2);
                   1602: [c4^15+122*c4^10-122*c4^5-1,...]
                   1603: [75] GM=gr_mod(cyclic(5),[c0,c1,c2,c3,c4],2,31991)$
                   1604: 24628*c4^15+29453*c4^10+2538*c4^5+7363
                   1605: [76] (G[0]*24628-GM[0])%31991;
                   1606: 0
                   1607: @end example
                   1608:
                   1609: @table @t
1.2       noro     1610: \JP @item $B;2>H(B
                   1611: \EG @item References
1.6       noro     1612: @fref{dp_gr_main dp_gr_mod_main dp_gr_f_main dp_weyl_gr_main dp_weyl_gr_mod_main dp_weyl_gr_f_main},
1.1       noro     1613: @fref{dp_ord}.
                   1614: @end table
                   1615:
1.2       noro     1616: \JP @node lex_hensel lex_tl tolex tolex_d tolex_tl,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   1617: \EG @node lex_hensel lex_tl tolex tolex_d tolex_tl,,, Functions for Groebner basis computation
1.1       noro     1618: @subsection @code{lex_hensel}, @code{lex_tl}, @code{tolex}, @code{tolex_d}, @code{tolex_tl}
                   1619: @findex lex_hensel
                   1620: @findex lex_tl
                   1621: @findex tolex
                   1622: @findex tolex_d
                   1623: @findex tolex_tl
                   1624:
                   1625: @table @t
                   1626: @item lex_hensel(@var{plist},@var{vlist1},@var{order},@var{vlist2},@var{homo})
                   1627: @itemx lex_tl(@var{plist},@var{vlist1},@var{order},@var{vlist2},@var{homo})
1.2       noro     1628: \JP :: $B4pDlJQ49$K$h$k<-=q<0=g=x%0%l%V%J4pDl$N7W;;(B
                   1629: \EG:: Groebner basis computation with respect to a lex order by change of ordering
1.1       noro     1630: @item tolex(@var{plist},@var{vlist1},@var{order},@var{vlist2})
                   1631: @itemx tolex_d(@var{plist},@var{vlist1},@var{order},@var{vlist2},@var{procs})
                   1632: @itemx tolex_tl(@var{plist},@var{vlist1},@var{order},@var{vlist2},@var{homo})
1.2       noro     1633: \JP :: $B%0%l%V%J4pDl$rF~NO$H$9$k(B, $B4pDlJQ49$K$h$k<-=q<0=g=x%0%l%V%J4pDl$N7W;;(B
                   1634: \EG :: Groebner basis computation with respect to a lex order by change of ordering, starting from a Groebner basis
1.1       noro     1635: @end table
                   1636:
                   1637: @table @var
                   1638: @item return
1.2       noro     1639: \JP $B%j%9%H(B
                   1640: \EG list
1.4       noro     1641: @item plist  vlist1  vlist2  procs
1.2       noro     1642: \JP $B%j%9%H(B
                   1643: \EG list
1.1       noro     1644: @item order
1.2       noro     1645: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   1646: \EG number, list or matrix
1.1       noro     1647: @item homo
1.2       noro     1648: \JP $B%U%i%0(B
                   1649: \EG flag
1.1       noro     1650: @end table
                   1651:
                   1652: @itemize @bullet
1.2       noro     1653: \BJP
1.1       noro     1654: @item
                   1655: $BI8=`%i%$%V%i%j$N(B @samp{gr} $B$GDj5A$5$l$F$$$k(B.
                   1656: @item
                   1657: @code{lex_hensel()}, @code{lex_tl()} $B$O(B,
                   1658: $BB?9`<0%j%9%H(B @var{plist} $B$N(B, $BJQ?t=g=x(B @var{vlist1}, $B9`=g=x7?(B
                   1659: @var{order} $B$K4X$9$k%0%l%V%J4pDl$r5a$a(B, $B$=$l$r(B, $BJQ?t=g=x(B @var{vlist2}
                   1660: $B$N<-=q<0=g=x%0%l%V%J4pDl$KJQ49$9$k(B.
                   1661: @item
                   1662: @code{tolex()}, @code{tolex_tl()} $B$O(B,
                   1663: $BJQ?t=g=x(B @var{vlist1}, $B9`=g=x7?(B @var{order} $B$K4X$9$k%0%l%V%J4pDl$G$"$k(B
                   1664: $BB?9`<0%j%9%H(B @var{plist} $B$rJQ?t=g=x(B @var{vlist2} $B$N<-=q<0=g=x%0%l%V%J(B
                   1665: $B4pDl$KJQ49$9$k(B.
                   1666: @code{tolex_d()} $B$O(B, @code{tolex()} $B$K$*$1$k(B, $B3F4pDl$N7W;;$r(B, $B;R%W%m%;%9(B
                   1667: $B%j%9%H(B @var{procs} $B$N3F%W%m%;%9$KJ,;67W;;$5$;$k(B.
                   1668: @item
                   1669: @code{lex_hensel()}, @code{lex_tl()} $B$K$*$$$F$O(B, $B<-=q<0=g=x%0%l%V%J4pDl$N(B
                   1670: $B7W;;$O<!$N$h$&$K9T$o$l$k(B. (@code{[Noro,Yokoyama]} $B;2>H(B.)
                   1671: @enumerate
                   1672: @item
                   1673: @var{vlist1}, @var{order} $B$K4X$9$k%0%l%V%J4pDl(B @var{G0} $B$r7W;;$9$k(B.
                   1674: (@code{lex_hensel()} $B$N$_(B. )
                   1675: @item
                   1676: @var{G0} $B$N3F85$N(B @var{vlist2} $B$K4X$9$k<-=q<0=g=x$K$*$1$kF,78?t$r3d$i$J$$(B
                   1677: $B$h$&$JAG?t(B @var{p} $B$rA*$S(B, GF(@var{p}) $B>e$G$N<-=q<0=g=x%0%l%V%J4pDl(B
                   1678: @var{Gp} $B$r7W;;$9$k(B.
                   1679: @item
                   1680: @var{Gp} $B$K8=$l$k$9$Y$F$N9`$N(B, @var{G0} $B$K4X$9$k@55,7A(B @var{NF} $B$r7W;;$9$k(B.
                   1681: @item
                   1682: @var{Gp} $B$N3F85(B @var{f} $B$K$D$-(B, @var{f} $B$N78?t$rL$Dj78?t$G(B,
                   1683: @var{f} $B$N3F9`$rBP1~$9$k(B @var{NF} $B$N85$GCV$-49$((B, $B3F9`$N78?t$r(B 0 $B$HCV$$$?(B,
                   1684: $BL$Dj78?t$K4X$9$k@~7AJ}Dx<07O(B @var{Lf} $B$r:n$k(B.
                   1685: @item
                   1686: @var{Lf} $B$,(B, $BK!(B @var{p} $B$G0l0U2r$r;}$D$3$H$rMQ$$$F(B @var{Lf} $B$N2r$r(B
                   1687: $BK!(B @var{p}$B$N2r$+$i(B Hensel $B9=@.$K$h$j5a$a$k(B.
                   1688: @item
                   1689: $B$9$Y$F$N(B @var{Gp} $B$N85$K$D$-@~7AJ}Dx<0$,2r$1$?$i$=$N2rA4BN$,5a$a$k(B
                   1690: $B<-=q<0=g=x$G$N%0%l%V%J4pDl(B. $B$b$7$I$l$+$N@~7AJ}Dx<0$N5a2r$K<:GT$7$?$i(B,
                   1691: @var{p} $B$r$H$jD>$7$F$d$jD>$9(B.
                   1692: @end enumerate
                   1693:
                   1694: @item
                   1695: @code{lex_tl()}, @code{tolex_tl()} $B$K$*$$$F$O(B, $B<-=q<0=g=x%0%l%V%J4pDl$N(B
                   1696: $B7W;;$O<!$N$h$&$K9T$o$l$k(B.
                   1697:
                   1698: @enumerate
                   1699: @item
                   1700: @var{vlist1}, @var{order} $B$K4X$9$k%0%l%V%J4pDl(B @var{G0} $B$r7W;;$9$k(B.
                   1701: (@code{lex_hensel()} $B$N$_(B. )
                   1702: @item
                   1703: @var{G0} $B$,(B 0 $B<!85%7%9%F%`$G$J$$$H$-(B, @var{G0} $B$rF~NO$H$7$F(B,
                   1704: @var{G0} $B$N3F85$N(B @var{vlist2} $B$K4X$9$k<-=q<0=g=x$K$*$1$kF,78?t$r3d$i$J$$(B
                   1705: $B$h$&$JAG?t(B @var{p} $B$rA*$S(B, @var{p} $B$rMQ$$$?(B trace-lifting $B$K$h$j<-=q<0(B
                   1706: $B=g=x$N%0%l%V%J4pDl8uJd$r5a$a(B, $B$b$75a$^$C$?$J$i%A%'%C%/$J$7$K$=$l$,5a$a$k(B
                   1707: $B%0%l%V%J4pDl$H$J$k(B. $B$b$7<:GT$7$?$i(B, @var{p} $B$r$H$jD>$7$F$d$jD>$9(B.
                   1708: @item
                   1709: @var{G0} $B$,(B 0 $B<!85%7%9%F%`$N$H$-(B, @var{G0} $B$rF~NO$H$7$F(B,
                   1710: $B$^$:(B, @var{vlist2} $B$N:G8e$NJQ?t0J30$r>C5n$9$k>C5n=g=x$K$h$j(B
                   1711: $B%0%l%V%J4pDl(B @var{G1} $B$r7W;;$7(B, $B$=$l$+$i<-=q<0=g=x$N%0%l%V%J4pDl$r(B
                   1712: $B7W;;$9$k(B. $B$=$N:](B, $B3F%9%F%C%W$G$O(B, $BF~NO$N3F85$N(B, $B5a$a$k=g=x$K$*$1$k(B
                   1713: $BF,78?t$r3d$i$J$$AG?t$rMQ$$$?(B trace-lifting $B$G%0%l%V%J4pDl8uJd$r5a$a(B,
                   1714: $B$b$75a$^$C$?$i%A%'%C%/$J$7$K$=$l$,$=$N=g=x$G$N%0%l%V%J4pDl$H$J$k(B.
                   1715: @end enumerate
                   1716:
                   1717: @item
                   1718: $BM-M}<078?t$N7W;;$O(B, @code{lex_tl()}, @code{tolex_tl()} $B$N$_<u$1IU$1$k(B.
                   1719: @item
                   1720: @code{homo} $B$,(B 0 $B$G$J$$>l9g(B, $BFbIt$G5/F0$5$l$k(B Buchberger $B%"%k%4%j%:%`$K(B
                   1721: $B$*$$$F(B, $B@F<!2=$,9T$o$l$k(B.
                   1722: @item
                   1723: @code{tolex_d()} $B$GI=<($5$l$k;~4V$O(B, $B$3$NH!?t$,<B9T$5$l$F$$$k%W%m%;%9$K(B
                   1724: $B$*$$$F9T$o$l$?7W;;$KBP1~$7$F$$$F(B, $B;R%W%m%;%9$K$*$1$k;~4V$O4^$^$l$J$$(B.
1.2       noro     1725: \E
                   1726: \BEG
                   1727: @item
                   1728: These functions are defined in @samp{gr} in the standard library
                   1729: directory.
                   1730: @item
                   1731: @code{lex_hensel()} and @code{lex_tl()} first compute a Groebner basis
                   1732: with respect to the variable order @var{vlist1} and the order type @var{order}.
                   1733: Then the Groebner basis is converted into a lex order Groebner basis
                   1734: with respect to the varable order @var{vlist2}.
                   1735: @item
                   1736: @code{tolex()} and @code{tolex_tl()} convert a Groebner basis @var{plist}
                   1737: with respect to the variable order @var{vlist1} and the order type @var{order}
                   1738: into a lex order Groebner basis
                   1739: with respect to the varable order @var{vlist2}.
                   1740: @code{tolex_d()} does computations of basis elements in @code{tolex()}
                   1741: in parallel on the processes in a child process list @var{procs}.
                   1742: @item
                   1743: In @code{lex_hensel()} and @code{tolex_hensel()} a lex order Groebner basis
                   1744: is computed as follows.(Refer to @code{[Noro,Yokoyama]}.)
                   1745: @enumerate
                   1746: @item
                   1747: Compute a Groebner basis @var{G0} with respect to @var{vlist1} and @var{order}.
                   1748: (Only in @code{lex_hensel()}. )
                   1749: @item
                   1750: Choose a prime which does not divide head coefficients of elements in @var{G0}
                   1751: with respect to @var{vlist1} and @var{order}. Then compute a lex order
                   1752: Groebner basis @var{Gp} over GF(@var{p}) with respect to @var{vlist2}.
                   1753: @item
                   1754: Compute @var{NF}, the set of all the normal forms with respect to
                   1755: @var{G0} of terms appearing in @var{Gp}.
                   1756: @item
                   1757: For each element @var{f} in @var{Gp}, replace coefficients and terms in @var{f}
                   1758: with undetermined coefficients and the corresponding polynomials in @var{NF}
                   1759: respectively, and generate a system of liear equation @var{Lf} by equating
                   1760: the coefficients of terms in the replaced polynomial with 0.
                   1761: @item
                   1762: Solve @var{Lf} by Hensel lifting, starting from the unique mod @var{p}
                   1763: solution.
                   1764: @item
                   1765: If all the linear equations generated from the elements in @var{Gp}
                   1766: could be solved, then the set of solutions corresponds to a lex order
                   1767: Groebner basis. Otherwise redo the whole process with another @var{p}.
                   1768: @end enumerate
                   1769:
                   1770: @item
                   1771: In @code{lex_tl()} and @code{tolex_tl()} a lex order Groebner basis
                   1772: is computed as follows.(Refer to @code{[Noro,Yokoyama]}.)
                   1773:
                   1774: @enumerate
                   1775: @item
                   1776: Compute a Groebner basis @var{G0} with respect to @var{vlist1} and @var{order}.
                   1777: (Only in @code{lex_tl()}. )
                   1778: @item
                   1779: If @var{G0} is not zero-dimensional, choose a prime which does not divide
                   1780: head coefficients of elements in @var{G0} with respect to @var{vlist1} and
                   1781: @var{order}. Then compute a candidate of a lex order Groebner basis
                   1782: via trace lifting with @var{p}. If it succeeds the candidate is indeed
                   1783: a lex order Groebner basis without any check. Otherwise redo the whole
                   1784: process with another @var{p}.
                   1785: @item
                   1786:
                   1787: If @var{G0} is zero-dimensional, starting from @var{G0},
                   1788: compute a Groebner basis @var{G1} with respect to an elimination order
                   1789: to eliminate variables other than the last varibale in @var{vlist2}.
                   1790: Then compute a lex order Groebner basis stating from @var{G1}. These
                   1791: computations are done by trace lifting and the selection of a mudulus
                   1792: @var{p} is the same as in non zero-dimensional cases.
                   1793: @end enumerate
                   1794:
                   1795: @item
                   1796: Computations with rational function coefficients can be done only by
                   1797: @code{lex_tl()} and @code{tolex_tl()}.
                   1798: @item
                   1799: If @code{homo} is not equal to 0, homogenization is used in Buchberger
                   1800: algorithm.
                   1801: @item
                   1802: The CPU time shown after an execution of @code{tolex_d()} indicates
                   1803: that of the master process, and it does not include the time in child
                   1804: processes.
                   1805: \E
1.1       noro     1806: @end itemize
                   1807:
                   1808: @example
                   1809: [78] K=katsura(5)$
                   1810: 30msec + gc : 20msec
                   1811: [79] V=[u5,u4,u3,u2,u1,u0]$
                   1812: 0msec
                   1813: [80] G0=hgr(K,V,2)$
                   1814: 91.558sec + gc : 15.583sec
                   1815: [81] G1=lex_hensel(K,V,0,V,0)$
                   1816: 49.049sec + gc : 9.961sec
                   1817: [82] G2=lex_tl(K,V,0,V,1)$
                   1818: 31.186sec + gc : 3.500sec
                   1819: [83] gb_comp(G0,G1);
                   1820: 1
                   1821: 10msec
                   1822: [84] gb_comp(G0,G2);
                   1823: 1
                   1824: @end example
                   1825:
                   1826: @table @t
1.2       noro     1827: \JP @item $B;2>H(B
                   1828: \EG @item References
1.6       noro     1829: @fref{dp_gr_main dp_gr_mod_main dp_gr_f_main dp_weyl_gr_main dp_weyl_gr_mod_main dp_weyl_gr_f_main},
1.2       noro     1830: \JP @fref{dp_ord}, @fref{$BJ,;67W;;(B}
                   1831: \EG @fref{dp_ord}, @fref{Distributed computation}
1.1       noro     1832: @end table
                   1833:
1.2       noro     1834: \JP @node lex_hensel_gsl tolex_gsl tolex_gsl_d,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   1835: \EG @node lex_hensel_gsl tolex_gsl tolex_gsl_d,,, Functions for Groebner basis computation
1.1       noro     1836: @subsection @code{lex_hensel_gsl}, @code{tolex_gsl}, @code{tolex_gsl_d}
                   1837: @findex lex_hensel_gsl
                   1838: @findex tolex_gsl
                   1839: @findex tolex_gsl_d
                   1840:
                   1841: @table @t
                   1842: @item lex_hensel_gsl(@var{plist},@var{vlist1},@var{order},@var{vlist2},@var{homo})
1.2       noro     1843: \JP :: GSL $B7A<0$N%$%G%"%k4pDl$N7W;;(B
                   1844: \EG ::Computation of an GSL form ideal basis
1.8       noro     1845: @item tolex_gsl(@var{plist},@var{vlist1},@var{order},@var{vlist2})
                   1846: @itemx tolex_gsl_d(@var{plist},@var{vlist1},@var{order},@var{vlist2},@var{procs})
1.2       noro     1847: \JP :: $B%0%l%V%J4pDl$rF~NO$H$9$k(B, GSL $B7A<0$N%$%G%"%k4pDl$N7W;;(B
                   1848: \EG :: Computation of an GSL form ideal basis stating from a Groebner basis
1.1       noro     1849: @end table
                   1850:
                   1851: @table @var
                   1852: @item return
1.2       noro     1853: \JP $B%j%9%H(B
                   1854: \EG list
1.4       noro     1855: @item plist  vlist1  vlist2  procs
1.2       noro     1856: \JP $B%j%9%H(B
                   1857: \EG list
1.1       noro     1858: @item order
1.2       noro     1859: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   1860: \EG number, list or matrix
1.1       noro     1861: @item homo
1.2       noro     1862: \JP $B%U%i%0(B
                   1863: \EG flag
1.1       noro     1864: @end table
                   1865:
                   1866: @itemize @bullet
1.2       noro     1867: \BJP
1.1       noro     1868: @item
                   1869: @code{lex_hensel_gsl()} $B$O(B @code{lex_hensel()} $B$N(B, @code{tolex_gsl()} $B$O(B
                   1870: @code{tolex()} $B$NJQ<o$G(B, $B7k2L$N$_$,0[$J$k(B.
                   1871: @code{tolex_gsl_d()} $B$O(B, $B4pDl7W;;$r(B, @code{procs} $B$G;XDj$5$l$k;R%W%m%;%9$K(B
                   1872: $BJ,;67W;;$5$;$k(B.
                   1873: @item
                   1874: $BF~NO$,(B 0 $B<!85%7%9%F%`$G(B, $B$=$N<-=q<0=g=x%0%l%V%J4pDl$,(B
                   1875: @code{[f0,x1-f1,...,xn-fn]} (@code{f0},...,@code{fn} $B$O(B
                   1876: @code{x0} $B$N(B 1 $BJQ?tB?9`<0(B) $B$J$k7A(B ($B$3$l$r(B SL $B7A<0$H8F$V(B) $B$r;}$D>l9g(B,
                   1877: @code{[[x1,g1,d1],...,[xn,gn,dn],[x0,f0,f0']]} $B$J$k%j%9%H(B ($B$3$l$r(B GSL $B7A<0$H8F$V(B)
                   1878: $B$rJV$9(B.
1.2       noro     1879: $B$3$3$G(B, @code{gi} $B$O(B, @code{di*f0'*fi-gi} $B$,(B @code{f0} $B$G3d$j@Z$l$k$h$&$J(B
1.1       noro     1880: @code{x0} $B$N(B1 $BJQ?tB?9`<0$G(B,
                   1881: $B2r$O(B @code{f0(x0)=0} $B$J$k(B @code{x0} $B$KBP$7(B, @code{[x1=g1/(d1*f0'),...,xn=gn/(dn*f0')]}
                   1882: $B$H$J$k(B. $B<-=q<0=g=x%0%l%V%J4pDl$,>e$N$h$&$J7A$G$J$$>l9g(B, @code{tolex()} $B$K(B
                   1883: $B$h$kDL>o$N%0%l%V%J4pDl$rJV$9(B.
                   1884: @item
                   1885: GSL $B7A<0$K$h$jI=$5$l$k4pDl$O%0%l%V%J4pDl$G$O$J$$$,(B, $B0lHL$K78?t$,(B SL $B7A<0(B
                   1886: $B$N%0%l%V%J4pDl$h$jHs>o$K>.$5$$$?$a7W;;$bB.$/(B, $B2r$b5a$a$d$9$$(B.
                   1887: @code{tolex_gsl_d()} $B$GI=<($5$l$k;~4V$O(B, $B$3$NH!?t$,<B9T$5$l$F$$$k%W%m%;%9$K(B
                   1888: $B$*$$$F9T$o$l$?7W;;$KBP1~$7$F$$$F(B, $B;R%W%m%;%9$K$*$1$k;~4V$O4^$^$l$J$$(B.
1.2       noro     1889: \E
                   1890: \BEG
                   1891: @item
                   1892: @code{lex_hensel_gsl()} and @code{lex_hensel()} are variants of
                   1893: @code{tolex_gsl()} and @code{tolex()} respectively. The results are
                   1894: Groebner basis or a kind of ideal basis, called GSL form.
                   1895: @code{tolex_gsl_d()} does basis computations in parallel on child
                   1896: processes specified in @code{procs}.
                   1897:
                   1898: @item
                   1899: If the input is zero-dimensional and a lex order Groebner basis has
                   1900: the form @code{[f0,x1-f1,...,xn-fn]} (@code{f0},...,@code{fn} are
                   1901: univariate polynomials of @code{x0}; SL form), then this these
                   1902: functions return a list such as
                   1903: @code{[[x1,g1,d1],...,[xn,gn,dn],[x0,f0,f0']]} (GSL form).  In this list
                   1904: @code{gi} is a univariate polynomial of @code{x0} such that
                   1905: @code{di*f0'*fi-gi} divides @code{f0} and the roots of the input ideal is
                   1906: @code{[x1=g1/(d1*f0'),...,xn=gn/(dn*f0')]} for @code{x0}
                   1907: such that @code{f0(x0)=0}.
                   1908: If the lex order Groebner basis does not have the above form,
                   1909: these functions return
                   1910: a lex order Groebner basis computed by @code{tolex()}.
                   1911: @item
                   1912: Though an ideal basis represented as GSL form is not a Groebner basis
                   1913: we can expect that the coefficients are much smaller than those in a Groebner
                   1914: basis and that the computation is efficient.
                   1915: The CPU time shown after an execution of @code{tolex_gsl_d()} indicates
                   1916: that of the master process, and it does not include the time in child
                   1917: processes.
                   1918: \E
1.1       noro     1919: @end itemize
                   1920:
                   1921: @example
                   1922: [103] K=katsura(5)$
                   1923: [104] V=[u5,u4,u3,u2,u1,u0]$
                   1924: [105] G0=gr(K,V,0)$
                   1925: [106] GSL=tolex_gsl(G0,V,0,V)$
                   1926: [107] GSL[0];
                   1927: [u1,8635837421130477667200000000*u0^31-...]
                   1928: [108] GSL[1];
                   1929: [u2,10352277157007342793600000000*u0^31-...]
                   1930: [109] GSL[5];
1.5       noro     1931: [u0,11771021876193064124640000000*u0^32-...,
                   1932: 376672700038178051988480000000*u0^31-...]
1.1       noro     1933: @end example
                   1934:
                   1935: @table @t
1.2       noro     1936: \JP @item $B;2>H(B
                   1937: \EG @item References
1.1       noro     1938: @fref{lex_hensel lex_tl tolex tolex_d tolex_tl},
1.2       noro     1939: \JP @fref{$BJ,;67W;;(B}
                   1940: \EG @fref{Distributed computation}
1.1       noro     1941: @end table
                   1942:
1.2       noro     1943: \JP @node gr_minipoly minipoly,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   1944: \EG @node gr_minipoly minipoly,,, Functions for Groebner basis computation
1.1       noro     1945: @subsection @code{gr_minipoly}, @code{minipoly}
                   1946: @findex gr_minipoly
                   1947: @findex minipoly
                   1948:
                   1949: @table @t
                   1950: @item gr_minipoly(@var{plist},@var{vlist},@var{order},@var{poly},@var{v},@var{homo})
1.2       noro     1951: \JP :: $BB?9`<0$N(B, $B%$%G%"%k$rK!$H$7$?:G>.B?9`<0$N7W;;(B
                   1952: \EG :: Computation of the minimal polynomial of a polynomial modulo an ideal
1.1       noro     1953: @item minipoly(@var{plist},@var{vlist},@var{order},@var{poly},@var{v})
1.2       noro     1954: \JP :: $B%0%l%V%J4pDl$rF~NO$H$9$k(B, $BB?9`<0$N:G>.B?9`<0$N7W;;(B
                   1955: \EG :: Computation of the minimal polynomial of a polynomial modulo an ideal
1.1       noro     1956: @end table
                   1957:
                   1958: @table @var
                   1959: @item return
1.2       noro     1960: \JP $BB?9`<0(B
                   1961: \EG polynomial
1.4       noro     1962: @item plist  vlist
1.2       noro     1963: \JP $B%j%9%H(B
                   1964: \EG list
1.1       noro     1965: @item order
1.2       noro     1966: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   1967: \EG number, list or matrix
1.1       noro     1968: @item poly
1.2       noro     1969: \JP $BB?9`<0(B
                   1970: \EG polynomial
1.1       noro     1971: @item v
1.2       noro     1972: \JP $BITDj85(B
                   1973: \EG indeterminate
1.1       noro     1974: @item homo
1.2       noro     1975: \JP $B%U%i%0(B
                   1976: \EG flag
1.1       noro     1977: @end table
                   1978:
                   1979: @itemize @bullet
1.2       noro     1980: \BJP
1.1       noro     1981: @item
                   1982: @code{gr_minipoly()} $B$O%0%l%V%J4pDl$N7W;;$+$i9T$$(B, @code{minipoly()} $B$O(B
                   1983: $BF~NO$r%0%l%V%J4pDl$H$_$J$9(B.
                   1984: @item
                   1985: $B%$%G%"%k(B I $B$,BN(B K $B>e$NB?9`<04D(B K[X] $B$N(B 0 $B<!85%$%G%"%k$N;~(B,
                   1986: K[@var{v}] $B$N85(B f(@var{v}) $B$K(B f(@var{p}) mod I $B$rBP1~$5$;$k(B
                   1987: $B4D=`F17?$N3K$O(B 0 $B$G$J$$B?9`<0$K$h$j@8@.$5$l$k(B. $B$3$N@8@.85$r(B @var{p}
                   1988: $B$N(B, $BK!(B @var{I} $B$G$N:G>.B?9`<0$H8F$V(B.
                   1989: @item
                   1990: @code{gr_minipoly()}, @code{minipoly()} $B$O(B, $BB?9`<0(B @var{p} $B$N:G>.B?9`<0(B
                   1991: $B$r5a$a(B, @var{v} $B$rJQ?t$H$9$kB?9`<0$H$7$FJV$9(B.
                   1992: @item
                   1993: $B:G>.B?9`<0$O(B, $B%0%l%V%J4pDl$N(B 1 $B$D$N85$H$7$F7W;;$9$k$3$H$b$G$-$k$,(B,
                   1994: $B:G>.B?9`<0$N$_$r5a$a$?$$>l9g(B, @code{minipoly()}, @code{gr_minipoly()} $B$O(B
                   1995: $B%0%l%V%J4pDl$rMQ$$$kJ}K!$KHf$Y$F8zN($,$h$$(B.
                   1996: @item
                   1997: @code{gr_minipoly()} $B$K;XDj$9$k9`=g=x$H$7$F$O(B, $BDL>oA4<!?t5U<-=q<0=g=x$r(B
                   1998: $BMQ$$$k(B.
1.2       noro     1999: \E
                   2000: \BEG
                   2001: @item
                   2002: @code{gr_minipoly()} begins by computing a Groebner basis.
                   2003: @code{minipoly()} regards an input as a Groebner basis with respect to
                   2004: the variable order @var{vlist} and the order type @var{order}.
                   2005: @item
                   2006: Let K be a field. If an ideal @var{I} in K[X] is zero-dimensional, then, for
                   2007: a polynomial @var{p} in K[X], the kernel of a homomorphism from
                   2008: K[@var{v}] to K[X]/@var{I} which maps f(@var{v}) to f(@var{p}) mod @var{I}
                   2009: is generated by a polynomial. The generator is called the minimal polynomial
                   2010: of @var{p} modulo @var{I}.
                   2011: @item
                   2012: @code{gr_minipoly()} and @code{minipoly()} computes the minimal polynomial
                   2013: of a polynomial @var{p} and returns it as a polynomial of @var{v}.
                   2014: @item
                   2015: The minimal polynomial can be computed as an element of a Groebner basis.
                   2016: But if we are only interested in the minimal polynomial,
                   2017: @code{minipoly()} and @code{gr_minipoly()} can compute it more efficiently
                   2018: than methods using Groebner basis computation.
                   2019: @item
                   2020: It is recommended to use a degree reverse lex order as a term order
                   2021: for @code{gr_minipoly()}.
                   2022: \E
1.1       noro     2023: @end itemize
                   2024:
                   2025: @example
                   2026: [117] G=tolex(G0,V,0,V)$
                   2027: 43.818sec + gc : 11.202sec
                   2028: [118] GSL=tolex_gsl(G0,V,0,V)$
                   2029: 17.123sec + gc : 2.590sec
                   2030: [119] MP=minipoly(G0,V,0,u0,z)$
                   2031: 4.370sec + gc : 780msec
                   2032: @end example
                   2033:
                   2034: @table @t
1.2       noro     2035: \JP @item $B;2>H(B
                   2036: \EG @item References
1.1       noro     2037: @fref{lex_hensel lex_tl tolex tolex_d tolex_tl}.
                   2038: @end table
                   2039:
1.2       noro     2040: \JP @node tolexm minipolym,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2041: \EG @node tolexm minipolym,,, Functions for Groebner basis computation
1.1       noro     2042: @subsection @code{tolexm}, @code{minipolym}
                   2043: @findex tolexm
                   2044: @findex minipolym
                   2045:
                   2046: @table @t
                   2047: @item tolexm(@var{plist},@var{vlist1},@var{order},@var{vlist2},@var{mod})
1.2       noro     2048: \JP :: $BK!(B @var{mod} $B$G$N4pDlJQ49$K$h$k%0%l%V%J4pDl7W;;(B
                   2049: \EG :: Groebner basis computation modulo @var{mod} by change of ordering.
1.1       noro     2050: @item minipolym(@var{plist},@var{vlist1},@var{order},@var{poly},@var{v},@var{mod})
1.2       noro     2051: \JP :: $BK!(B @var{mod} $B$G$N%0%l%V%J4pDl$K$h$kB?9`<0$N:G>.B?9`<0$N7W;;(B
                   2052: \EG :: Minimal polynomial computation modulo @var{mod} the same method as
1.1       noro     2053: @end table
                   2054:
                   2055: @table @var
                   2056: @item return
1.2       noro     2057: \JP @code{tolexm()} : $B%j%9%H(B, @code{minipolym()} : $BB?9`<0(B
                   2058: \EG @code{tolexm()} : list, @code{minipolym()} : polynomial
1.4       noro     2059: @item plist  vlist1  vlist2
1.2       noro     2060: \JP $B%j%9%H(B
                   2061: \EG list
1.1       noro     2062: @item order
1.2       noro     2063: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   2064: \EG number, list or matrix
1.1       noro     2065: @item mod
1.2       noro     2066: \JP $BAG?t(B
                   2067: \EG prime
1.1       noro     2068: @end table
                   2069:
                   2070: @itemize @bullet
1.2       noro     2071: \BJP
1.1       noro     2072: @item
                   2073: $BF~NO(B @var{plist} $B$O$$$:$l$b(B $BJQ?t=g=x(B @var{vlist1}, $B9`=g=x7?(B @var{order},
                   2074: $BK!(B @var{mod} $B$K$*$1$k%0%l%V%J4pDl$G$J$1$l$P$J$i$J$$(B.
                   2075: @item
                   2076: @code{minipolym()} $B$O(B @code{minipoly} $B$KBP1~$9$k7W;;$rK!(B @var{mod}$B$G9T$&(B.
                   2077: @item
                   2078: @code{tolexm()} $B$O(B FGLM $BK!$K$h$k4pDlJQ49$K$h$j(B @var{vlist2},
                   2079: $B<-=q<0=g=x$K$h$k%0%l%V%J4pDl$r7W;;$9$k(B.
1.2       noro     2080: \E
                   2081: \BEG
                   2082: @item
                   2083: An input @var{plist} must be a Groebner basis modulo @var{mod}
                   2084: with respect to the variable order @var{vlist1} and the order type @var{order}.
                   2085: @item
                   2086: @code{minipolym()} executes the same computation as in @code{minipoly}.
                   2087: @item
                   2088: @code{tolexm()} computes a lex order Groebner basis modulo @var{mod}
                   2089: with respect to the variable order @var{vlist2}, by using FGLM algorithm.
                   2090: \E
1.1       noro     2091: @end itemize
                   2092:
                   2093: @example
                   2094: [197] tolexm(G0,V,0,V,31991);
                   2095: [8271*u0^31+10435*u0^30+816*u0^29+26809*u0^28+...,...]
                   2096: [198] minipolym(G0,V,0,u0,z,31991);
                   2097: z^32+11405*z^31+20868*z^30+21602*z^29+...
                   2098: @end example
                   2099:
                   2100: @table @t
1.2       noro     2101: \JP @item $B;2>H(B
                   2102: \EG @item References
1.1       noro     2103: @fref{lex_hensel lex_tl tolex tolex_d tolex_tl},
                   2104: @fref{gr_minipoly minipoly}.
                   2105: @end table
                   2106:
1.6       noro     2107: \JP @node dp_gr_main dp_gr_mod_main dp_gr_f_main dp_weyl_gr_main dp_weyl_gr_mod_main dp_weyl_gr_f_main,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2108: \EG @node dp_gr_main dp_gr_mod_main dp_gr_f_main dp_weyl_gr_main dp_weyl_gr_mod_main dp_weyl_gr_f_main,,, Functions for Groebner basis computation
                   2109: @subsection @code{dp_gr_main}, @code{dp_gr_mod_main}, @code{dp_gr_f_main}, @code{dp_weyl_gr_main}, @code{dp_weyl_gr_mod_main}, @code{dp_weyl_gr_f_main}
1.1       noro     2110: @findex dp_gr_main
                   2111: @findex dp_gr_mod_main
1.5       noro     2112: @findex dp_gr_f_main
1.6       noro     2113: @findex dp_weyl_gr_main
                   2114: @findex dp_weyl_gr_mod_main
                   2115: @findex dp_weyl_gr_f_main
1.1       noro     2116:
                   2117: @table @t
                   2118: @item dp_gr_main(@var{plist},@var{vlist},@var{homo},@var{modular},@var{order})
                   2119: @itemx dp_gr_mod_main(@var{plist},@var{vlist},@var{homo},@var{modular},@var{order})
1.5       noro     2120: @itemx dp_gr_f_main(@var{plist},@var{vlist},@var{homo},@var{order})
1.6       noro     2121: @itemx dp_weyl_gr_main(@var{plist},@var{vlist},@var{homo},@var{modular},@var{order})
                   2122: @itemx dp_weyl_gr_mod_main(@var{plist},@var{vlist},@var{homo},@var{modular},@var{order})
                   2123: @itemx dp_weyl_gr_f_main(@var{plist},@var{vlist},@var{homo},@var{order})
1.2       noro     2124: \JP :: $B%0%l%V%J4pDl$N7W;;(B ($BAH$_9~$_H!?t(B)
                   2125: \EG :: Groebner basis computation (built-in functions)
1.1       noro     2126: @end table
                   2127:
                   2128: @table @var
                   2129: @item return
1.2       noro     2130: \JP $B%j%9%H(B
                   2131: \EG list
1.4       noro     2132: @item plist  vlist
1.2       noro     2133: \JP $B%j%9%H(B
                   2134: \EG list
1.1       noro     2135: @item order
1.2       noro     2136: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   2137: \EG number, list or matrix
1.1       noro     2138: @item homo
1.2       noro     2139: \JP $B%U%i%0(B
                   2140: \EG flag
1.1       noro     2141: @item modular
1.2       noro     2142: \JP $B%U%i%0$^$?$OAG?t(B
                   2143: \EG flag or prime
1.1       noro     2144: @end table
                   2145:
                   2146: @itemize @bullet
1.2       noro     2147: \BJP
1.1       noro     2148: @item
                   2149: $B$3$l$i$NH!?t$O(B, $B%0%l%V%J4pDl7W;;$N4pK\E*AH$_9~$_H!?t$G$"$j(B, @code{gr()},
                   2150: @code{hgr()}, @code{gr_mod()} $B$J$I$O$9$Y$F$3$l$i$NH!?t$r8F$S=P$7$F7W;;(B
1.6       noro     2151: $B$r9T$C$F$$$k(B. $B4X?tL>$K(B weyl $B$,F~$C$F$$$k$b$N$O(B, Weyl $BBe?t>e$N7W;;(B
                   2152: $B$N$?$a$N4X?t$G$"$k(B.
1.1       noro     2153: @item
1.6       noro     2154: @code{dp_gr_f_main()}, @code{dp_weyl_f_main()} $B$O(B, $B<o!9$NM-8BBN>e$N%0%l%V%J4pDl$r7W;;$9$k(B
1.5       noro     2155: $B>l9g$KMQ$$$k(B. $BF~NO$O(B, $B$"$i$+$8$a(B, @code{simp_ff()} $B$J$I$G(B,
                   2156: $B9M$($kM-8BBN>e$K<M1F$5$l$F$$$kI,MW$,$"$k(B.
                   2157: @item
1.1       noro     2158: $B%U%i%0(B @var{homo} $B$,(B 0 $B$G$J$$;~(B, $BF~NO$r@F<!2=$7$F$+$i(B Buchberger $B%"%k%4%j%:%`(B
                   2159: $B$r<B9T$9$k(B.
                   2160: @item
                   2161: @code{dp_gr_mod_main()} $B$KBP$7$F$O(B, @var{modular} $B$O(B, GF(@var{modular}) $B>e(B
                   2162: $B$G$N7W;;$r0UL#$9$k(B.
                   2163: @code{dp_gr_main()} $B$KBP$7$F$O(B, @var{modular} $B$O<!$N$h$&$J0UL#$r;}$D(B.
                   2164: @enumerate
                   2165: @item
                   2166: @var{modular} $B$,(B 1 $B$N;~(B, trace-lifting $B$K$h$k7W;;$r9T$&(B. $BAG?t$O(B
                   2167: @code{lprime(0)} $B$+$i=g$K@.8y$9$k$^$G(B @code{lprime()} $B$r8F$S=P$7$F@8@.$9$k(B.
                   2168: @item
                   2169: @var{modular} $B$,(B 2 $B0J>e$N<+A3?t$N;~(B, $B$=$NCM$rAG?t$H$_$J$7$F(B trace-lifting
                   2170: $B$r9T$&(B. $B$=$NAG?t$G<:GT$7$?>l9g(B, 0 $B$rJV$9(B.
                   2171: @item
                   2172: @var{modular} $B$,Ii$N>l9g(B,
                   2173: @var{-modular} $B$KBP$7$F>e=R$N5,B'$,E,MQ$5$l$k$,(B, trace-lifting $B$N:G=*(B
                   2174: $BCJ3,$N%0%l%V%J4pDl%A%'%C%/$H%$%G%"%k%a%s%P%7%C%W%A%'%C%/$,>JN,$5$l$k(B.
                   2175: @end enumerate
                   2176:
                   2177: @item
                   2178: @code{gr(P,V,O)} $B$O(B @code{dp_gr_main(P,V,0,1,O)}, @code{hgr(P,V,O)} $B$O(B
                   2179: @code{dp_gr_main(P,V,1,1,O)}, @code{gr_mod(P,V,O,M)} $B$O(B
                   2180: @code{dp_gr_mod_main(P,V,0,M,O)} $B$r$=$l$>$l<B9T$9$k(B.
                   2181: @item
                   2182: @var{homo}, @var{modular} $B$NB>$K(B, @code{dp_gr_flags()} $B$G@_Dj$5$l$k(B
                   2183: $B$5$^$6$^$J%U%i%0$K$h$j7W;;$,@)8f$5$l$k(B.
1.2       noro     2184: \E
                   2185: \BEG
                   2186: @item
                   2187: These functions are fundamental built-in functions for Groebner basis
                   2188: computation and @code{gr()},@code{hgr()} and @code{gr_mod()}
1.6       noro     2189: are all interfaces to these functions. Functions whose names
                   2190: contain weyl are those for computation in Weyl algebra.
1.2       noro     2191: @item
1.6       noro     2192: @code{dp_gr_f_main()} and @code{dp_weyl_gr_f_main()}
                   2193: are functions for Groebner basis computation
1.5       noro     2194: over various finite fields. Coefficients of input polynomials
                   2195: must be converted to elements of a finite field
                   2196: currently specified by @code{setmod_ff()}.
                   2197: @item
1.2       noro     2198: If @var{homo} is not equal to 0, homogenization is applied before entering
                   2199: Buchberger algorithm
                   2200: @item
                   2201: For @code{dp_gr_mod_main()}, @var{modular} means a computation over
                   2202: GF(@var{modular}).
                   2203: For @code{dp_gr_main()}, @var{modular} has the following mean.
                   2204: @enumerate
                   2205: @item
                   2206: If @var{modular} is 1 , trace lifting is used. Primes for trace lifting
                   2207: are generated by @code{lprime()}, starting from @code{lprime(0)}, until
                   2208: the computation succeeds.
                   2209: @item
                   2210: If @var{modular} is an integer  greater than 1, the integer is regarded as a
                   2211: prime and trace lifting is executed by using the prime. If the computation
                   2212: fails then 0 is returned.
                   2213: @item
                   2214: If @var{modular} is negative, the above rule is applied for @var{-modular}
                   2215: but the Groebner basis check and ideal-membership check are omitted in
                   2216: the last stage of trace lifting.
                   2217: @end enumerate
                   2218:
                   2219: @item
                   2220: @code{gr(P,V,O)}, @code{hgr(P,V,O)} and @code{gr_mod(P,V,O,M)} execute
                   2221: @code{dp_gr_main(P,V,0,1,O)}, @code{dp_gr_main(P,V,1,1,O)}
                   2222: and @code{dp_gr_mod_main(P,V,0,M,O)} respectively.
                   2223: @item
                   2224: Actual computation is controlled by various parameters set by
                   2225: @code{dp_gr_flags()}, other then by @var{homo} and @var{modular}.
                   2226: \E
1.1       noro     2227: @end itemize
                   2228:
                   2229: @table @t
1.2       noro     2230: \JP @item $B;2>H(B
                   2231: \EG @item References
1.1       noro     2232: @fref{dp_ord},
                   2233: @fref{dp_gr_flags dp_gr_print},
                   2234: @fref{gr hgr gr_mod},
1.5       noro     2235: @fref{setmod_ff},
1.2       noro     2236: \JP @fref{$B7W;;$*$h$SI=<($N@)8f(B}.
                   2237: \EG @fref{Controlling Groebner basis computations}
1.1       noro     2238: @end table
                   2239:
1.6       noro     2240: \JP @node dp_f4_main dp_f4_mod_main dp_weyl_f4_main dp_weyl_f4_mod_main,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2241: \EG @node dp_f4_main dp_f4_mod_main dp_weyl_f4_main dp_weyl_f4_mod_main,,, Functions for Groebner basis computation
                   2242: @subsection @code{dp_f4_main}, @code{dp_f4_mod_main}, @code{dp_weyl_f4_main}, @code{dp_weyl_f4_mod_main}
1.1       noro     2243: @findex dp_f4_main
                   2244: @findex dp_f4_mod_main
1.6       noro     2245: @findex dp_weyl_f4_main
                   2246: @findex dp_weyl_f4_mod_main
1.1       noro     2247:
                   2248: @table @t
                   2249: @item dp_f4_main(@var{plist},@var{vlist},@var{order})
                   2250: @itemx dp_f4_mod_main(@var{plist},@var{vlist},@var{order})
1.6       noro     2251: @itemx dp_weyl_f4_main(@var{plist},@var{vlist},@var{order})
                   2252: @itemx dp_weyl_f4_mod_main(@var{plist},@var{vlist},@var{order})
1.2       noro     2253: \JP :: F4 $B%"%k%4%j%:%`$K$h$k%0%l%V%J4pDl$N7W;;(B ($BAH$_9~$_H!?t(B)
                   2254: \EG :: Groebner basis computation by F4 algorithm (built-in functions)
1.1       noro     2255: @end table
                   2256:
                   2257: @table @var
                   2258: @item return
1.2       noro     2259: \JP $B%j%9%H(B
                   2260: \EG list
1.4       noro     2261: @item plist  vlist
1.2       noro     2262: \JP $B%j%9%H(B
                   2263: \EG list
1.1       noro     2264: @item order
1.2       noro     2265: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   2266: \EG number, list or matrix
1.1       noro     2267: @end table
                   2268:
                   2269: @itemize @bullet
1.2       noro     2270: \BJP
1.1       noro     2271: @item
                   2272: F4 $B%"%k%4%j%:%`$K$h$j%0%l%V%J4pDl$N7W;;$r9T$&(B.
                   2273: @item
                   2274: F4 $B%"%k%4%j%:%`$O(B, J.C. Faugere $B$K$h$jDs>'$5$l$??7@$Be%0%l%V%J4pDl(B
                   2275: $B;;K!$G$"$j(B, $BK\<BAu$O(B, $BCf9q>jM>DjM}$K$h$k@~7AJ}Dx<05a2r$rMQ$$$?(B
                   2276: $B;n83E*$J<BAu$G$"$k(B.
                   2277: @item
1.6       noro     2278: $B@F<!2=$N0z?t$,$J$$$3$H$r=|$1$P(B, $B0z?t$*$h$SF0:n$O$=$l$>$l(B
                   2279: @code{dp_gr_main()}, @code{dp_gr_mod_main()},
                   2280: @code{dp_weyl_gr_main()}, @code{dp_weyl_gr_mod_main()}
1.1       noro     2281: $B$HF1MM$G$"$k(B.
1.2       noro     2282: \E
                   2283: \BEG
                   2284: @item
                   2285: These functions compute Groebner bases by F4 algorithm.
                   2286: @item
                   2287: F4 is a new generation algorithm for Groebner basis computation
                   2288: invented by J.C. Faugere. The current implementation of @code{dp_f4_main()}
                   2289: uses Chinese Remainder theorem and not highly optimized.
                   2290: @item
                   2291: Arguments and actions are the same as those of
1.6       noro     2292: @code{dp_gr_main()}, @code{dp_gr_mod_main()},
                   2293: @code{dp_weyl_gr_main()}, @code{dp_weyl_gr_mod_main()},
                   2294: except for lack of the argument for controlling homogenization.
1.2       noro     2295: \E
1.1       noro     2296: @end itemize
                   2297:
                   2298: @table @t
1.2       noro     2299: \JP @item $B;2>H(B
                   2300: \EG @item References
1.1       noro     2301: @fref{dp_ord},
                   2302: @fref{dp_gr_flags dp_gr_print},
                   2303: @fref{gr hgr gr_mod},
1.15      noro     2304: \JP @fref{$B7W;;$*$h$SI=<($N@)8f(B}.
                   2305: \EG @fref{Controlling Groebner basis computations}
                   2306: @end table
                   2307:
1.17      noro     2308: \JP @node nd_gr nd_gr_trace nd_f4 nd_f4_trace nd_weyl_gr nd_weyl_gr_trace,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2309: \EG @node nd_gr nd_gr_trace nd_f4 nd_f4_trace nd_weyl_gr nd_weyl_gr_trace,,, Functions for Groebner basis computation
                   2310: @subsection @code{nd_gr}, @code{nd_gr_trace}, @code{nd_f4}, @code{nd_f4_trace}, @code{nd_weyl_gr}, @code{nd_weyl_gr_trace}
1.15      noro     2311: @findex nd_gr
                   2312: @findex nd_gr_trace
                   2313: @findex nd_f4
1.17      noro     2314: @findex nd_f4_trace
1.15      noro     2315: @findex nd_weyl_gr
                   2316: @findex nd_weyl_gr_trace
                   2317:
                   2318: @table @t
                   2319: @item nd_gr(@var{plist},@var{vlist},@var{p},@var{order})
                   2320: @itemx nd_gr_trace(@var{plist},@var{vlist},@var{homo},@var{p},@var{order})
                   2321: @itemx nd_f4(@var{plist},@var{vlist},@var{modular},@var{order})
1.17      noro     2322: @itemx nd_f4_trace(@var{plist},@var{vlist},@var{homo},@var{p},@var{order})
1.15      noro     2323: @item nd_weyl_gr(@var{plist},@var{vlist},@var{p},@var{order})
                   2324: @itemx nd_weyl_gr_trace(@var{plist},@var{vlist},@var{homo},@var{p},@var{order})
                   2325: \JP :: $B%0%l%V%J4pDl$N7W;;(B ($BAH$_9~$_H!?t(B)
                   2326: \EG :: Groebner basis computation (built-in functions)
                   2327: @end table
                   2328:
                   2329: @table @var
                   2330: @item return
                   2331: \JP $B%j%9%H(B
                   2332: \EG list
                   2333: @item plist  vlist
                   2334: \JP $B%j%9%H(B
                   2335: \EG list
                   2336: @item order
                   2337: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   2338: \EG number, list or matrix
                   2339: @item homo
                   2340: \JP $B%U%i%0(B
                   2341: \EG flag
                   2342: @item modular
                   2343: \JP $B%U%i%0$^$?$OAG?t(B
                   2344: \EG flag or prime
                   2345: @end table
                   2346:
                   2347: \BJP
                   2348: @itemize @bullet
                   2349: @item
                   2350: $B$3$l$i$NH!?t$O(B, $B%0%l%V%J4pDl7W;;AH$_9~$_4X?t$N?7<BAu$G$"$k(B.
                   2351: @item @code{nd_gr} $B$O(B, @code{p} $B$,(B 0 $B$N$H$-M-M}?tBN>e$N(B Buchberger
                   2352: $B%"%k%4%j%:%`$r<B9T$9$k(B. @code{p} $B$,(B 2 $B0J>e$N<+A3?t$N$H$-(B, GF(p) $B>e$N(B
                   2353: Buchberger $B%"%k%4%j%:%`$r<B9T$9$k(B.
1.17      noro     2354: @item @code{nd_gr_trace} $B$*$h$S(B @code{nd_f4_trace}
                   2355: $B$OM-M}?tBN>e$G(B trace $B%"%k%4%j%:%`$r<B9T$9$k(B.
1.18    ! noro     2356: @var{p} $B$,(B 0 $B$^$?$O(B 1 $B$N$H$-(B, $B<+F0E*$KA*$P$l$?AG?t$rMQ$$$F(B, $B@.8y$9$k(B
1.15      noro     2357: $B$^$G(B trace $B%"%k%4%j%:%`$r<B9T$9$k(B.
1.18    ! noro     2358: @var{p} $B$,(B 2 $B0J>e$N$H$-(B, trace $B$O(BGF(p) $B>e$G7W;;$5$l$k(B. trace $B%"%k%4%j%:%`(B
        !          2359: $B$,<:GT$7$?>l9g(B 0 $B$,JV$5$l$k(B. @var{p} $B$,Ii$N>l9g(B, $B%0%l%V%J4pDl%A%'%C%/$O(B
        !          2360: $B9T$o$J$$(B. $B$3$N>l9g(B, @var{p} $B$,(B -1 $B$J$i$P<+F0E*$KA*$P$l$?AG?t$,(B,
1.17      noro     2361: $B$=$l0J30$O;XDj$5$l$?AG?t$rMQ$$$F%0%l%V%J4pDl8uJd$N7W;;$,9T$o$l$k(B.
                   2362: @code{nd_f4_trace} $B$O(B, $B3FA4<!?t$K$D$$$F(B, $B$"$kM-8BBN>e$G(B F4 $B%"%k%4%j%:%`(B
                   2363: $B$G9T$C$?7k2L$r$b$H$K(B, $B$=$NM-8BBN>e$G(B 0 $B$G$J$$4pDl$rM?$($k(B S-$BB?9`<0$N$_$r(B
                   2364: $BMQ$$$F9TNs@8@.$r9T$$(B, $B$=$NA4<!?t$K$*$1$k4pDl$r@8@.$9$kJ}K!$G$"$k(B. $BF@$i$l$k(B
                   2365: $BB?9`<0=89g$O$d$O$j%0%l%V%J4pDl8uJd$G$"$j(B, @code{nd_gr_trace} $B$HF1MM$N(B
                   2366: $B%A%'%C%/$,9T$o$l$k(B.
1.15      noro     2367: @item
1.17      noro     2368: @code{nd_f4} $B$O(B @code{modular} $B$,(B 0 $B$N$H$-M-M}?tBN>e$N(B, @code{modular} $B$,(B
                   2369: $B%^%7%s%5%$%:AG?t$N$H$-M-8BBN>e$N(B F4 $B%"%k%4%j%:%`$r<B9T$9$k(B.
1.15      noro     2370: @item
1.18    ! noro     2371: @var{plist} $B$,B?9`<0%j%9%H$N>l9g(B, @var{plist}$B$G@8@.$5$l$k%$%G%"%k$N%0%l%V%J!<4pDl$,(B
        !          2372: $B7W;;$5$l$k(B. @var{plist} $B$,B?9`<0%j%9%H$N%j%9%H$N>l9g(B, $B3FMWAG$OB?9`<04D>e$N<+M32C72$N85$H8+$J$5$l(B,
        !          2373: $B$3$l$i$,@8@.$9$kItJ,2C72$N%0%l%V%J!<4pDl$,7W;;$5$l$k(B. $B8e<T$N>l9g(B, $B9`=g=x$O2C72$KBP$9$k9`=g=x$r(B
        !          2374: $B;XDj$9$kI,MW$,$"$k(B. $B$3$l$O(B @var{[s,ord]} $B$N7A$G;XDj$9$k(B. @var{s} $B$,(B 0 $B$J$i$P(B TOP (Term Over Position),
        !          2375: 1 $B$J$i$P(B POT (Position Over Term) $B$r0UL#$7(B, @var{ord} $B$OB?9`<04D$NC19`<0$KBP$9$k9`=g=x$G$"$k(B.
        !          2376: @item
1.15      noro     2377: @code{nd_weyl_gr}, @code{nd_weyl_gr_trace} $B$O(B Weyl $BBe?tMQ$G$"$k(B.
                   2378: @item
1.18    ! noro     2379: @code{f4} $B7O4X?t0J30$O$9$Y$FM-M}4X?t78?t$N7W;;$,2DG=$G$"$k(B.
1.15      noro     2380: @item
                   2381: $B0lHL$K(B @code{dp_gr_main}, @code{dp_gr_mod_main} $B$h$j9bB.$G$"$k$,(B,
                   2382: $BFC$KM-8BBN>e$N>l9g82Cx$G$"$k(B.
                   2383: @end itemize
                   2384: \E
                   2385:
                   2386: \BEG
                   2387: @itemize @bullet
                   2388: @item
                   2389: These functions are new implementations for computing Groebner bases.
                   2390: @item @code{nd_gr} executes Buchberger algorithm over the rationals
                   2391: if  @code{p} is 0, and that over GF(p) if @code{p} is a prime.
                   2392: @item @code{nd_gr_trace} executes the trace algorithm over the rationals.
                   2393: If @code{p} is 0 or 1, the trace algorithm is executed until it succeeds
                   2394: by using automatically chosen primes.
                   2395: If @code{p} a positive prime,
                   2396: the trace is comuted over GF(p).
                   2397: If the trace algorithm fails 0 is returned.
                   2398: If @code{p} is negative,
                   2399: the Groebner basis check and ideal-membership check are omitted.
                   2400: In this case, an automatically chosen prime if @code{p} is 1,
                   2401: otherwise the specified prime is used to compute a Groebner basis
                   2402: candidate.
1.17      noro     2403: Execution of @code{nd_f4_trace} is done as follows:
                   2404: For each total degree, an F4-reduction of S-polynomials over a finite field
                   2405: is done, and S-polynomials which give non-zero basis elements are gathered.
                   2406: Then F4-reduction over Q is done for the gathered S-polynomials.
                   2407: The obtained polynomial set is a Groebner basis candidate and the same
                   2408: check procedure as in the case of @code{nd_gr_trace} is done.
                   2409: @item
                   2410: @code{nd_f4} executes F4 algorithm over Q if @code{modular} is equal to 0,
                   2411: or over a finite field GF(@code{modular})
                   2412: if @code{modular} is a prime number of machine size (<2^29).
1.18    ! noro     2413: If @var{plist} is a list of polynomials, then a Groebner basis of the ideal generated by @var{plist}
        !          2414: is computed. If @var{plist} is a list of lists of polynomials, then each list of polynomials are regarded
        !          2415: as an element of a free module over a polynomial ring and a Groebner basis of the sub-module generated by @var{plist}
        !          2416: in the free module. In the latter case a term order in the free module should be specified.
        !          2417: This is specified by @var{[s,ord]}. If @var{s} is 0 then it means TOP (Term Over Position).
        !          2418: If @var{s} is 1 then it means POT 1 (Position Over Term). @var{ord} is a term order in the base polynomial ring.
1.15      noro     2419: @item
                   2420: @code{nd_weyl_gr}, @code{nd_weyl_gr_trace} are for Weyl algebra computation.
                   2421: @item
1.18    ! noro     2422: Functions except for F4 related ones can handle rational coeffient cases.
1.15      noro     2423: @item
                   2424: In general these functions are more efficient than
                   2425: @code{dp_gr_main}, @code{dp_gr_mod_main}, especially over finite fields.
                   2426: @end itemize
                   2427: \E
                   2428:
                   2429: @example
                   2430: [38] load("cyclic")$
                   2431: [49] C=cyclic(7)$
                   2432: [50] V=vars(C)$
                   2433: [51] cputime(1)$
                   2434: [52] dp_gr_mod_main(C,V,0,31991,0)$
                   2435: 26.06sec + gc : 0.313sec(26.4sec)
                   2436: [53] nd_gr(C,V,31991,0)$
                   2437: ndv_alloc=1477188
                   2438: 5.737sec + gc : 0.1837sec(5.921sec)
                   2439: [54] dp_f4_mod_main(C,V,31991,0)$
                   2440: 3.51sec + gc : 0.7109sec(4.221sec)
                   2441: [55] nd_f4(C,V,31991,0)$
                   2442: 1.906sec + gc : 0.126sec(2.032sec)
                   2443: @end example
                   2444:
                   2445: @table @t
                   2446: \JP @item $B;2>H(B
                   2447: \EG @item References
                   2448: @fref{dp_ord},
                   2449: @fref{dp_gr_flags dp_gr_print},
1.2       noro     2450: \JP @fref{$B7W;;$*$h$SI=<($N@)8f(B}.
                   2451: \EG @fref{Controlling Groebner basis computations}
1.1       noro     2452: @end table
                   2453:
1.2       noro     2454: \JP @node dp_gr_flags dp_gr_print,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2455: \EG @node dp_gr_flags dp_gr_print,,, Functions for Groebner basis computation
1.1       noro     2456: @subsection @code{dp_gr_flags}, @code{dp_gr_print}
                   2457: @findex dp_gr_flags
                   2458: @findex dp_gr_print
                   2459:
                   2460: @table @t
                   2461: @item dp_gr_flags([@var{list}])
1.7       noro     2462: @itemx dp_gr_print([@var{i}])
1.2       noro     2463: \JP :: $B7W;;$*$h$SI=<(MQ%Q%i%a%?$N@_Dj(B, $B;2>H(B
                   2464: \BEG :: Set and show various parameters for cotrolling computations
                   2465: and showing informations.
                   2466: \E
1.1       noro     2467: @end table
                   2468:
                   2469: @table @var
                   2470: @item return
1.2       noro     2471: \JP $B@_DjCM(B
                   2472: \EG value currently set
1.1       noro     2473: @item list
1.2       noro     2474: \JP $B%j%9%H(B
                   2475: \EG list
1.7       noro     2476: @item i
                   2477: \JP $B@0?t(B
                   2478: \EG integer
1.1       noro     2479: @end table
                   2480:
                   2481: @itemize @bullet
1.2       noro     2482: \BJP
1.1       noro     2483: @item
1.5       noro     2484: @code{dp_gr_main()}, @code{dp_gr_mod_main()}, @code{dp_gr_f_main()}  $B<B9T;~$K$*$1$k$5$^$6$^(B
1.1       noro     2485: $B$J%Q%i%a%?$r@_Dj(B, $B;2>H$9$k(B.
                   2486: @item
                   2487: $B0z?t$,$J$$>l9g(B, $B8=:_$N@_Dj$,JV$5$l$k(B.
                   2488: @item
                   2489: $B0z?t$O(B, @code{["Print",1,"NoSugar",1,...]} $B$J$k7A$N%j%9%H$G(B, $B:8$+$i=g$K(B
                   2490: $B@_Dj$5$l$k(B. $B%Q%i%a%?L>$OJ8;zNs$GM?$($kI,MW$,$"$k(B.
                   2491: @item
1.7       noro     2492: @code{dp_gr_print()} $B$O(B, $BFC$K%Q%i%a%?(B @code{Print}, @code{PrintShort} $B$NCM$rD>@\@_Dj(B, $B;2>H(B
                   2493: $B$G$-$k(B. $B@_Dj$5$l$kCM$O<!$NDL$j$G$"$k!#(B
                   2494: @table @var
                   2495: @item i=0
                   2496: @code{Print=0}, @code{PrintShort=0}
                   2497: @item i=1
                   2498: @code{Print=1}, @code{PrintShort=0}
                   2499: @item i=2
                   2500: @code{Print=0}, @code{PrintShort=1}
                   2501: @end table
                   2502: $B$3$l$O(B, @code{dp_gr_main()} $B$J$I$r%5%V%k!<%A%s$H$7$FMQ$$$k%f!<%6(B
                   2503: $BH!?t$K$*$$$F(B, $B$=$N%5%V%k!<%A%s$,Cf4V>pJs$NI=<((B
1.1       noro     2504: $B$r9T$&:]$K(B, $B?WB.$K%U%i%0$r8+$k$3$H$,$G$-$k$h$&$KMQ0U$5$l$F$$$k(B.
1.2       noro     2505: \E
                   2506: \BEG
                   2507: @item
                   2508: @code{dp_gr_flags()} sets and shows various parameters for Groebner basis
                   2509:  computation.
                   2510: @item
                   2511: If no argument is specified the current settings are returned.
                   2512: @item
                   2513: Arguments must be specified as a list such as
                   2514:  @code{["Print",1,"NoSugar",1,...]}. Names of parameters must be character
                   2515: strings.
                   2516: @item
                   2517: @code{dp_gr_print()} is used to set and show the value of a parameter
1.7       noro     2518: @code{Print} and @code{PrintShort}.
                   2519: @table @var
                   2520: @item i=0
                   2521: @code{Print=0}, @code{PrintShort=0}
                   2522: @item i=1
                   2523: @code{Print=1}, @code{PrintShort=0}
                   2524: @item i=2
                   2525: @code{Print=0}, @code{PrintShort=1}
                   2526: @end table
                   2527: This functions is prepared to get quickly the value
                   2528: when a user defined function calling @code{dp_gr_main()} etc.
1.2       noro     2529: uses the value as a flag for showing intermediate informations.
                   2530: \E
1.1       noro     2531: @end itemize
                   2532:
                   2533: @table @t
1.2       noro     2534: \JP @item $B;2>H(B
                   2535: \EG @item References
                   2536: \JP @fref{$B7W;;$*$h$SI=<($N@)8f(B}
                   2537: \EG @fref{Controlling Groebner basis computations}
1.1       noro     2538: @end table
                   2539:
1.2       noro     2540: \JP @node dp_ord,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2541: \EG @node dp_ord,,, Functions for Groebner basis computation
1.1       noro     2542: @subsection @code{dp_ord}
                   2543: @findex dp_ord
                   2544:
                   2545: @table @t
                   2546: @item dp_ord([@var{order}])
1.2       noro     2547: \JP :: $BJQ?t=g=x7?$N@_Dj(B, $B;2>H(B
                   2548: \EG :: Set and show the ordering type.
1.1       noro     2549: @end table
                   2550:
                   2551: @table @var
                   2552: @item return
1.2       noro     2553: \JP $BJQ?t=g=x7?(B ($B?t(B, $B%j%9%H$^$?$O9TNs(B)
                   2554: \EG ordering type (number, list or matrix)
1.1       noro     2555: @item order
1.2       noro     2556: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   2557: \EG number, list or matrix
1.1       noro     2558: @end table
                   2559:
                   2560: @itemize @bullet
1.2       noro     2561: \BJP
1.1       noro     2562: @item
                   2563: $B0z?t$,$"$k;~(B, $BJQ?t=g=x7?$r(B @var{order} $B$K@_Dj$9$k(B. $B0z?t$,$J$$;~(B,
                   2564: $B8=:_@_Dj$5$l$F$$$kJQ?t=g=x7?$rJV$9(B.
                   2565:
                   2566: @item
                   2567: $BJ,;6I=8=B?9`<0$K4X$9$kH!?t(B, $B1i;;$O0z?t$H$7$FJQ?t=g=x7?$r$H$k$b$N$H$H$i$J$$$b$N(B
                   2568: $B$,$"$j(B, $B$H$i$J$$$b$N$K4X$7$F$O(B, $B$=$N;~E@$G@_Dj$5$l$F$$$kCM$rMQ$$$F7W;;$,(B
                   2569: $B9T$o$l$k(B.
                   2570:
                   2571: @item
                   2572: @code{gr()} $B$J$I(B, $B0z?t$H$7$FJQ?t=g=x7?$r$H$k$b$N$O(B, $BFbIt$G(B @code{dp_ord()}
                   2573: $B$r8F$S=P$7(B, $BJQ?t=g=x7?$r@_Dj$9$k(B. $B$3$N@_Dj$O(B, $B7W;;=*N;8e$b@8$-;D$k(B.
                   2574:
                   2575: @item
                   2576: $BJ,;6I=8=B?9`<0$N;MB'1i;;$b(B, $B@_Dj$5$l$F$$$kCM$rMQ$$$F7W;;$5$l$k(B. $B=>$C$F(B,
                   2577: $B$=$NB?9`<0$,@8@.$5$l$?;~E@$K$*$1$kJQ?t=g=x7?$,(B, $B;MB'1i;;;~$K@5$7$/@_Dj(B
                   2578: $B$5$l$F$$$J$1$l$P$J$i$J$$(B. $B$^$?(B, $B1i;;BP>]$H$J$kB?9`<0$O(B, $BF10l$NJQ?t=g=x(B
                   2579: $B7?$K4p$E$$$F@8@.$5$l$?$b$N$G$J$1$l$P$J$i$J$$(B.
                   2580:
                   2581: @item
                   2582: $B%H%C%W%l%Y%kH!?t0J30$NH!?t$rD>@\8F$S=P$9>l9g$K$O(B, $B$3$NH!?t$K$h$j(B
                   2583: $BJQ?t=g=x7?$r@5$7$/@_Dj$7$J$1$l$P$J$i$J$$(B.
1.2       noro     2584: \E
                   2585: \BEG
                   2586: @item
                   2587: If an argument is specified, the function
                   2588: sets the current ordering type to @var{order}.
                   2589: If no argument is specified, the function returns the ordering
                   2590: type currently set.
                   2591:
                   2592: @item
                   2593: There are two types of functions concerning distributed polynomial,
                   2594: functions which take a ordering type and those which don't take it.
                   2595: The latter ones use the current setting.
                   2596:
                   2597: @item
                   2598: Functions such as @code{gr()}, which need a ordering type as an argument,
                   2599: call @code{dp_ord()} internally during the execution.
                   2600: The setting remains after the execution.
                   2601:
                   2602: Fundamental arithmetics for distributed polynomial also use the current
                   2603: setting. Therefore, when such arithmetics for distributed polynomials
                   2604: are done, the current setting must coincide with the ordering type
                   2605: which was used upon the creation of the polynomials. It is assumed
                   2606: that such polynomials were generated under the same ordering type.
                   2607:
                   2608: @item
                   2609: Type of term ordering must be correctly set by this function
                   2610: when functions other than top level functions are called directly.
                   2611: \E
1.1       noro     2612: @end itemize
                   2613:
                   2614: @example
                   2615: [19] dp_ord(0)$
                   2616: [20] <<1,2,3>>+<<3,1,1>>;
                   2617: (1)*<<1,2,3>>+(1)*<<3,1,1>>
                   2618: [21] dp_ord(2)$
                   2619: [22] <<1,2,3>>+<<3,1,1>>;
                   2620: (1)*<<3,1,1>>+(1)*<<1,2,3>>
                   2621: @end example
                   2622:
                   2623: @table @t
1.2       noro     2624: \JP @item $B;2>H(B
                   2625: \EG @item References
                   2626: \JP @fref{$B9`=g=x$N@_Dj(B}
                   2627: \EG @fref{Setting term orderings}
1.1       noro     2628: @end table
                   2629:
1.18    ! noro     2630: \JP @node dp_set_weight dp_set_top_weight dp_weyl_set_weight,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
        !          2631: \EG @node dp_set_weight dp_set_top_weight dp_weyl_set_weight,,, Functions for Groebner basis computation
        !          2632: @subsection @code{dp_set_weight}, @code{dp_set_top_weight}, @code{dp_weyl_set_weight}
        !          2633: @findex dp_set_weight
        !          2634: @findex dp_set_top_weight
        !          2635: @findex dp_weyl_set_weight
        !          2636:
        !          2637: @table @t
        !          2638: @item dp_set_weight([@var{weight}])
        !          2639: \JP :: sugar weight $B$N@_Dj(B, $B;2>H(B
        !          2640: \EG :: Set and show the sugar weight.
        !          2641: @item dp_set_top_weight([@var{weight}])
        !          2642: \JP :: top weight $B$N@_Dj(B, $B;2>H(B
        !          2643: \EG :: Set and show the top weight.
        !          2644: @item dp_weyl_set_weight([@var{weight}])
        !          2645: \JP :: weyl weight $B$N@_Dj(B, $B;2>H(B
        !          2646: \EG :: Set and show the weyl weight.
        !          2647: @end table
        !          2648:
        !          2649: @table @var
        !          2650: @item return
        !          2651: \JP $B%Y%/%H%k(B
        !          2652: \EG a vector
        !          2653: @item weight
        !          2654: \JP $B@0?t$N%j%9%H$^$?$O%Y%/%H%k(B
        !          2655: \EG a list or vector of integers
        !          2656: @end table
        !          2657:
        !          2658: @itemize @bullet
        !          2659: \BJP
        !          2660: @item
        !          2661: @code{dp_set_weight} $B$O(B sugar weight $B$r(B @var{weight} $B$K@_Dj$9$k(B. $B0z?t$,$J$$;~(B,
        !          2662: $B8=:_@_Dj$5$l$F$$$k(B sugar weight $B$rJV$9(B. sugar weight $B$O@5@0?t$r@.J,$H$9$k%Y%/%H%k$G(B,
        !          2663: $B3FJQ?t$N=E$_$rI=$9(B. $B<!?t$D$-=g=x$K$*$$$F(B, $BC19`<0$N<!?t$r7W;;$9$k:]$KMQ$$$i$l$k(B.
        !          2664: $B@F<!2=JQ?tMQ$K(B, $BKvHx$K(B 1 $B$rIU$12C$($F$*$/$H0BA4$G$"$k(B.
        !          2665: @item
        !          2666: @code{dp_set_top_weight} $B$O(B top weight $B$r(B @var{weight} $B$K@_Dj$9$k(B. $B0z?t$,$J$$;~(B,
        !          2667: $B8=:_@_Dj$5$l$F$$$k(B top weight $B$rJV$9(B. top weight $B$,@_Dj$5$l$F$$$k$H$-(B,
        !          2668: $B$^$:(B top weight $B$K$h$kC19`<0Hf3S$r@h$K9T$&(B. tie breaker $B$H$7$F8=:_@_Dj$5$l$F$$$k(B
        !          2669: $B9`=g=x$,MQ$$$i$l$k$,(B, $B$3$NHf3S$K$O(B top weight $B$OMQ$$$i$l$J$$(B.
        !          2670:
        !          2671: @item
        !          2672: @code{dp_weyl_set_weight} $B$O(B weyl weight $B$r(B @var{weight} $B$K@_Dj$9$k(B. $B0z?t$,$J$$;~(B,
        !          2673: $B8=:_@_Dj$5$l$F$$$k(B weyl weight $B$rJV$9(B. weyl weight w $B$r@_Dj$9$k$H(B,
        !          2674: $B9`=g=x7?(B 11 $B$G$N7W;;$K$*$$$F(B, (-w,w) $B$r(B top weight, tie breaker $B$r(B graded reverse lex
        !          2675: $B$H$7$?9`=g=x$,@_Dj$5$l$k(B.
        !          2676: \E
        !          2677: \BEG
        !          2678: @item
        !          2679: @code{dp_set_weight} sets the sugar weight=@var{weight}. It returns the current sugar weight.
        !          2680: A sugar weight is a vector with positive integer components and it represents the weights of variables.
        !          2681: It is used for computing the weight of a monomial in a graded ordering.
        !          2682: It is recommended to append a component 1 at the end of the weight vector for a homogenizing variable.
        !          2683: @item
        !          2684: @code{dp_set_top_weight} sets the top weight=@var{weight}. It returns the current top weight.
        !          2685: It a top weight is set, the weights of monomials under the top weight are firstly compared.
        !          2686: If the the weights are equal then the current term ordering is applied as a tie breaker, but
        !          2687: the top weight is not used in the tie breaker.
        !          2688:
        !          2689: @item
        !          2690: @code{dp_weyl_set_weight} sets the weyl weigh=@var{weight}. It returns the current weyl weight.
        !          2691: If a weyl weight w is set, in the comparsion by the term order type 11, a term order with
        !          2692: the top weight=(-w,w) and the tie breaker=graded reverse lex is applied.
        !          2693: \E
        !          2694: @end itemize
        !          2695:
        !          2696: @table @t
        !          2697: \JP @item $B;2>H(B
        !          2698: \EG @item References
        !          2699: @fref{Weight}
        !          2700: @end table
        !          2701:
        !          2702:
1.2       noro     2703: \JP @node dp_ptod,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2704: \EG @node dp_ptod,,, Functions for Groebner basis computation
1.1       noro     2705: @subsection @code{dp_ptod}
                   2706: @findex dp_ptod
                   2707:
                   2708: @table @t
                   2709: @item dp_ptod(@var{poly},@var{vlist})
1.2       noro     2710: \JP :: $BB?9`<0$rJ,;6I=8=B?9`<0$KJQ49$9$k(B.
                   2711: \EG :: Converts an ordinary polynomial into a distributed polynomial.
1.1       noro     2712: @end table
                   2713:
                   2714: @table @var
                   2715: @item return
1.2       noro     2716: \JP $BJ,;6I=8=B?9`<0(B
                   2717: \EG distributed polynomial
1.1       noro     2718: @item poly
1.2       noro     2719: \JP $BB?9`<0(B
                   2720: \EG polynomial
1.1       noro     2721: @item vlist
1.2       noro     2722: \JP $B%j%9%H(B
                   2723: \EG list
1.1       noro     2724: @end table
                   2725:
                   2726: @itemize @bullet
1.2       noro     2727: \BJP
1.1       noro     2728: @item
                   2729: $BJQ?t=g=x(B @var{vlist} $B$*$h$S8=:_$NJQ?t=g=x7?$K=>$C$FJ,;6I=8=B?9`<0$KJQ49$9$k(B.
                   2730: @item
                   2731: @var{vlist} $B$K4^$^$l$J$$ITDj85$O(B, $B78?tBN$KB0$9$k$H$7$FJQ49$5$l$k(B.
1.2       noro     2732: \E
                   2733: \BEG
                   2734: @item
                   2735: According to the variable ordering @var{vlist} and current
                   2736: type of term ordering, this function converts an ordinary
                   2737: polynomial into a distributed polynomial.
                   2738: @item
                   2739: Indeterminates not included in @var{vlist} are regarded to belong to
                   2740: the coefficient field.
                   2741: \E
1.1       noro     2742: @end itemize
                   2743:
                   2744: @example
                   2745: [50] dp_ord(0);
                   2746: 1
                   2747: [51] dp_ptod((x+y+z)^2,[x,y,z]);
                   2748: (1)*<<2,0,0>>+(2)*<<1,1,0>>+(1)*<<0,2,0>>+(2)*<<1,0,1>>+(2)*<<0,1,1>>
                   2749: +(1)*<<0,0,2>>
                   2750: [52] dp_ptod((x+y+z)^2,[x,y]);
1.5       noro     2751: (1)*<<2,0>>+(2)*<<1,1>>+(1)*<<0,2>>+(2*z)*<<1,0>>+(2*z)*<<0,1>>
                   2752: +(z^2)*<<0,0>>
1.1       noro     2753: @end example
                   2754:
                   2755: @table @t
1.2       noro     2756: \JP @item $B;2>H(B
                   2757: \EG @item References
1.1       noro     2758: @fref{dp_dtop},
                   2759: @fref{dp_ord}.
                   2760: @end table
                   2761:
1.2       noro     2762: \JP @node dp_dtop,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2763: \EG @node dp_dtop,,, Functions for Groebner basis computation
1.1       noro     2764: @subsection @code{dp_dtop}
                   2765: @findex dp_dtop
                   2766:
                   2767: @table @t
                   2768: @item dp_dtop(@var{dpoly},@var{vlist})
1.2       noro     2769: \JP :: $BJ,;6I=8=B?9`<0$rB?9`<0$KJQ49$9$k(B.
                   2770: \EG :: Converts a distributed polynomial into an ordinary polynomial.
1.1       noro     2771: @end table
                   2772:
                   2773: @table @var
                   2774: @item return
1.2       noro     2775: \JP $BB?9`<0(B
                   2776: \EG polynomial
1.1       noro     2777: @item dpoly
1.2       noro     2778: \JP $BJ,;6I=8=B?9`<0(B
                   2779: \EG distributed polynomial
1.1       noro     2780: @item vlist
1.2       noro     2781: \JP $B%j%9%H(B
                   2782: \EG list
1.1       noro     2783: @end table
                   2784:
                   2785: @itemize @bullet
1.2       noro     2786: \BJP
1.1       noro     2787: @item
                   2788: $BJ,;6I=8=B?9`<0$r(B, $BM?$($i$l$?ITDj85%j%9%H$rMQ$$$FB?9`<0$KJQ49$9$k(B.
                   2789: @item
                   2790: $BITDj85%j%9%H$O(B, $BD9$5J,;6I=8=B?9`<0$NJQ?t$N8D?t$H0lCW$7$F$$$l$P2?$G$b$h$$(B.
1.2       noro     2791: \E
                   2792: \BEG
                   2793: @item
                   2794: This function converts a distributed polynomial into an ordinary polynomial
                   2795: according to a list of indeterminates @var{vlist}.
                   2796: @item
                   2797: @var{vlist} is such a list that its length coincides with the number of
                   2798: variables of @var{dpoly}.
                   2799: \E
1.1       noro     2800: @end itemize
                   2801:
                   2802: @example
                   2803: [53] T=dp_ptod((x+y+z)^2,[x,y]);
1.5       noro     2804: (1)*<<2,0>>+(2)*<<1,1>>+(1)*<<0,2>>+(2*z)*<<1,0>>+(2*z)*<<0,1>>
                   2805: +(z^2)*<<0,0>>
1.1       noro     2806: [54] P=dp_dtop(T,[a,b]);
                   2807: z^2+(2*a+2*b)*z+a^2+2*b*a+b^2
                   2808: @end example
                   2809:
1.2       noro     2810: \JP @node dp_mod dp_rat,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2811: \EG @node dp_mod dp_rat,,, Functions for Groebner basis computation
1.1       noro     2812: @subsection @code{dp_mod}, @code{dp_rat}
                   2813: @findex dp_mod
                   2814: @findex dp_rat
                   2815:
                   2816: @table @t
                   2817: @item dp_mod(@var{p},@var{mod},@var{subst})
1.2       noro     2818: \JP :: $BM-M}?t78?tJ,;6I=8=B?9`<0$NM-8BBN78?t$X$NJQ49(B
                   2819: \EG :: Converts a disributed polynomial into one with coefficients in a finite field.
1.1       noro     2820: @item dp_rat(@var{p})
1.2       noro     2821: \JP :: $BM-8BBN78?tJ,;6I=8=B?9`<0$NM-M}?t78?t$X$NJQ49(B
                   2822: \BEG
                   2823: :: Converts a distributed polynomial with coefficients in a finite field into
                   2824: one with coefficients in the rationals.
                   2825: \E
1.1       noro     2826: @end table
                   2827:
                   2828: @table @var
                   2829: @item return
1.2       noro     2830: \JP $BJ,;6I=8=B?9`<0(B
                   2831: \EG distributed polynomial
1.1       noro     2832: @item p
1.2       noro     2833: \JP $BJ,;6I=8=B?9`<0(B
                   2834: \EG distributed polynomial
1.1       noro     2835: @item mod
1.2       noro     2836: \JP $BAG?t(B
                   2837: \EG prime
1.1       noro     2838: @item subst
1.2       noro     2839: \JP $B%j%9%H(B
                   2840: \EG list
1.1       noro     2841: @end table
                   2842:
                   2843: @itemize @bullet
1.2       noro     2844: \BJP
1.1       noro     2845: @item
                   2846: @code{dp_nf_mod()}, @code{dp_true_nf_mod()} $B$O(B, $BF~NO$H$7$FM-8BBN78?t$N(B
                   2847: $BJ,;6I=8=B?9`<0$rI,MW$H$9$k(B. $B$3$N$h$&$J>l9g(B, @code{dp_mod()} $B$K$h$j(B
                   2848: $BM-M}?t78?tJ,;6I=8=B?9`<0$rJQ49$7$FMQ$$$k$3$H$,$G$-$k(B. $B$^$?(B, $BF@$i$l$?(B
                   2849: $B7k2L$O(B, $BM-8BBN78?tB?9`<0$H$O1i;;$G$-$k$,(B, $BM-M}?t78?tB?9`<0$H$O1i;;$G$-$J$$(B
                   2850: $B$?$a(B, @code{dp_rat()} $B$K$h$jJQ49$9$kI,MW$,$"$k(B.
                   2851: @item
                   2852: $BM-8BBN78?t$N1i;;$K$*$$$F$O(B, $B$"$i$+$8$a(B @code{setmod()} $B$K$h$jM-8BBN$N85$N(B
                   2853: $B8D?t$r;XDj$7$F$*$/I,MW$,$"$k(B.
                   2854: @item
                   2855: @var{subst} $B$O(B, $B78?t$,M-M}<0$N>l9g(B, $B$=$NM-M}<0$NJQ?t$K$"$i$+$8$a?t$rBeF~(B
                   2856: $B$7$?8eM-8BBN78?t$KJQ49$9$k$H$$$&A`:n$r9T$&:]$N(B, $BBeF~CM$r;XDj$9$k$b$N$G(B,
                   2857: @code{[[@var{var},@var{value}],...]} $B$N7A$N%j%9%H$G$"$k(B.
1.2       noro     2858: \E
                   2859: \BEG
                   2860: @item
                   2861: @code{dp_nf_mod()} and @code{dp_true_nf_mod()} require
                   2862: distributed polynomials with coefficients in a finite field as arguments.
                   2863: @code{dp_mod()} is used to convert distributed polynomials with rational
                   2864: number coefficients into appropriate ones.
                   2865: Polynomials with coefficients in a finite field
                   2866: cannot be used as inputs of operations with polynomials
                   2867: with rational number coefficients. @code{dp_rat()} is used for such cases.
                   2868: @item
                   2869: The ground finite field must be set in advance by using @code{setmod()}.
                   2870: @item
                   2871: @var{subst} is such a list as @code{[[@var{var},@var{value}],...]}.
                   2872: This is valid when the ground field of the input polynomial is a
                   2873: rational function field. @var{var}'s are variables in the ground field and
                   2874: the list means that @var{value} is substituted for @var{var} before
                   2875: converting the coefficients into elements of a finite field.
                   2876: \E
1.1       noro     2877: @end itemize
                   2878:
                   2879: @example
                   2880: @end example
                   2881:
                   2882: @table @t
1.2       noro     2883: \JP @item $B;2>H(B
                   2884: \EG @item References
1.18    ! noro     2885: @fref{dp_nf dp_nf_mod dp_true_nf dp_true_nf_mod dp_weyl_nf dp_weyl_nf_mod},
1.1       noro     2886: @fref{subst psubst},
                   2887: @fref{setmod}.
                   2888: @end table
                   2889:
1.2       noro     2890: \JP @node dp_homo dp_dehomo,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2891: \EG @node dp_homo dp_dehomo,,, Functions for Groebner basis computation
1.1       noro     2892: @subsection @code{dp_homo}, @code{dp_dehomo}
                   2893: @findex dp_homo
                   2894: @findex dp_dehomo
                   2895:
                   2896: @table @t
                   2897: @item dp_homo(@var{dpoly})
1.2       noro     2898: \JP :: $BJ,;6I=8=B?9`<0$N@F<!2=(B
                   2899: \EG :: Homogenize a distributed polynomial
1.1       noro     2900: @item dp_dehomo(@var{dpoly})
1.2       noro     2901: \JP :: $B@F<!J,;6I=8=B?9`<0$NHs@F<!2=(B
                   2902: \EG :: Dehomogenize a homogenious distributed polynomial
1.1       noro     2903: @end table
                   2904:
                   2905: @table @var
                   2906: @item return
1.2       noro     2907: \JP $BJ,;6I=8=B?9`<0(B
                   2908: \EG distributed polynomial
1.1       noro     2909: @item dpoly
1.2       noro     2910: \JP $BJ,;6I=8=B?9`<0(B
                   2911: \EG distributed polynomial
1.1       noro     2912: @end table
                   2913:
                   2914: @itemize @bullet
1.2       noro     2915: \BJP
1.1       noro     2916: @item
                   2917: @code{dp_homo()} $B$O(B, @var{dpoly} $B$N(B $B3F9`(B @var{t} $B$K$D$$$F(B, $B;X?t%Y%/%H%k$ND9$5$r(B
                   2918: 1 $B?-$P$7(B, $B:G8e$N@.J,$NCM$r(B @var{d}-@code{deg(@var{t})}
                   2919: (@var{d} $B$O(B @var{dpoly} $B$NA4<!?t(B) $B$H$7$?J,;6I=8=B?9`<0$rJV$9(B.
                   2920: @item
                   2921: @code{dp_dehomo()} $B$O(B, @var{dpoly} $B$N3F9`$K$D$$$F(B, $B;X?t%Y%/%H%k$N:G8e$N@.J,(B
                   2922: $B$r<h$j=|$$$?J,;6B?9`<0$rJV$9(B.
                   2923: @item
                   2924: $B$$$:$l$b(B, $B@8@.$5$l$?B?9`<0$rMQ$$$?1i;;$r9T$&>l9g(B, $B$=$l$i$KE,9g$9$k9`=g=x$r(B
                   2925: $B@5$7$/@_Dj$9$kI,MW$,$"$k(B.
                   2926: @item
                   2927: @code{hgr()} $B$J$I$K$*$$$F(B, $BFbItE*$KMQ$$$i$l$F$$$k(B.
1.2       noro     2928: \E
                   2929: \BEG
                   2930: @item
                   2931: @code{dp_homo()} makes a copy of @var{dpoly}, extends
                   2932: the length of the exponent vector of each term @var{t} in the copy by 1,
                   2933: and sets the value of the newly appended
                   2934: component to @var{d}-@code{deg(@var{t})}, where @var{d} is the total
                   2935: degree of @var{dpoly}.
                   2936: @item
                   2937: @code{dp_dehomo()} make a copy of @var{dpoly} and removes the last component
                   2938: of each terms in the copy.
                   2939: @item
                   2940: Appropriate term orderings must be set when the results are used as inputs
                   2941: of some operations.
                   2942: @item
                   2943: These are used internally in @code{hgr()} etc.
                   2944: \E
1.1       noro     2945: @end itemize
                   2946:
                   2947: @example
                   2948: [202] X=<<1,2,3>>+3*<<1,2,1>>;
                   2949: (1)*<<1,2,3>>+(3)*<<1,2,1>>
                   2950: [203] dp_homo(X);
                   2951: (1)*<<1,2,3,0>>+(3)*<<1,2,1,2>>
                   2952: [204] dp_dehomo(@@);
                   2953: (1)*<<1,2,3>>+(3)*<<1,2,1>>
                   2954: @end example
                   2955:
                   2956: @table @t
1.2       noro     2957: \JP @item $B;2>H(B
                   2958: \EG @item References
1.1       noro     2959: @fref{gr hgr gr_mod}.
                   2960: @end table
                   2961:
1.2       noro     2962: \JP @node dp_ptozp dp_prim,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   2963: \EG @node dp_ptozp dp_prim,,, Functions for Groebner basis computation
1.1       noro     2964: @subsection @code{dp_ptozp}, @code{dp_prim}
                   2965: @findex dp_ptozp
                   2966: @findex dp_prim
                   2967:
                   2968: @table @t
                   2969: @item dp_ptozp(@var{dpoly})
1.2       noro     2970: \JP :: $BDj?tG\$7$F78?t$r@0?t78?t$+$D78?t$N@0?t(B GCD $B$r(B 1 $B$K$9$k(B.
                   2971: \BEG
                   2972: :: Converts a distributed polynomial @var{poly} with rational coefficients
                   2973: into an integral distributed polynomial such that GCD of all its coefficients
                   2974: is 1.
                   2975: \E
1.1       noro     2976: @itemx dp_prim(@var{dpoly})
1.2       noro     2977: \JP :: $BM-M}<0G\$7$F78?t$r@0?t78?tB?9`<078?t$+$D78?t$NB?9`<0(B GCD $B$r(B 1 $B$K$9$k(B.
                   2978: \BEG
                   2979: :: Converts a distributed polynomial @var{poly} with rational function
                   2980: coefficients into an integral distributed polynomial such that polynomial
                   2981: GCD of all its coefficients is 1.
                   2982: \E
1.1       noro     2983: @end table
                   2984:
                   2985: @table @var
                   2986: @item return
1.2       noro     2987: \JP $BJ,;6I=8=B?9`<0(B
                   2988: \EG distributed polynomial
1.1       noro     2989: @item dpoly
1.2       noro     2990: \JP $BJ,;6I=8=B?9`<0(B
                   2991: \EG distributed polynomial
1.1       noro     2992: @end table
                   2993:
                   2994: @itemize @bullet
1.2       noro     2995: \BJP
1.1       noro     2996: @item
                   2997: @code{dp_ptozp()} $B$O(B,  @code{ptozp()} $B$KAjEv$9$kA`:n$rJ,;6I=8=B?9`<0$K(B
                   2998: $BBP$7$F9T$&(B. $B78?t$,B?9`<0$r4^$`>l9g(B, $B78?t$K4^$^$l$kB?9`<06&DL0x;R$O(B
                   2999: $B<h$j=|$+$J$$(B.
                   3000: @item
                   3001: @code{dp_prim()} $B$O(B, $B78?t$,B?9`<0$r4^$`>l9g(B, $B78?t$K4^$^$l$kB?9`<06&DL0x;R(B
                   3002: $B$r<h$j=|$/(B.
1.2       noro     3003: \E
                   3004: \BEG
                   3005: @item
                   3006: @code{dp_ptozp()} executes the same operation as @code{ptozp()} for
                   3007: a distributed polynomial. If the coefficients include polynomials,
                   3008: polynomial contents included in the coefficients are not removed.
                   3009: @item
                   3010: @code{dp_prim()} removes polynomial contents.
                   3011: \E
1.1       noro     3012: @end itemize
                   3013:
                   3014: @example
                   3015: [208] X=dp_ptod(3*(x-y)*(y-z)*(z-x),[x]);
                   3016: (-3*y+3*z)*<<2>>+(3*y^2-3*z^2)*<<1>>+(-3*z*y^2+3*z^2*y)*<<0>>
                   3017: [209] dp_ptozp(X);
                   3018: (-y+z)*<<2>>+(y^2-z^2)*<<1>>+(-z*y^2+z^2*y)*<<0>>
                   3019: [210] dp_prim(X);
                   3020: (1)*<<2>>+(-y-z)*<<1>>+(z*y)*<<0>>
                   3021: @end example
                   3022:
                   3023: @table @t
1.2       noro     3024: \JP @item $B;2>H(B
                   3025: \EG @item References
1.1       noro     3026: @fref{ptozp}.
                   3027: @end table
                   3028:
1.18    ! noro     3029: \JP @node dp_nf dp_nf_mod dp_true_nf dp_true_nf_mod dp_weyl_nf dp_weyl_nf_mod,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
        !          3030: \EG @node dp_nf dp_nf_mod dp_true_nf dp_true_nf_mod dp_weyl_nf dp_weyl_nf_mod,,, Functions for Groebner basis computation
1.1       noro     3031: @subsection @code{dp_nf}, @code{dp_nf_mod}, @code{dp_true_nf}, @code{dp_true_nf_mod}
                   3032: @findex dp_nf
                   3033: @findex  dp_true_nf
                   3034: @findex dp_nf_mod
                   3035: @findex  dp_true_nf_mod
1.18    ! noro     3036: @findex dp_weyl_nf
        !          3037: @findex dp_weyl_nf_mod
1.1       noro     3038:
                   3039: @table @t
                   3040: @item dp_nf(@var{indexlist},@var{dpoly},@var{dpolyarray},@var{fullreduce})
1.18    ! noro     3041: @item dp_weyl_nf(@var{indexlist},@var{dpoly},@var{dpolyarray},@var{fullreduce})
1.1       noro     3042: @item dp_nf_mod(@var{indexlist},@var{dpoly},@var{dpolyarray},@var{fullreduce},@var{mod})
1.18    ! noro     3043: @item dp_weyl_nf_mod(@var{indexlist},@var{dpoly},@var{dpolyarray},@var{fullreduce},@var{mod})
1.2       noro     3044: \JP :: $BJ,;6I=8=B?9`<0$N@55,7A$r5a$a$k(B. ($B7k2L$ODj?tG\$5$l$F$$$k2DG=@-$"$j(B)
1.1       noro     3045:
1.2       noro     3046: \BEG
                   3047: :: Computes the normal form of a distributed polynomial.
                   3048: (The result may be multiplied by a constant in the ground field.)
                   3049: \E
1.1       noro     3050: @item dp_true_nf(@var{indexlist},@var{dpoly},@var{dpolyarray},@var{fullreduce})
                   3051: @item dp_true_nf_mod(@var{indexlist},@var{dpoly},@var{dpolyarray},@var{fullreduce},@var{mod})
1.2       noro     3052: \JP :: $BJ,;6I=8=B?9`<0$N@55,7A$r5a$a$k(B. ($B??$N7k2L$r(B @code{[$BJ,;R(B, $BJ,Jl(B]} $B$N7A$GJV$9(B)
                   3053: \BEG
                   3054: :: Computes the normal form of a distributed polynomial. (The true result
                   3055: is returned in such a list as @code{[numerator, denominator]})
                   3056: \E
1.1       noro     3057: @end table
                   3058:
                   3059: @table @var
                   3060: @item return
1.2       noro     3061: \JP @code{dp_nf()} : $BJ,;6I=8=B?9`<0(B, @code{dp_true_nf()} : $B%j%9%H(B
                   3062: \EG @code{dp_nf()} : distributed polynomial, @code{dp_true_nf()} : list
1.1       noro     3063: @item indexlist
1.2       noro     3064: \JP $B%j%9%H(B
                   3065: \EG list
1.1       noro     3066: @item dpoly
1.2       noro     3067: \JP $BJ,;6I=8=B?9`<0(B
                   3068: \EG distributed polynomial
1.1       noro     3069: @item dpolyarray
1.2       noro     3070: \JP $BG[Ns(B
                   3071: \EG array of distributed polynomial
1.1       noro     3072: @item fullreduce
1.2       noro     3073: \JP $B%U%i%0(B
                   3074: \EG flag
1.1       noro     3075: @item mod
1.2       noro     3076: \JP $BAG?t(B
                   3077: \EG prime
1.1       noro     3078: @end table
                   3079:
                   3080: @itemize @bullet
1.2       noro     3081: \BJP
1.1       noro     3082: @item
                   3083: $BJ,;6I=8=B?9`<0(B @var{dpoly} $B$N@55,7A$r5a$a$k(B.
                   3084: @item
1.18    ! noro     3085: $BL>A0$K(B weyl $B$r4^$`4X?t$O%o%$%kBe?t$K$*$1$k@55,7A7W;;$r9T$&(B. $B0J2<$N@bL@$O(B weyl $B$r4^$`$b$N$KBP$7$F$bF1MM$K@.N)$9$k(B.
        !          3086: @item
1.1       noro     3087: @code{dp_nf_mod()}, @code{dp_true_nf_mod()} $B$NF~NO$O(B, @code{dp_mod()} $B$J$I(B
                   3088: $B$K$h$j(B, $BM-8BBN>e$NJ,;6I=8=B?9`<0$K$J$C$F$$$J$1$l$P$J$i$J$$(B.
                   3089: @item
                   3090: $B7k2L$KM-M}?t(B, $BM-M}<0$,4^$^$l$k$N$rHr$1$k$?$a(B, @code{dp_nf()} $B$O(B
                   3091: $B??$NCM$NDj?tG\$NCM$rJV$9(B. $BM-M}<078?t$N>l9g$N(B @code{dp_nf_mod()} $B$bF1MM(B
                   3092: $B$G$"$k$,(B, $B78?tBN$,M-8BBN$N>l9g(B @code{dp_nf_mod()} $B$O??$NCM$rJV$9(B.
                   3093: @item
                   3094: @code{dp_true_nf()}, @code{dp_true_nf_mod()} $B$O(B,
                   3095: @code{[@var{nm},@var{dn}]} $B$J$k7A$N%j%9%H$rJV$9(B.
                   3096: $B$?$@$7(B, @var{nm} $B$O78?t$KJ,?t(B, $BM-M}<0$r4^$^$J$$J,;6I=8=B?9`<0(B, @var{dn} $B$O(B
                   3097: $B?t$^$?$OB?9`<0$G(B @var{nm}/@var{dn} $B$,??$NCM$H$J$k(B.
                   3098: @item
                   3099: @var{dpolyarray} $B$OJ,;6I=8=B?9`<0$rMWAG$H$9$k%Y%/%H%k(B,
                   3100: @var{indexlist} $B$O@55,2=7W;;$KMQ$$$k(B @var{dpolyarray} $B$NMWAG$N%$%s%G%C%/%9(B
                   3101: $B$N%j%9%H(B.
                   3102: @item
                   3103: @var{fullreduce} $B$,(B 0 $B$G$J$$$H$-A4$F$N9`$KBP$7$F4JLs$r9T$&(B. @var{fullreduce}
                   3104: $B$,(B 0 $B$N$H$-F,9`$N$_$KBP$7$F4JLs$r9T$&(B.
                   3105: @item
                   3106: @var{indexlist} $B$G;XDj$5$l$?B?9`<0$O(B, $BA0$NJ}$N$b$N$,M%@hE*$K;H$o$l$k(B.
                   3107: @item
                   3108: $B0lHL$K$O(B @var{indexlist} $B$NM?$(J}$K$h$jH!?t$NCM$O0[$J$k2DG=@-$,$"$k$,(B,
                   3109: $B%0%l%V%J4pDl$KBP$7$F$O0l0UE*$KDj$^$k(B.
                   3110: @item
                   3111: $BJ,;6I=8=$G$J$$8GDj$5$l$?B?9`<0=89g$K$h$k@55,7A$rB??t5a$a$kI,MW$,$"$k>l9g(B
                   3112: $B$KJXMx$G$"$k(B. $BC10l$N1i;;$K4X$7$F$O(B, @code{p_nf}, @code{p_true_nf} $B$r(B
                   3113: $BMQ$$$k$H$h$$(B.
1.2       noro     3114: \E
                   3115: \BEG
                   3116: @item
                   3117: Computes the normal form of a distributed polynomial.
                   3118: @item
1.18    ! noro     3119: Functions whose name contain @code{weyl} compute normal forms in Weyl algebra. The description below also applies to
        !          3120: the functions for Weyl algebra.
        !          3121: @item
1.2       noro     3122: @code{dp_nf_mod()} and @code{dp_true_nf_mod()} require
                   3123: distributed polynomials with coefficients in a finite field as arguments.
                   3124: @item
                   3125: The result of @code{dp_nf()} may be multiplied by a constant in the
                   3126: ground field in order to make the result integral. The same is true
                   3127: for @code{dp_nf_mod()}, but it returns the true normal form if
                   3128: the ground field is a finite field.
                   3129: @item
                   3130: @code{dp_true_nf()} and @code{dp_true_nf_mod()} return
                   3131: such a list as @code{[@var{nm},@var{dn}]}.
                   3132: Here @var{nm} is a distributed polynomial whose coefficients are integral
                   3133: in the ground field, @var{dn} is an integral element in the ground
                   3134: field and @var{nm}/@var{dn} is the true normal form.
                   3135: @item
                   3136: @var{dpolyarray} is a vector whose components are distributed polynomials
                   3137: and @var{indexlist} is a list of indices which is used for the normal form
                   3138: computation.
                   3139: @item
                   3140: When argument @var{fullreduce} has non-zero value,
                   3141: all terms are reduced. When it has value 0,
                   3142: only the head term is reduced.
                   3143: @item
                   3144: As for the polynomials specified by @var{indexlist}, one specified by
                   3145: an index placed at the preceding position has priority to be selected.
                   3146: @item
                   3147: In general, the result of the function may be different depending on
                   3148: @var{indexlist}.  However, the result is unique for Groebner bases.
                   3149: @item
                   3150: These functions are useful when a fixed non-distributed polynomial set
                   3151: is used as a set of reducers to compute normal forms of many polynomials.
                   3152: For single computation @code{p_nf} and @code{p_true_nf} are sufficient.
                   3153: \E
1.1       noro     3154: @end itemize
                   3155:
                   3156: @example
                   3157: [0] load("gr")$
                   3158: [64] load("katsura")$
                   3159: [69] K=katsura(4)$
                   3160: [70] dp_ord(2)$
                   3161: [71] V=[u0,u1,u2,u3,u4]$
                   3162: [72] DP1=newvect(length(K),map(dp_ptod,K,V))$
                   3163: [73] G=gr(K,V,2)$
                   3164: [74] DP2=newvect(length(G),map(dp_ptod,G,V))$
                   3165: [75] T=dp_ptod((u0-u1+u2-u3+u4)^2,V)$
                   3166: [76] dp_dtop(dp_nf([0,1,2,3,4],T,DP1,1),V);
1.5       noro     3167: u4^2+(6*u3+2*u2+6*u1-2)*u4+9*u3^2+(6*u2+18*u1-6)*u3+u2^2
                   3168: +(6*u1-2)*u2+9*u1^2-6*u1+1
1.1       noro     3169: [77] dp_dtop(dp_nf([4,3,2,1,0],T,DP1,1),V);
                   3170: -5*u4^2+(-4*u3-4*u2-4*u1)*u4-u3^2-3*u3-u2^2+(2*u1-1)*u2-2*u1^2-3*u1+1
                   3171: [78] dp_dtop(dp_nf([0,1,2,3,4],T,DP2,1),V);
1.5       noro     3172: -11380879768451657780886122972730785203470970010204714556333530492210
                   3173: 456775930005716505560062087150928400876150217079820311439477560587583
                   3174: 488*u4^15+...
1.1       noro     3175: [79] dp_dtop(dp_nf([4,3,2,1,0],T,DP2,1),V);
1.5       noro     3176: -11380879768451657780886122972730785203470970010204714556333530492210
                   3177: 456775930005716505560062087150928400876150217079820311439477560587583
                   3178: 488*u4^15+...
1.1       noro     3179: [80] @@78==@@79;
                   3180: 1
                   3181: @end example
                   3182:
                   3183: @table @t
1.2       noro     3184: \JP @item $B;2>H(B
                   3185: \EG @item References
1.1       noro     3186: @fref{dp_dtop},
                   3187: @fref{dp_ord},
                   3188: @fref{dp_mod dp_rat},
                   3189: @fref{p_nf p_nf_mod p_true_nf p_true_nf_mod}.
                   3190: @end table
                   3191:
1.2       noro     3192: \JP @node dp_hm dp_ht dp_hc dp_rest,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3193: \EG @node dp_hm dp_ht dp_hc dp_rest,,, Functions for Groebner basis computation
1.1       noro     3194: @subsection @code{dp_hm}, @code{dp_ht}, @code{dp_hc}, @code{dp_rest}
                   3195: @findex dp_hm
                   3196: @findex dp_ht
                   3197: @findex dp_hc
                   3198: @findex dp_rest
                   3199:
                   3200: @table @t
                   3201: @item dp_hm(@var{dpoly})
1.2       noro     3202: \JP :: $BF,C19`<0$r<h$j=P$9(B.
                   3203: \EG :: Gets the head monomial.
1.1       noro     3204: @item dp_ht(@var{dpoly})
1.2       noro     3205: \JP :: $BF,9`$r<h$j=P$9(B.
                   3206: \EG :: Gets the head term.
1.1       noro     3207: @item dp_hc(@var{dpoly})
1.2       noro     3208: \JP :: $BF,78?t$r<h$j=P$9(B.
                   3209: \EG :: Gets the head coefficient.
1.1       noro     3210: @item dp_rest(@var{dpoly})
1.2       noro     3211: \JP :: $BF,C19`<0$r<h$j=|$$$?;D$j$rJV$9(B.
                   3212: \EG :: Gets the remainder of the polynomial where the head monomial is removed.
1.1       noro     3213: @end table
                   3214:
                   3215: @table @var
1.2       noro     3216: \BJP
1.1       noro     3217: @item return
                   3218: @code{dp_hm()}, @code{dp_ht()}, @code{dp_rest()} : $BJ,;6I=8=B?9`<0(B,
                   3219: @code{dp_hc()} : $B?t$^$?$OB?9`<0(B
                   3220: @item dpoly
                   3221: $BJ,;6I=8=B?9`<0(B
1.2       noro     3222: \E
                   3223: \BEG
                   3224: @item return
                   3225: @code{dp_hm()}, @code{dp_ht()}, @code{dp_rest()} : distributed polynomial
                   3226: @code{dp_hc()} : number or polynomial
                   3227: @item dpoly
                   3228: distributed polynomial
                   3229: \E
1.1       noro     3230: @end table
                   3231:
                   3232: @itemize @bullet
1.2       noro     3233: \BJP
1.1       noro     3234: @item
                   3235: $B$3$l$i$O(B, $BJ,;6I=8=B?9`<0$N3FItJ,$r<h$j=P$9$?$a$NH!?t$G$"$k(B.
                   3236: @item
                   3237: $BJ,;6I=8=B?9`<0(B @var{p} $B$KBP$7<!$,@.$jN)$D(B.
1.2       noro     3238: \E
                   3239: \BEG
                   3240: @item
                   3241: These are used to get various parts of a distributed polynomial.
                   3242: @item
                   3243: The next equations hold for a distributed polynomial @var{p}.
                   3244: \E
1.1       noro     3245: @table @code
                   3246: @item @var{p} = dp_hm(@var{p}) + dp_rest(@var{p})
                   3247: @item dp_hm(@var{p}) = dp_hc(@var{p}) dp_ht(@var{p})
                   3248: @end table
                   3249: @end itemize
                   3250:
                   3251: @example
                   3252: [87] dp_ord(0)$
                   3253: [88] X=ptozp((a46^2+7/10*a46+7/48)*u3^4-50/27*a46^2-35/27*a46-49/216)$
                   3254: [89] T=dp_ptod(X,[u3,u4,a46])$
                   3255: [90] dp_hm(T);
                   3256: (2160)*<<4,0,2>>
                   3257: [91] dp_ht(T);
                   3258: (1)*<<4,0,2>>
                   3259: [92] dp_hc(T);
                   3260: 2160
                   3261: [93] dp_rest(T);
                   3262: (1512)*<<4,0,1>>+(315)*<<4,0,0>>+(-4000)*<<0,0,2>>+(-2800)*<<0,0,1>>
                   3263: +(-490)*<<0,0,0>>
                   3264: @end example
                   3265:
1.2       noro     3266: \JP @node dp_td dp_sugar,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3267: \EG @node dp_td dp_sugar,,, Functions for Groebner basis computation
1.1       noro     3268: @subsection @code{dp_td}, @code{dp_sugar}
                   3269: @findex dp_td
                   3270: @findex dp_sugar
                   3271:
                   3272: @table @t
                   3273: @item dp_td(@var{dpoly})
1.2       noro     3274: \JP :: $BF,9`$NA4<!?t$rJV$9(B.
                   3275: \EG :: Gets the total degree of the head term.
1.1       noro     3276: @item dp_sugar(@var{dpoly})
1.2       noro     3277: \JP :: $BB?9`<0$N(B @code{sugar} $B$rJV$9(B.
                   3278: \EG :: Gets the @code{sugar} of a polynomial.
1.1       noro     3279: @end table
                   3280:
                   3281: @table @var
                   3282: @item return
1.2       noro     3283: \JP $B<+A3?t(B
                   3284: \EG non-negative integer
1.1       noro     3285: @item dpoly
1.2       noro     3286: \JP $BJ,;6I=8=B?9`<0(B
                   3287: \EG distributed polynomial
1.1       noro     3288: @item onoff
1.2       noro     3289: \JP $B%U%i%0(B
                   3290: \EG flag
1.1       noro     3291: @end table
                   3292:
                   3293: @itemize @bullet
1.2       noro     3294: \BJP
1.1       noro     3295: @item
                   3296: @code{dp_td()} $B$O(B, $BF,9`$NA4<!?t(B, $B$9$J$o$A3FJQ?t$N;X?t$NOB$rJV$9(B.
                   3297: @item
                   3298: $BJ,;6I=8=B?9`<0$,@8@.$5$l$k$H(B, @code{sugar} $B$H8F$P$l$k$"$k@0?t$,IUM?(B
                   3299: $B$5$l$k(B. $B$3$NCM$O(B $B2>A[E*$K@F<!2=$7$F7W;;$7$?>l9g$K7k2L$,;}$DA4<!?t$NCM$H$J$k(B.
                   3300: @item
                   3301: @code{sugar} $B$O(B, $B%0%l%V%J4pDl7W;;$K$*$1$k@55,2=BP$NA*Br$N%9%H%i%F%8$r(B
                   3302: $B7hDj$9$k$?$a$N=EMW$J;X?K$H$J$k(B.
1.2       noro     3303: \E
                   3304: \BEG
                   3305: @item
                   3306: Function @code{dp_td()} returns the total degree of the head term,
                   3307: i.e., the sum of all exponent of variables in that term.
                   3308: @item
                   3309: Upon creation of a distributed polynomial, an integer called @code{sugar}
                   3310: is associated.  This value is
                   3311: the total degree of the virtually homogenized one of the original
                   3312: polynomial.
                   3313: @item
                   3314: The quantity @code{sugar} is an important guide to determine the
                   3315: selection strategy of critical pairs in Groebner basis computation.
                   3316: \E
1.1       noro     3317: @end itemize
                   3318:
                   3319: @example
                   3320: [74] dp_ord(0)$
                   3321: [75] X=<<1,2>>+<<0,1>>$
                   3322: [76] Y=<<1,2>>+<<1,0>>$
                   3323: [77] Z=X-Y;
                   3324: (-1)*<<1,0>>+(1)*<<0,1>>
                   3325: [78] dp_sugar(T);
                   3326: 3
                   3327: @end example
                   3328:
1.2       noro     3329: \JP @node dp_lcm,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3330: \EG @node dp_lcm,,, Functions for Groebner basis computation
1.1       noro     3331: @subsection @code{dp_lcm}
                   3332: @findex dp_lcm
                   3333:
                   3334: @table @t
                   3335: @item dp_lcm(@var{dpoly1},@var{dpoly2})
1.2       noro     3336: \JP :: $B:G>.8xG\9`$rJV$9(B.
                   3337: \EG :: Returns the least common multiple of the head terms of the given two polynomials.
1.1       noro     3338: @end table
                   3339:
                   3340: @table @var
                   3341: @item return
1.2       noro     3342: \JP $BJ,;6I=8=B?9`<0(B
                   3343: \EG distributed polynomial
1.4       noro     3344: @item dpoly1  dpoly2
1.2       noro     3345: \JP $BJ,;6I=8=B?9`<0(B
                   3346: \EG distributed polynomial
1.1       noro     3347: @end table
                   3348:
                   3349: @itemize @bullet
1.2       noro     3350: \BJP
1.1       noro     3351: @item
                   3352: $B$=$l$>$l$N0z?t$NF,9`$N:G>.8xG\9`$rJV$9(B. $B78?t$O(B 1 $B$G$"$k(B.
1.2       noro     3353: \E
                   3354: \BEG
                   3355: @item
                   3356: Returns the least common multiple of the head terms of the given
                   3357: two polynomials, where coefficient is always set to 1.
                   3358: \E
1.1       noro     3359: @end itemize
                   3360:
                   3361: @example
                   3362: [100] dp_lcm(<<1,2,3,4,5>>,<<5,4,3,2,1>>);
                   3363: (1)*<<5,4,3,4,5>>
                   3364: @end example
                   3365:
                   3366: @table @t
1.2       noro     3367: \JP @item $B;2>H(B
                   3368: \EG @item References
1.1       noro     3369: @fref{p_nf p_nf_mod p_true_nf p_true_nf_mod}.
                   3370: @end table
                   3371:
1.2       noro     3372: \JP @node dp_redble,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3373: \EG @node dp_redble,,, Functions for Groebner basis computation
1.1       noro     3374: @subsection @code{dp_redble}
                   3375: @findex dp_redble
                   3376:
                   3377: @table @t
                   3378: @item dp_redble(@var{dpoly1},@var{dpoly2})
1.2       noro     3379: \JP :: $BF,9`$I$&$7$,@0=|2DG=$+$I$&$+D4$Y$k(B.
                   3380: \EG :: Checks whether one head term is divisible by the other head term.
1.1       noro     3381: @end table
                   3382:
                   3383: @table @var
                   3384: @item return
1.2       noro     3385: \JP $B@0?t(B
                   3386: \EG integer
1.4       noro     3387: @item dpoly1  dpoly2
1.2       noro     3388: \JP $BJ,;6I=8=B?9`<0(B
                   3389: \EG distributed polynomial
1.1       noro     3390: @end table
                   3391:
                   3392: @itemize @bullet
1.2       noro     3393: \BJP
1.1       noro     3394: @item
                   3395: @var{dpoly1} $B$NF,9`$,(B @var{dpoly2} $B$NF,9`$G3d$j@Z$l$l$P(B 1, $B3d$j@Z$l$J$1$l$P(B
                   3396: 0 $B$rJV$9(B.
                   3397: @item
                   3398: $BB?9`<0$N4JLs$r9T$&:](B, $B$I$N9`$r4JLs$G$-$k$+$rC5$9$N$KMQ$$$k(B.
1.2       noro     3399: \E
                   3400: \BEG
                   3401: @item
                   3402: Returns 1 if the head term of @var{dpoly2} divides the head term of
                   3403: @var{dpoly1}; otherwise 0.
                   3404: @item
                   3405: Used for finding candidate terms at reduction of polynomials.
                   3406: \E
1.1       noro     3407: @end itemize
                   3408:
                   3409: @example
                   3410: [148] C;
                   3411: (1)*<<1,1,1,0,0>>+(1)*<<0,1,1,1,0>>+(1)*<<1,1,0,0,1>>+(1)*<<1,0,0,1,1>>
                   3412: [149] T;
                   3413: (3)*<<2,1,0,0,0>>+(3)*<<1,2,0,0,0>>+(1)*<<0,3,0,0,0>>+(6)*<<1,1,1,0,0>>
                   3414: [150] for ( ; T; T = dp_rest(T)) print(dp_redble(T,C));
                   3415: 0
                   3416: 0
                   3417: 0
                   3418: 1
                   3419: @end example
                   3420:
                   3421: @table @t
1.2       noro     3422: \JP @item $B;2>H(B
                   3423: \EG @item References
1.1       noro     3424: @fref{dp_red dp_red_mod}.
                   3425: @end table
                   3426:
1.2       noro     3427: \JP @node dp_subd,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3428: \EG @node dp_subd,,, Functions for Groebner basis computation
1.1       noro     3429: @subsection @code{dp_subd}
                   3430: @findex dp_subd
                   3431:
                   3432: @table @t
                   3433: @item dp_subd(@var{dpoly1},@var{dpoly2})
1.2       noro     3434: \JP :: $BF,9`$N>&C19`<0$rJV$9(B.
                   3435: \EG :: Returns the quotient monomial of the head terms.
1.1       noro     3436: @end table
                   3437:
                   3438: @table @var
                   3439: @item return
1.2       noro     3440: \JP $BJ,;6I=8=B?9`<0(B
                   3441: \EG distributed polynomial
1.4       noro     3442: @item dpoly1  dpoly2
1.2       noro     3443: \JP $BJ,;6I=8=B?9`<0(B
                   3444: \EG distributed polynomial
1.1       noro     3445: @end table
                   3446:
                   3447: @itemize @bullet
1.2       noro     3448: \BJP
1.1       noro     3449: @item
                   3450: @code{dp_ht(@var{dpoly1})/dp_ht(@var{dpoly2})} $B$r5a$a$k(B. $B7k2L$N78?t$O(B 1
                   3451: $B$G$"$k(B.
                   3452: @item
                   3453: $B3d$j@Z$l$k$3$H$,$"$i$+$8$a$o$+$C$F$$$kI,MW$,$"$k(B.
1.2       noro     3454: \E
                   3455: \BEG
                   3456: @item
                   3457: Gets @code{dp_ht(@var{dpoly1})/dp_ht(@var{dpoly2})}.
                   3458: The coefficient of the result is always set to 1.
                   3459: @item
                   3460: Divisibility assumed.
                   3461: \E
1.1       noro     3462: @end itemize
                   3463:
                   3464: @example
                   3465: [162] dp_subd(<<1,2,3,4,5>>,<<1,1,2,3,4>>);
                   3466: (1)*<<0,1,1,1,1>>
                   3467: @end example
                   3468:
                   3469: @table @t
1.2       noro     3470: \JP @item $B;2>H(B
                   3471: \EG @item References
1.1       noro     3472: @fref{dp_red dp_red_mod}.
                   3473: @end table
                   3474:
1.2       noro     3475: \JP @node dp_vtoe dp_etov,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3476: \EG @node dp_vtoe dp_etov,,, Functions for Groebner basis computation
1.1       noro     3477: @subsection @code{dp_vtoe}, @code{dp_etov}
                   3478: @findex dp_vtoe
                   3479: @findex dp_etov
                   3480:
                   3481: @table @t
                   3482: @item dp_vtoe(@var{vect})
1.2       noro     3483: \JP :: $B;X?t%Y%/%H%k$r9`$KJQ49(B
                   3484: \EG :: Converts an exponent vector into a term.
1.1       noro     3485: @item dp_etov(@var{dpoly})
1.2       noro     3486: \JP :: $BF,9`$r;X?t%Y%/%H%k$KJQ49(B
                   3487: \EG :: Convert the head term of a distributed polynomial into an exponent vector.
1.1       noro     3488: @end table
                   3489:
                   3490: @table @var
                   3491: @item return
1.2       noro     3492: \JP @code{dp_vtoe} : $BJ,;6I=8=B?9`<0(B, @code{dp_etov} : $B%Y%/%H%k(B
                   3493: \EG @code{dp_vtoe} : distributed polynomial, @code{dp_etov} : vector
1.1       noro     3494: @item vect
1.2       noro     3495: \JP $B%Y%/%H%k(B
                   3496: \EG vector
1.1       noro     3497: @item dpoly
1.2       noro     3498: \JP $BJ,;6I=8=B?9`<0(B
                   3499: \EG distributed polynomial
1.1       noro     3500: @end table
                   3501:
                   3502: @itemize @bullet
1.2       noro     3503: \BJP
1.1       noro     3504: @item
                   3505: @code{dp_vtoe()} $B$O(B, $B%Y%/%H%k(B @var{vect} $B$r;X?t%Y%/%H%k$H$9$k9`$r@8@.$9$k(B.
                   3506: @item
                   3507: @code{dp_etov()} $B$O(B, $BJ,;6I=8=B?9`<0(B @code{dpoly} $B$NF,9`$N;X?t%Y%/%H%k$r(B
                   3508: $B%Y%/%H%k$KJQ49$9$k(B.
1.2       noro     3509: \E
                   3510: \BEG
                   3511: @item
                   3512: @code{dp_vtoe()} generates a term whose exponent vector is @var{vect}.
                   3513: @item
                   3514: @code{dp_etov()} generates a vector which is the exponent vector of the
                   3515: head term of @code{dpoly}.
                   3516: \E
1.1       noro     3517: @end itemize
                   3518:
                   3519: @example
                   3520: [211] X=<<1,2,3>>;
                   3521: (1)*<<1,2,3>>
                   3522: [212] V=dp_etov(X);
                   3523: [ 1 2 3 ]
                   3524: [213] V[2]++$
                   3525: [214] Y=dp_vtoe(V);
                   3526: (1)*<<1,2,4>>
                   3527: @end example
                   3528:
1.2       noro     3529: \JP @node dp_mbase,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3530: \EG @node dp_mbase,,, Functions for Groebner basis computation
1.1       noro     3531: @subsection @code{dp_mbase}
                   3532: @findex dp_mbase
                   3533:
                   3534: @table @t
                   3535: @item dp_mbase(@var{dplist})
1.2       noro     3536: \JP :: monomial $B4pDl$N7W;;(B
                   3537: \EG :: Computes the monomial basis
1.1       noro     3538: @end table
                   3539:
                   3540: @table @var
                   3541: @item return
1.2       noro     3542: \JP $BJ,;6I=8=B?9`<0$N%j%9%H(B
                   3543: \EG list of distributed polynomial
1.1       noro     3544: @item dplist
1.2       noro     3545: \JP $BJ,;6I=8=B?9`<0$N%j%9%H(B
                   3546: \EG list of distributed polynomial
1.1       noro     3547: @end table
                   3548:
                   3549: @itemize @bullet
1.2       noro     3550: \BJP
1.1       noro     3551: @item
                   3552: $B$"$k=g=x$G%0%l%V%J4pDl$H$J$C$F$$$kB?9`<0=89g$N(B, $B$=$N=g=x$K4X$9$kJ,;6I=8=(B
                   3553: $B$G$"$k(B @var{dplist} $B$K$D$$$F(B,
                   3554: @var{dplist} $B$,(B K[X] $BCf$G@8@.$9$k%$%G%"%k(B I $B$,(B 0 $B<!85$N;~(B,
                   3555: K $B>eM-8B<!85@~7A6u4V$G$"$k(B K[X]/I $B$N(B monomial $B$K$h$k4pDl$r5a$a$k(B.
                   3556: @item
                   3557: $BF@$i$l$?4pDl$N8D?t$,(B, K[X]/I $B$N(B K-$B@~7A6u4V$H$7$F$N<!85$KEy$7$$(B.
1.2       noro     3558: \E
                   3559: \BEG
                   3560: @item
                   3561: Assuming that @var{dplist} is a list of distributed polynomials which
                   3562: is a Groebner basis with respect to the current ordering type and
                   3563: that the ideal @var{I} generated by @var{dplist} in K[X] is zero-dimensional,
                   3564: this function computes the monomial basis of a finite dimenstional K-vector
                   3565: space K[X]/I.
                   3566: @item
                   3567: The number of elements in the monomial basis is equal to the
                   3568: K-dimenstion of K[X]/I.
                   3569: \E
1.1       noro     3570: @end itemize
                   3571:
                   3572: @example
                   3573: [215] K=katsura(5)$
                   3574: [216] V=[u5,u4,u3,u2,u1,u0]$
                   3575: [217] G0=gr(K,V,0)$
                   3576: [218] H=map(dp_ptod,G0,V)$
                   3577: [219] map(dp_ptod,dp_mbase(H),V)$
                   3578: [u0^5,u4*u0^3,u3*u0^3,u2*u0^3,u1*u0^3,u0^4,u3^2*u0,u2*u3*u0,u1*u3*u0,
                   3579: u1*u2*u0,u1^2*u0,u4*u0^2,u3*u0^2,u2*u0^2,u1*u0^2,u0^3,u3^2,u2*u3,u1*u3,
                   3580: u1*u2,u1^2,u4*u0,u3*u0,u2*u0,u1*u0,u0^2,u4,u3,u2,u1,u0,1]
                   3581: @end example
                   3582:
                   3583: @table @t
1.2       noro     3584: \JP @item $B;2>H(B
                   3585: \EG @item References
1.1       noro     3586: @fref{gr hgr gr_mod}.
                   3587: @end table
                   3588:
1.2       noro     3589: \JP @node dp_mag,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3590: \EG @node dp_mag,,, Functions for Groebner basis computation
1.1       noro     3591: @subsection @code{dp_mag}
                   3592: @findex dp_mag
                   3593:
                   3594: @table @t
                   3595: @item dp_mag(@var{p})
1.2       noro     3596: \JP :: $B78?t$N%S%C%HD9$NOB$rJV$9(B
                   3597: \EG :: Computes the sum of bit lengths of coefficients of a distributed polynomial.
1.1       noro     3598: @end table
                   3599:
                   3600: @table @var
                   3601: @item return
1.2       noro     3602: \JP $B?t(B
                   3603: \EG integer
1.1       noro     3604: @item p
1.2       noro     3605: \JP $BJ,;6I=8=B?9`<0(B
                   3606: \EG distributed polynomial
1.1       noro     3607: @end table
                   3608:
                   3609: @itemize @bullet
1.2       noro     3610: \BJP
1.1       noro     3611: @item
                   3612: $BJ,;6I=8=B?9`<0$N78?t$K8=$l$kM-M}?t$K$D$-(B, $B$=$NJ,JlJ,;R(B ($B@0?t$N>l9g$OJ,;R(B)
                   3613: $B$N%S%C%HD9$NAmOB$rJV$9(B.
                   3614: @item
                   3615: $BBP>]$H$J$kB?9`<0$NBg$-$5$NL\0B$H$7$FM-8z$G$"$k(B. $BFC$K(B, 0 $B<!85%7%9%F%`$K$*$$$F$O(B
                   3616: $B78?tKDD%$,LdBj$H$J$j(B, $BESCf@8@.$5$l$kB?9`<0$,78?tKDD%$r5/$3$7$F$$$k$+$I$&$+(B
                   3617: $B$NH=Dj$KLrN)$D(B.
                   3618: @item
                   3619: @code{dp_gr_flags()} $B$G(B, @code{ShowMag}, @code{Print} $B$r(B on $B$K$9$k$3$H$K$h$j(B
                   3620: $BESCf@8@.$5$l$kB?9`<0$K$?$$$9$k(B @code{dp_mag()} $B$NCM$r8+$k$3$H$,$G$-$k(B.
1.2       noro     3621: \E
                   3622: \BEG
                   3623: @item
                   3624: This function computes the sum of bit lengths of coefficients of a
                   3625: distributed polynomial @var{p}. If a coefficient is non integral,
                   3626: the sum of bit lengths of the numerator and the denominator is taken.
                   3627: @item
                   3628: This is a measure of the size of a polynomial. Especially for
                   3629: zero-dimensional system coefficient swells are often serious and
                   3630: the returned value is useful to detect such swells.
                   3631: @item
                   3632: If @code{ShowMag} and @code{Print} for @code{dp_gr_flags()} are on,
                   3633: values of @code{dp_mag()} for intermediate basis elements are shown.
                   3634: \E
1.1       noro     3635: @end itemize
                   3636:
                   3637: @example
                   3638: [221] X=dp_ptod((x+2*y)^10,[x,y])$
                   3639: [222] dp_mag(X);
                   3640: 115
                   3641: @end example
                   3642:
                   3643: @table @t
1.2       noro     3644: \JP @item $B;2>H(B
                   3645: \EG @item References
1.1       noro     3646: @fref{dp_gr_flags dp_gr_print}.
                   3647: @end table
                   3648:
1.2       noro     3649: \JP @node dp_red dp_red_mod,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3650: \EG @node dp_red dp_red_mod,,, Functions for Groebner basis computation
1.1       noro     3651: @subsection @code{dp_red}, @code{dp_red_mod}
                   3652: @findex dp_red
                   3653: @findex dp_red_mod
                   3654:
                   3655: @table @t
                   3656: @item dp_red(@var{dpoly1},@var{dpoly2},@var{dpoly3})
                   3657: @item dp_red_mod(@var{dpoly1},@var{dpoly2},@var{dpoly3},@var{mod})
1.2       noro     3658: \JP :: $B0l2s$N4JLsA`:n(B
                   3659: \EG :: Single reduction operation
1.1       noro     3660: @end table
                   3661:
                   3662: @table @var
                   3663: @item return
1.2       noro     3664: \JP $B%j%9%H(B
                   3665: \EG list
1.4       noro     3666: @item dpoly1  dpoly2  dpoly3
1.2       noro     3667: \JP $BJ,;6I=8=B?9`<0(B
                   3668: \EG distributed polynomial
1.1       noro     3669: @item vlist
1.2       noro     3670: \JP $B%j%9%H(B
                   3671: \EG list
1.1       noro     3672: @item mod
1.2       noro     3673: \JP $BAG?t(B
                   3674: \EG prime
1.1       noro     3675: @end table
                   3676:
                   3677: @itemize @bullet
1.2       noro     3678: \BJP
1.1       noro     3679: @item
                   3680: @var{dpoly1} + @var{dpoly2} $B$J$kJ,;6I=8=B?9`<0$r(B @var{dpoly3} $B$G(B
                   3681: 1 $B2s4JLs$9$k(B.
                   3682: @item
                   3683: @code{dp_red_mod()} $B$NF~NO$O(B, $BA4$FM-8BBN78?t$KJQ49$5$l$F$$$kI,MW$,$"$k(B.
                   3684: @item
                   3685: $B4JLs$5$l$k9`$O(B @var{dpoly2} $B$NF,9`$G$"$k(B. $B=>$C$F(B, @var{dpoly2} $B$N(B
                   3686: $BF,9`$,(B @var{dpoly3} $B$NF,9`$G3d$j@Z$l$k$3$H$,$"$i$+$8$a$o$+$C$F$$$J$1$l$P(B
                   3687: $B$J$i$J$$(B.
                   3688: @item
                   3689: $B0z?t$,@0?t78?t$N;~(B, $B4JLs$O(B, $BJ,?t$,8=$l$J$$$h$&(B, $B@0?t(B @var{a}, @var{b},
1.4       noro     3690: $B9`(B @var{t} $B$K$h$j(B @var{a}(@var{dpoly1} + @var{dpoly2})-@var{bt} @var{dpoly3} $B$H$7$F7W;;$5$l$k(B.
1.1       noro     3691: @item
                   3692: $B7k2L$O(B, @code{[@var{a dpoly1},@var{a dpoly2 - bt dpoly3}]} $B$J$k%j%9%H$G$"$k(B.
1.2       noro     3693: \E
                   3694: \BEG
                   3695: @item
                   3696: Reduces a distributed polynomial, @var{dpoly1} + @var{dpoly2},
                   3697: by @var{dpoly3} for single time.
                   3698: @item
                   3699: An input for @code{dp_red_mod()} must be converted into a distributed
                   3700: polynomial with coefficients in a finite field.
                   3701: @item
                   3702: This implies that
                   3703: the divisibility of the head term of @var{dpoly2} by the head term of
                   3704: @var{dpoly3} is assumed.
                   3705: @item
                   3706: When integral coefficients, computation is so carefully performed that
                   3707: no rational operations appear in the reduction procedure.
                   3708: It is computed for integers @var{a} and @var{b}, and a term @var{t} as:
1.4       noro     3709: @var{a}(@var{dpoly1} + @var{dpoly2})-@var{bt} @var{dpoly3}.
1.2       noro     3710: @item
                   3711: The result is a list @code{[@var{a dpoly1},@var{a dpoly2 - bt dpoly3}]}.
                   3712: \E
1.1       noro     3713: @end itemize
                   3714:
                   3715: @example
                   3716: [157] D=(3)*<<2,1,0,0,0>>+(3)*<<1,2,0,0,0>>+(1)*<<0,3,0,0,0>>;
                   3717: (3)*<<2,1,0,0,0>>+(3)*<<1,2,0,0,0>>+(1)*<<0,3,0,0,0>>
                   3718: [158] R=(6)*<<1,1,1,0,0>>;
                   3719: (6)*<<1,1,1,0,0>>
                   3720: [159] C=12*<<1,1,1,0,0>>+(1)*<<0,1,1,1,0>>+(1)*<<1,1,0,0,1>>;
                   3721: (12)*<<1,1,1,0,0>>+(1)*<<0,1,1,1,0>>+(1)*<<1,1,0,0,1>>
                   3722: [160] dp_red(D,R,C);
1.5       noro     3723: [(6)*<<2,1,0,0,0>>+(6)*<<1,2,0,0,0>>+(2)*<<0,3,0,0,0>>,
                   3724: (-1)*<<0,1,1,1,0>>+(-1)*<<1,1,0,0,1>>]
1.1       noro     3725: @end example
                   3726:
                   3727: @table @t
1.2       noro     3728: \JP @item $B;2>H(B
                   3729: \EG @item References
1.1       noro     3730: @fref{dp_mod dp_rat}.
                   3731: @end table
                   3732:
1.2       noro     3733: \JP @node dp_sp dp_sp_mod,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3734: \EG @node dp_sp dp_sp_mod,,, Functions for Groebner basis computation
1.1       noro     3735: @subsection @code{dp_sp}, @code{dp_sp_mod}
                   3736: @findex dp_sp
                   3737: @findex dp_sp_mod
                   3738:
                   3739: @table @t
                   3740: @item dp_sp(@var{dpoly1},@var{dpoly2})
                   3741: @item dp_sp_mod(@var{dpoly1},@var{dpoly2},@var{mod})
1.2       noro     3742: \JP :: S-$BB?9`<0$N7W;;(B
                   3743: \EG :: Computation of an S-polynomial
1.1       noro     3744: @end table
                   3745:
                   3746: @table @var
                   3747: @item return
1.2       noro     3748: \JP $BJ,;6I=8=B?9`<0(B
                   3749: \EG distributed polynomial
1.4       noro     3750: @item dpoly1  dpoly2
1.2       noro     3751: \JP $BJ,;6I=8=B?9`<0(B
                   3752: \EG distributed polynomial
1.1       noro     3753: @item mod
1.2       noro     3754: \JP $BAG?t(B
                   3755: \EG prime
1.1       noro     3756: @end table
                   3757:
                   3758: @itemize @bullet
1.2       noro     3759: \BJP
1.1       noro     3760: @item
                   3761: @var{dpoly1}, @var{dpoly2} $B$N(B S-$BB?9`<0$r7W;;$9$k(B.
                   3762: @item
                   3763: @code{dp_sp_mod()} $B$NF~NO$O(B, $BA4$FM-8BBN78?t$KJQ49$5$l$F$$$kI,MW$,$"$k(B.
                   3764: @item
                   3765: $B7k2L$KM-M}?t(B, $BM-M}<0$,F~$k$N$rHr$1$k$?$a(B, $B7k2L$,Dj?tG\(B, $B$"$k$$$OB?9`<0(B
                   3766: $BG\$5$l$F$$$k2DG=@-$,$"$k(B.
1.2       noro     3767: \E
                   3768: \BEG
                   3769: @item
                   3770: This function computes the S-polynomial of @var{dpoly1} and @var{dpoly2}.
                   3771: @item
                   3772: Inputs of @code{dp_sp_mod()} must be polynomials with coefficients in a
                   3773: finite field.
                   3774: @item
                   3775: The result may be multiplied by a constant in the ground field in order to
                   3776: make the result integral.
                   3777: \E
1.1       noro     3778: @end itemize
                   3779:
                   3780: @example
                   3781: [227] X=dp_ptod(x^2*y+x*y,[x,y]);
                   3782: (1)*<<2,1>>+(1)*<<1,1>>
                   3783: [228] Y=dp_ptod(x*y^2+x*y,[x,y]);
                   3784: (1)*<<1,2>>+(1)*<<1,1>>
                   3785: [229] dp_sp(X,Y);
                   3786: (-1)*<<2,1>>+(1)*<<1,2>>
                   3787: @end example
                   3788:
                   3789: @table @t
1.2       noro     3790: \JP @item $B;2>H(B
                   3791: \EG @item References
1.1       noro     3792: @fref{dp_mod dp_rat}.
                   3793: @end table
1.2       noro     3794: \JP @node p_nf p_nf_mod p_true_nf p_true_nf_mod,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3795: \EG @node p_nf p_nf_mod p_true_nf p_true_nf_mod,,, Functions for Groebner basis computation
1.1       noro     3796: @subsection @code{p_nf}, @code{p_nf_mod}, @code{p_true_nf}, @code{p_true_nf_mod}
                   3797: @findex p_nf
                   3798: @findex p_nf_mod
                   3799: @findex p_true_nf
                   3800: @findex p_true_nf_mod
                   3801:
                   3802: @table @t
                   3803: @item p_nf(@var{poly},@var{plist},@var{vlist},@var{order})
                   3804: @itemx p_nf_mod(@var{poly},@var{plist},@var{vlist},@var{order},@var{mod})
1.2       noro     3805: \JP :: $BI=8=B?9`<0$N@55,7A$r5a$a$k(B. ($B7k2L$ODj?tG\$5$l$F$$$k2DG=@-$"$j(B)
                   3806: \BEG
                   3807: :: Computes the normal form of the given polynomial.
                   3808: (The result may be multiplied by a constant.)
                   3809: \E
1.1       noro     3810: @item p_true_nf(@var{poly},@var{plist},@var{vlist},@var{order})
                   3811: @itemx p_true_nf_mod(@var{poly},@var{plist},@var{vlist},@var{order},@var{mod})
1.2       noro     3812: \JP :: $BI=8=B?9`<0$N@55,7A$r5a$a$k(B. ($B??$N7k2L$r(B @code{[$BJ,;R(B, $BJ,Jl(B]} $B$N7A$GJV$9(B)
                   3813: \BEG
                   3814: :: Computes the normal form of the given polynomial. (The result is returned
                   3815: as a form of @code{[numerator, denominator]})
                   3816: \E
1.1       noro     3817: @end table
                   3818:
                   3819: @table @var
                   3820: @item return
1.2       noro     3821: \JP @code{p_nf} : $BB?9`<0(B, @code{p_true_nf} : $B%j%9%H(B
                   3822: \EG @code{p_nf} : polynomial, @code{p_true_nf} : list
1.1       noro     3823: @item poly
1.2       noro     3824: \JP $BB?9`<0(B
                   3825: \EG polynomial
1.4       noro     3826: @item plist vlist
1.2       noro     3827: \JP $B%j%9%H(B
                   3828: \EG list
1.1       noro     3829: @item order
1.2       noro     3830: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   3831: \EG number, list or matrix
1.1       noro     3832: @item mod
1.2       noro     3833: \JP $BAG?t(B
                   3834: \EG prime
1.1       noro     3835: @end table
                   3836:
                   3837: @itemize @bullet
1.2       noro     3838: \BJP
1.1       noro     3839: @item
                   3840: @samp{gr} $B$GDj5A$5$l$F$$$k(B.
                   3841: @item
                   3842: $BB?9`<0$N(B, $BB?9`<0%j%9%H$K$h$k@55,7A$r5a$a$k(B.
                   3843: @item
                   3844: @code{dp_nf()}, @code{dp_true_nf()}, @code{dp_nf_mod()}, @code{dp_true_nf_mod}
                   3845: $B$KBP$9$k%$%s%?%U%'!<%9$G$"$k(B.
                   3846: @item
                   3847: @var{poly} $B$*$h$S(B @var{plist} $B$O(B, $BJQ?t=g=x(B @var{vlist} $B$*$h$S(B
                   3848: $BJQ?t=g=x7?(B @var{otype} $B$K=>$C$FJ,;6I=8=B?9`<0$KJQ49$5$l(B,
                   3849: @code{dp_nf()}, @code{dp_true_nf()}, @code{dp_nf_mod()},
                   3850: @code{dp_true_nf_mod()} $B$KEO$5$l$k(B.
                   3851: @item
                   3852: @code{dp_nf()}, @code{dp_true_nf()}, @code{dp_nf_mod()},
                   3853: @code{dp_true_nf_mod()} $B$O(B @var{fullreduce} $B$,(B 1 $B$G8F$S=P$5$l$k(B.
                   3854: @item
                   3855: $B7k2L$OB?9`<0$KJQ49$5$l$F=PNO$5$l$k(B.
                   3856: @item
                   3857: @code{p_true_nf()}, @code{p_true_nf_mod()} $B$N=PNO$K4X$7$F$O(B,
                   3858: @code{dp_true_nf()}, @code{dp_true_nf_mod()} $B$N9`$r;2>H(B.
1.2       noro     3859: \E
                   3860: \BEG
                   3861: @item
                   3862: Defined in the package @samp{gr}.
                   3863: @item
                   3864: Obtains the normal form of a polynomial by a polynomial list.
                   3865: @item
                   3866: These are interfaces to @code{dp_nf()}, @code{dp_true_nf()}, @code{dp_nf_mod()},
                   3867:  @code{dp_true_nf_mod}
                   3868: @item
                   3869: The polynomial @var{poly} and the polynomials in @var{plist} is
                   3870: converted, according to the variable ordering @var{vlist} and
                   3871: type of term ordering @var{otype}, into their distributed polynomial
                   3872: counterparts and passed to @code{dp_nf()}.
                   3873: @item
                   3874: @code{dp_nf()}, @code{dp_true_nf()}, @code{dp_nf_mod()} and
                   3875: @code{dp_true_nf_mod()}
                   3876: is called with value 1 for @var{fullreduce}.
                   3877: @item
                   3878: The result is converted back into an ordinary polynomial.
                   3879: @item
                   3880: As for @code{p_true_nf()}, @code{p_true_nf_mod()}
                   3881: refer to @code{dp_true_nf()} and @code{dp_true_nf_mod()}.
                   3882: \E
1.1       noro     3883: @end itemize
                   3884:
                   3885: @example
                   3886: [79] K = katsura(5)$
                   3887: [80] V = [u5,u4,u3,u2,u1,u0]$
                   3888: [81] G = hgr(K,V,2)$
                   3889: [82] p_nf(K[1],G,V,2);
                   3890: 0
                   3891: [83] L = p_true_nf(K[1]+1,G,V,2);
                   3892: [-1503...,-1503...]
                   3893: [84] L[0]/L[1];
                   3894: 1
                   3895: @end example
                   3896:
                   3897: @table @t
1.2       noro     3898: \JP @item $B;2>H(B
                   3899: \EG @item References
1.1       noro     3900: @fref{dp_ptod},
                   3901: @fref{dp_dtop},
                   3902: @fref{dp_ord},
                   3903: @fref{dp_nf dp_nf_mod dp_true_nf dp_true_nf_mod}.
                   3904: @end table
                   3905:
1.2       noro     3906: \JP @node p_terms,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3907: \EG @node p_terms,,, Functions for Groebner basis computation
1.1       noro     3908: @subsection @code{p_terms}
                   3909: @findex p_terms
                   3910:
                   3911: @table @t
                   3912: @item p_terms(@var{poly},@var{vlist},@var{order})
1.2       noro     3913: \JP :: $BB?9`<0$K$"$i$o$l$kC19`$r%j%9%H$K$9$k(B.
                   3914: \EG :: Monomials appearing in the given polynomial is collected into a list.
1.1       noro     3915: @end table
                   3916:
                   3917: @table @var
                   3918: @item return
1.2       noro     3919: \JP $B%j%9%H(B
                   3920: \EG list
1.1       noro     3921: @item poly
1.2       noro     3922: \JP $BB?9`<0(B
                   3923: \EG polynomial
1.1       noro     3924: @item vlist
1.2       noro     3925: \JP $B%j%9%H(B
                   3926: \EG list
1.1       noro     3927: @item order
1.2       noro     3928: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   3929: \EG number, list or matrix
1.1       noro     3930: @end table
                   3931:
                   3932: @itemize @bullet
1.2       noro     3933: \BJP
1.1       noro     3934: @item
                   3935: @samp{gr} $B$GDj5A$5$l$F$$$k(B.
                   3936: @item
                   3937: $BB?9`<0$rC19`$KE83+$7$?;~$K8=$l$k9`$r%j%9%H$K$7$FJV$9(B.
                   3938: @var{vlist} $B$*$h$S(B @var{order} $B$K$h$jDj$^$k9`=g=x$K$h$j(B, $B=g=x$N9b$$$b$N(B
                   3939: $B$,%j%9%H$N@hF,$KMh$k$h$&$K%=!<%H$5$l$k(B.
                   3940: @item
                   3941: $B%0%l%V%J4pDl$O$7$P$7$P78?t$,5pBg$K$J$k$?$a(B, $B<B:]$K$I$N9`$,8=$l$F(B
                   3942: $B$$$k$N$+$r8+$k$?$a$J$I$KMQ$$$k(B.
1.2       noro     3943: \E
                   3944: \BEG
                   3945: @item
                   3946: Defined in the package @samp{gr}.
                   3947: @item
                   3948: This returns a list which contains all non-zero monomials in the given
                   3949: polynomial.  The monomials are ordered according to the current
                   3950: type of term ordering and @var{vlist}.
                   3951: @item
                   3952: Since polynomials in a Groebner base often have very large coefficients,
                   3953: examining a polynomial as it is may sometimes be difficult to perform.
                   3954: For such a case, this function enables to examine which term is really
                   3955: exists.
                   3956: \E
1.1       noro     3957: @end itemize
                   3958:
                   3959: @example
                   3960: [233] G=gr(katsura(5),[u5,u4,u3,u2,u1,u0],2)$
                   3961: [234] p_terms(G[0],[u5,u4,u3,u2,u1,u0],2);
1.5       noro     3962: [u5,u0^31,u0^30,u0^29,u0^28,u0^27,u0^26,u0^25,u0^24,u0^23,u0^22,
                   3963: u0^21,u0^20,u0^19,u0^18,u0^17,u0^16,u0^15,u0^14,u0^13,u0^12,u0^11,
                   3964: u0^10,u0^9,u0^8,u0^7,u0^6,u0^5,u0^4,u0^3,u0^2,u0,1]
1.1       noro     3965: @end example
                   3966:
1.2       noro     3967: \JP @node gb_comp,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   3968: \EG @node gb_comp,,, Functions for Groebner basis computation
1.1       noro     3969: @subsection @code{gb_comp}
                   3970: @findex gb_comp
                   3971:
                   3972: @table @t
                   3973: @item gb_comp(@var{plist1}, @var{plist2})
1.2       noro     3974: \JP :: $BB?9`<0%j%9%H$,(B, $BId9f$r=|$$$F=89g$H$7$FEy$7$$$+$I$&$+D4$Y$k(B.
                   3975: \EG :: Checks whether two polynomial lists are equal or not as a set
1.1       noro     3976: @end table
                   3977:
                   3978: @table @var
1.2       noro     3979: \JP @item return 0 $B$^$?$O(B 1
                   3980: \EG @item return 0 or 1
1.4       noro     3981: @item plist1  plist2
1.1       noro     3982: @end table
                   3983:
                   3984: @itemize @bullet
1.2       noro     3985: \BJP
1.1       noro     3986: @item
                   3987: @var{plist1}, @var{plist2} $B$K$D$$$F(B, $BId9f$r=|$$$F=89g$H$7$FEy$7$$$+$I$&$+(B
                   3988: $BD4$Y$k(B.
                   3989: @item
                   3990: $B0[$J$kJ}K!$G5a$a$?%0%l%V%J4pDl$O(B, $B4pDl$N=g=x(B, $BId9f$,0[$J$k>l9g$,$"$j(B,
                   3991: $B$=$l$i$,Ey$7$$$+$I$&$+$rD4$Y$k$?$a$KMQ$$$k(B.
1.2       noro     3992: \E
                   3993: \BEG
                   3994: @item
                   3995: This function checks whether @var{plist1} and @var{plist2} are equal or
                   3996: not as a set .
                   3997: @item
                   3998: For the same input and the same term ordering different
                   3999: functions for Groebner basis computations may produce different outputs
                   4000: as lists. This function compares such lists whether they are equal
                   4001: as a generating set of an ideal.
                   4002: \E
1.1       noro     4003: @end itemize
                   4004:
                   4005: @example
                   4006: [243] C=cyclic(6)$
                   4007: [244] V=[c0,c1,c2,c3,c4,c5]$
                   4008: [245] G0=gr(C,V,0)$
                   4009: [246] G=tolex(G0,V,0,V)$
                   4010: [247] GG=lex_tl(C,V,0,V,0)$
                   4011: [248] gb_comp(G,GG);
                   4012: 1
                   4013: @end example
                   4014:
1.2       noro     4015: \JP @node katsura hkatsura cyclic hcyclic,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   4016: \EG @node katsura hkatsura cyclic hcyclic,,, Functions for Groebner basis computation
1.1       noro     4017: @subsection @code{katsura}, @code{hkatsura}, @code{cyclic}, @code{hcyclic}
                   4018: @findex katsura
                   4019: @findex hkatsura
                   4020: @findex cyclic
                   4021: @findex hcyclic
                   4022:
                   4023: @table @t
                   4024: @item katsura(@var{n})
                   4025: @item hkatsura(@var{n})
                   4026: @item cyclic(@var{n})
                   4027: @item hcyclic(@var{n})
1.2       noro     4028: \JP :: $BB?9`<0%j%9%H$N@8@.(B
                   4029: \EG :: Generates a polynomial list of standard benchmark.
1.1       noro     4030: @end table
                   4031:
                   4032: @table @var
                   4033: @item return
1.2       noro     4034: \JP $B%j%9%H(B
                   4035: \EG list
1.1       noro     4036: @item n
1.2       noro     4037: \JP $B@0?t(B
                   4038: \EG integer
1.1       noro     4039: @end table
                   4040:
                   4041: @itemize @bullet
1.2       noro     4042: \BJP
1.1       noro     4043: @item
                   4044: @code{katsura()} $B$O(B @samp{katsura}, @code{cyclic()} $B$O(B @samp{cyclic}
                   4045: $B$GDj5A$5$l$F$$$k(B.
                   4046: @item
                   4047: $B%0%l%V%J4pDl7W;;$G$7$P$7$P%F%9%H(B, $B%Y%s%A%^!<%/$KMQ$$$i$l$k(B @code{katsura},
                   4048: @code{cyclic} $B$*$h$S$=$N@F<!2=$r@8@.$9$k(B.
                   4049: @item
                   4050: @code{cyclic} $B$O(B @code{Arnborg}, @code{Lazard}, @code{Davenport} $B$J$I$N(B
                   4051: $BL>$G8F$P$l$k$3$H$b$"$k(B.
1.2       noro     4052: \E
                   4053: \BEG
                   4054: @item
                   4055: Function @code{katsura()} is defined in @samp{katsura}, and
                   4056: function @code{cyclic()} in  @samp{cyclic}.
                   4057: @item
                   4058: These functions generate a series of polynomial sets, respectively,
                   4059: which are often used for testing and bench marking:
                   4060: @code{katsura}, @code{cyclic} and their homogenized versions.
                   4061: @item
                   4062: Polynomial set @code{cyclic} is sometimes called by other name:
                   4063: @code{Arnborg}, @code{Lazard}, and @code{Davenport}.
                   4064: \E
1.1       noro     4065: @end itemize
                   4066:
                   4067: @example
                   4068: [74] load("katsura")$
                   4069: [79] load("cyclic")$
                   4070: [89] katsura(5);
                   4071: [u0+2*u4+2*u3+2*u2+2*u1+2*u5-1,2*u4*u0-u4+2*u1*u3+u2^2+2*u5*u1,
1.5       noro     4072: 2*u3*u0+2*u1*u4-u3+(2*u1+2*u5)*u2,2*u2*u0+2*u2*u4+(2*u1+2*u5)*u3
                   4073: -u2+u1^2,2*u1*u0+(2*u3+2*u5)*u4+2*u2*u3+2*u1*u2-u1,
1.1       noro     4074: u0^2-u0+2*u4^2+2*u3^2+2*u2^2+2*u1^2+2*u5^2]
                   4075: [90] hkatsura(5);
                   4076: [-t+u0+2*u4+2*u3+2*u2+2*u1+2*u5,
                   4077: -u4*t+2*u4*u0+2*u1*u3+u2^2+2*u5*u1,-u3*t+2*u3*u0+2*u1*u4+(2*u1+2*u5)*u2,
                   4078: -u2*t+2*u2*u0+2*u2*u4+(2*u1+2*u5)*u3+u1^2,
                   4079: -u1*t+2*u1*u0+(2*u3+2*u5)*u4+2*u2*u3+2*u1*u2,
                   4080: -u0*t+u0^2+2*u4^2+2*u3^2+2*u2^2+2*u1^2+2*u5^2]
                   4081: [91] cyclic(6);
                   4082: [c5*c4*c3*c2*c1*c0-1,
                   4083: ((((c4+c5)*c3+c5*c4)*c2+c5*c4*c3)*c1+c5*c4*c3*c2)*c0+c5*c4*c3*c2*c1,
                   4084: (((c3+c5)*c2+c5*c4)*c1+c5*c4*c3)*c0+c4*c3*c2*c1+c5*c4*c3*c2,
                   4085: ((c2+c5)*c1+c5*c4)*c0+c3*c2*c1+c4*c3*c2+c5*c4*c3,
                   4086: (c1+c5)*c0+c2*c1+c3*c2+c4*c3+c5*c4,c0+c1+c2+c3+c4+c5]
                   4087: [92] hcyclic(6);
                   4088: [-c^6+c5*c4*c3*c2*c1*c0,
                   4089: ((((c4+c5)*c3+c5*c4)*c2+c5*c4*c3)*c1+c5*c4*c3*c2)*c0+c5*c4*c3*c2*c1,
                   4090: (((c3+c5)*c2+c5*c4)*c1+c5*c4*c3)*c0+c4*c3*c2*c1+c5*c4*c3*c2,
                   4091: ((c2+c5)*c1+c5*c4)*c0+c3*c2*c1+c4*c3*c2+c5*c4*c3,
                   4092: (c1+c5)*c0+c2*c1+c3*c2+c4*c3+c5*c4,c0+c1+c2+c3+c4+c5]
                   4093: @end example
                   4094:
                   4095: @table @t
1.2       noro     4096: \JP @item $B;2>H(B
                   4097: \EG @item References
1.1       noro     4098: @fref{dp_dtop}.
                   4099: @end table
                   4100:
1.3       noro     4101: \JP @node primadec primedec,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   4102: \EG @node primadec primedec,,, Functions for Groebner basis computation
                   4103: @subsection @code{primadec}, @code{primedec}
                   4104: @findex primadec
                   4105: @findex primedec
                   4106:
                   4107: @table @t
                   4108: @item primadec(@var{plist},@var{vlist})
                   4109: @item primedec(@var{plist},@var{vlist})
                   4110: \JP :: $B%$%G%"%k$NJ,2r(B
                   4111: \EG :: Computes decompositions of ideals.
                   4112: @end table
                   4113:
                   4114: @table @var
                   4115: @item return
                   4116: @itemx plist
                   4117: \JP $BB?9`<0%j%9%H(B
                   4118: \EG list of polynomials
                   4119: @item vlist
                   4120: \JP $BJQ?t%j%9%H(B
                   4121: \EG list of variables
                   4122: @end table
                   4123:
                   4124: @itemize @bullet
                   4125: \BJP
                   4126: @item
                   4127: @code{primadec()}, @code{primedec} $B$O(B @samp{primdec} $B$GDj5A$5$l$F$$$k(B.
                   4128: @item
                   4129: @code{primadec()}, @code{primedec()} $B$O$=$l$>$lM-M}?tBN>e$G$N%$%G%"%k$N(B
                   4130: $B=`AGJ,2r(B, $B:,4p$NAG%$%G%"%kJ,2r$r9T$&(B.
                   4131: @item
                   4132: $B0z?t$OB?9`<0%j%9%H$*$h$SJQ?t%j%9%H$G$"$k(B. $BB?9`<0$OM-M}?t78?t$N$_$,5v$5$l$k(B.
                   4133: @item
                   4134: @code{primadec} $B$O(B @code{[$B=`AG@.J,(B, $BIUB0AG%$%G%"%k(B]} $B$N%j%9%H$rJV$9(B.
                   4135: @item
                   4136: @code{primadec} $B$O(B $BAG0x;R$N%j%9%H$rJV$9(B.
                   4137: @item
                   4138: $B7k2L$K$*$$$F(B, $BB?9`<0%j%9%H$H$7$FI=<($5$l$F$$$k3F%$%G%"%k$OA4$F(B
                   4139: $B%0%l%V%J4pDl$G$"$k(B. $BBP1~$9$k9`=g=x$O(B, $B$=$l$>$l(B
                   4140: $BJQ?t(B @code{PRIMAORD}, @code{PRIMEORD} $B$K3JG<$5$l$F$$$k(B.
                   4141: @item
                   4142: @code{primadec} $B$O(B @code{[Shimoyama,Yokoyama]} $B$N=`AGJ,2r%"%k%4%j%:%`(B
                   4143: $B$r<BAu$7$F$$$k(B.
                   4144: @item
                   4145: $B$b$7AG0x;R$N$_$r5a$a$?$$$J$i(B, @code{primedec} $B$r;H$&J}$,$h$$(B.
                   4146: $B$3$l$O(B, $BF~NO%$%G%"%k$,:,4p%$%G%"%k$G$J$$>l9g$K(B, @code{primadec}
                   4147: $B$N7W;;$KM>J,$J%3%9%H$,I,MW$H$J$k>l9g$,$"$k$+$i$G$"$k(B.
                   4148: \E
                   4149: \BEG
                   4150: @item
                   4151: Function @code{primadec()} and @code{primedec} are defined in @samp{primdec}.
                   4152: @item
                   4153: @code{primadec()}, @code{primedec()} are the function for primary
                   4154: ideal decomposition and prime decomposition of the radical over the
                   4155: rationals respectively.
                   4156: @item
                   4157: The arguments are a list of polynomials and a list of variables.
                   4158: These functions accept ideals with rational function coefficients only.
                   4159: @item
                   4160: @code{primadec} returns the list of pair lists consisting a primary component
                   4161: and its associated prime.
                   4162: @item
                   4163: @code{primedec} returns the list of prime components.
                   4164: @item
                   4165: Each component is a Groebner basis and the corresponding term order
                   4166: is indicated by the global variables @code{PRIMAORD}, @code{PRIMEORD}
                   4167: respectively.
                   4168: @item
                   4169: @code{primadec} implements the primary decompostion algorithm
                   4170: in @code{[Shimoyama,Yokoyama]}.
                   4171: @item
                   4172: If one only wants to know the prime components of an ideal, then
                   4173: use @code{primedec} because @code{primadec} may need additional costs
                   4174: if an input ideal is not radical.
                   4175: \E
                   4176: @end itemize
                   4177:
                   4178: @example
                   4179: [84] load("primdec")$
                   4180: [102] primedec([p*q*x-q^2*y^2+q^2*y,-p^2*x^2+p^2*x+p*q*y,
                   4181: (q^3*y^4-2*q^3*y^3+q^3*y^2)*x-q^3*y^4+q^3*y^3,
                   4182: -q^3*y^4+2*q^3*y^3+(-q^3+p*q^2)*y^2],[p,q,x,y]);
                   4183: [[y,x],[y,p],[x,q],[q,p],[x-1,q],[y-1,p],[(y-1)*x-y,q*y^2-2*q*y-p+q]]
                   4184: [103] primadec([x,z*y,w*y^2,w^2*y-z^3,y^3],[x,y,z,w]);
                   4185: [[[x,z*y,y^2,w^2*y-z^3],[z,y,x]],[[w,x,z*y,z^3,y^3],[w,z,y,x]]]
                   4186: @end example
                   4187:
                   4188: @table @t
                   4189: \JP @item $B;2>H(B
                   4190: \EG @item References
                   4191: @fref{fctr sqfr},
                   4192: \JP @fref{$B9`=g=x$N@_Dj(B}.
                   4193: \EG @fref{Setting term orderings}.
                   4194: @end table
1.5       noro     4195:
                   4196: \JP @node primedec_mod,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   4197: \EG @node primedec_mod,,, Functions for Groebner basis computation
                   4198: @subsection @code{primedec_mod}
                   4199: @findex primedec_mod
                   4200:
                   4201: @table @t
                   4202: @item primedec_mod(@var{plist},@var{vlist},@var{ord},@var{mod},@var{strategy})
                   4203: \JP :: $B%$%G%"%k$NJ,2r(B
                   4204: \EG :: Computes decompositions of ideals over small finite fields.
                   4205: @end table
                   4206:
                   4207: @table @var
                   4208: @item return
                   4209: @itemx plist
                   4210: \JP $BB?9`<0%j%9%H(B
                   4211: \EG list of polynomials
                   4212: @item vlist
                   4213: \JP $BJQ?t%j%9%H(B
                   4214: \EG list of variables
                   4215: @item ord
                   4216: \JP $B?t(B, $B%j%9%H$^$?$O9TNs(B
                   4217: \EG number, list or matrix
                   4218: @item mod
                   4219: \JP $B@5@0?t(B
                   4220: \EG positive integer
                   4221: @item strategy
                   4222: \JP $B@0?t(B
                   4223: \EG integer
                   4224: @end table
                   4225:
                   4226: @itemize @bullet
                   4227: \BJP
                   4228: @item
                   4229: @code{primedec_mod()} $B$O(B @samp{primdec_mod}
                   4230: $B$GDj5A$5$l$F$$$k(B. @code{[Yokoyama]} $B$NAG%$%G%"%kJ,2r%"%k%4%j%:%`(B
                   4231: $B$r<BAu$7$F$$$k(B.
                   4232: @item
                   4233: @code{primedec_mod()} $B$OM-8BBN>e$G$N%$%G%"%k$N(B
                   4234: $B:,4p$NAG%$%G%"%kJ,2r$r9T$$(B, $BAG%$%G%"%k$N%j%9%H$rJV$9(B.
                   4235: @item
                   4236: @code{primedec_mod()} $B$O(B, GF(@var{mod}) $B>e$G$NJ,2r$rM?$($k(B.
                   4237: $B7k2L$N3F@.J,$N@8@.85$O(B, $B@0?t78?tB?9`<0$G$"$k(B.
                   4238: @item
                   4239: $B7k2L$K$*$$$F(B, $BB?9`<0%j%9%H$H$7$FI=<($5$l$F$$$k3F%$%G%"%k$OA4$F(B
                   4240: [@var{vlist},@var{ord}] $B$G;XDj$5$l$k9`=g=x$K4X$9$k%0%l%V%J4pDl$G$"$k(B.
                   4241: @item
                   4242: @var{strategy} $B$,(B 0 $B$G$J$$$H$-(B, incremental $B$K(B component $B$N6&DL(B
                   4243: $BItJ,$r7W;;$9$k$3$H$K$h$k(B early termination $B$r9T$&(B. $B0lHL$K(B,
                   4244: $B%$%G%"%k$N<!85$,9b$$>l9g$KM-8z$@$,(B, 0 $B<!85$N>l9g$J$I(B, $B<!85$,>.$5$$(B
                   4245: $B>l9g$K$O(B overhead $B$,Bg$-$$>l9g$,$"$k(B.
1.7       noro     4246: @item
                   4247: $B7W;;ESCf$GFbIt>pJs$r8+$?$$>l9g$K$O!"(B
                   4248: $BA0$b$C$F(B @code{dp_gr_print(2)} $B$r<B9T$7$F$*$1$P$h$$(B.
1.5       noro     4249: \E
                   4250: \BEG
                   4251: @item
                   4252: Function @code{primedec_mod()}
                   4253: is defined in @samp{primdec_mod} and implements the prime decomposition
                   4254: algorithm in @code{[Yokoyama]}.
                   4255: @item
                   4256: @code{primedec_mod()}
                   4257: is the function for prime ideal decomposition
                   4258: of the radical of a polynomial ideal over small finite field,
                   4259: and they return a list of prime ideals, which are associated primes
                   4260: of the input ideal.
                   4261: @item
                   4262: @code{primedec_mod()} gives the decomposition over GF(@var{mod}).
                   4263: The generators of each resulting component consists of integral polynomials.
                   4264: @item
                   4265: Each resulting component is a Groebner basis with respect to
                   4266: a term order specified by [@var{vlist},@var{ord}].
                   4267: @item
                   4268: If @var{strategy} is non zero, then the early termination strategy
                   4269: is tried by computing the intersection of obtained components
                   4270: incrementally. In general, this strategy is useful when the krull
                   4271: dimension of the ideal is high, but it may add some overhead
                   4272: if the dimension is small.
1.7       noro     4273: @item
                   4274: If you want to see internal information during the computation,
                   4275: execute @code{dp_gr_print(2)} in advance.
1.5       noro     4276: \E
                   4277: @end itemize
                   4278:
                   4279: @example
                   4280: [0] load("primdec_mod")$
                   4281: [246] PP444=[x^8+x^2+t,y^8+y^2+t,z^8+z^2+t]$
                   4282: [247] primedec_mod(PP444,[x,y,z,t],0,2,1);
                   4283: [[y+z,x+z,z^8+z^2+t],[x+y,y^2+y+z^2+z+1,z^8+z^2+t],
                   4284: [y+z+1,x+z+1,z^8+z^2+t],[x+z,y^2+y+z^2+z+1,z^8+z^2+t],
                   4285: [y+z,x^2+x+z^2+z+1,z^8+z^2+t],[y+z+1,x^2+x+z^2+z+1,z^8+z^2+t],
                   4286: [x+z+1,y^2+y+z^2+z+1,z^8+z^2+t],[y+z+1,x+z,z^8+z^2+t],
                   4287: [x+y+1,y^2+y+z^2+z+1,z^8+z^2+t],[y+z,x+z+1,z^8+z^2+t]]
                   4288: [248]
                   4289: @end example
                   4290:
                   4291: @table @t
                   4292: \JP @item $B;2>H(B
                   4293: \EG @item References
                   4294: @fref{modfctr},
1.6       noro     4295: @fref{dp_gr_main dp_gr_mod_main dp_gr_f_main dp_weyl_gr_main dp_weyl_gr_mod_main dp_weyl_gr_f_main},
1.5       noro     4296: \JP @fref{$B9`=g=x$N@_Dj(B}.
1.7       noro     4297: \EG @fref{Setting term orderings},
                   4298: @fref{dp_gr_flags dp_gr_print}.
1.5       noro     4299: @end table
                   4300:
1.10      noro     4301: \JP @node bfunction bfct generic_bfct ann ann0,,, $B%0%l%V%J4pDl$K4X$9$kH!?t(B
                   4302: \EG @node bfunction bfct generic_bfct ann ann0,,, Functions for Groebner basis computation
                   4303: @subsection @code{bfunction}, @code{bfct}, @code{generic_bfct}, @code{ann}, @code{ann0}
1.6       noro     4304: @findex bfunction
1.9       noro     4305: @findex bfct
1.6       noro     4306: @findex generic_bfct
1.10      noro     4307: @findex ann
                   4308: @findex ann0
1.5       noro     4309:
1.6       noro     4310: @table @t
                   4311: @item bfunction(@var{f})
1.10      noro     4312: @itemx bfct(@var{f})
                   4313: @itemx generic_bfct(@var{plist},@var{vlist},@var{dvlist},@var{weight})
                   4314: \JP :: @var{b} $B4X?t$N7W;;(B
                   4315: \EG :: Computes the global @var{b} function of a polynomial or an ideal
                   4316: @item ann(@var{f})
                   4317: @itemx ann0(@var{f})
                   4318: \JP :: $BB?9`<0$N%Y%-$N(B annihilator $B$N7W;;(B
                   4319: \EG :: Computes the annihilator of a power of polynomial
1.6       noro     4320: @end table
1.10      noro     4321:
1.6       noro     4322: @table @var
                   4323: @item return
1.10      noro     4324: \JP $BB?9`<0$^$?$O%j%9%H(B
                   4325: \EG polynomial or list
                   4326: @item f
1.6       noro     4327: \JP $BB?9`<0(B
                   4328: \EG polynomial
                   4329: @item plist
                   4330: \JP $BB?9`<0%j%9%H(B
                   4331: \EG list of polynomials
                   4332: @item vlist dvlist
                   4333: \JP $BJQ?t%j%9%H(B
                   4334: \EG list of variables
                   4335: @end table
1.5       noro     4336:
1.6       noro     4337: @itemize @bullet
                   4338: \BJP
                   4339: @item @samp{bfct} $B$GDj5A$5$l$F$$$k(B.
1.10      noro     4340: @item @code{bfunction(@var{f})}, @code{bfct(@var{f})} $B$OB?9`<0(B @var{f} $B$N(B global @var{b} $B4X?t(B @code{b(s)} $B$r(B
1.6       noro     4341: $B7W;;$9$k(B. @code{b(s)} $B$O(B, Weyl $BBe?t(B @code{D} $B>e$N0lJQ?tB?9`<04D(B @code{D[s]}
                   4342: $B$N85(B @code{P(x,s)} $B$,B8:_$7$F(B, @code{P(x,s)f^(s+1)=b(s)f^s} $B$rK~$?$9$h$&$J(B
                   4343: $BB?9`<0(B @code{b(s)} $B$NCf$G(B, $B<!?t$,:G$bDc$$$b$N$G$"$k(B.
                   4344: @item @code{generic_bfct(@var{f},@var{vlist},@var{dvlist},@var{weight})}
                   4345: $B$O(B, @var{plist} $B$G@8@.$5$l$k(B @code{D} $B$N:8%$%G%"%k(B @code{I} $B$N(B,
1.10      noro     4346: $B%&%'%$%H(B @var{weight} $B$K4X$9$k(B global @var{b} $B4X?t$r7W;;$9$k(B.
1.6       noro     4347: @var{vlist} $B$O(B @code{x}-$BJQ?t(B, @var{vlist} $B$OBP1~$9$k(B @code{D}-$BJQ?t(B
                   4348: $B$r=g$KJB$Y$k(B.
1.9       noro     4349: @item @code{bfunction} $B$H(B @code{bfct} $B$G$OMQ$$$F$$$k%"%k%4%j%:%`$,(B
1.11      noro     4350: $B0[$J$k(B. $B$I$A$i$,9bB.$+$OF~NO$K$h$k(B.
1.10      noro     4351: @item @code{ann(@var{f})} $B$O(B, @code{@var{f}^s} $B$N(B annihilator ideal
                   4352: $B$N@8@.7O$rJV$9(B. @code{ann(@var{f})} $B$O(B, @code{[@var{a},@var{list}]}
                   4353: $B$J$k%j%9%H$rJV$9(B. $B$3$3$G(B, @var{a} $B$O(B @var{f} $B$N(B @var{b} $B4X?t$N:G>.@0?t:,(B,
                   4354: @var{list} $B$O(B @code{ann(@var{f})} $B$N7k2L$N(B @code{s}$ $B$K(B, @var{a} $B$r(B
                   4355: $BBeF~$7$?$b$N$G$"$k(B.
1.7       noro     4356: @item $B>\:Y$K$D$$$F$O(B, [Saito,Sturmfels,Takayama] $B$r8+$h(B.
1.6       noro     4357: \E
                   4358: \BEG
                   4359: @item These functions are defined in @samp{bfct}.
1.10      noro     4360: @item @code{bfunction(@var{f})} and @code{bfct(@var{f})} compute the global @var{b}-function @code{b(s)} of
1.6       noro     4361: a polynomial @var{f}.
                   4362: @code{b(s)} is a polynomial of the minimal degree
                   4363: such that there exists @code{P(x,s)} in D[s], which is a polynomial
                   4364: ring over Weyl algebra @code{D}, and @code{P(x,s)f^(s+1)=b(s)f^s} holds.
                   4365: @item @code{generic_bfct(@var{f},@var{vlist},@var{dvlist},@var{weight})}
1.10      noro     4366: computes the global @var{b}-function of a left ideal @code{I} in @code{D}
1.6       noro     4367: generated by @var{plist}, with respect to @var{weight}.
                   4368: @var{vlist} is the list of @code{x}-variables,
                   4369: @var{vlist} is the list of corresponding @code{D}-variables.
1.9       noro     4370: @item @code{bfunction(@var{f})} and @code{bfct(@var{f})} implement
                   4371: different algorithms and the efficiency depends on inputs.
1.10      noro     4372: @item @code{ann(@var{f})} returns the generator set of the annihilator
                   4373: ideal of @code{@var{f}^s}.
                   4374: @code{ann(@var{f})} returns a list @code{[@var{a},@var{list}]},
                   4375: where @var{a} is the minimal integral root of the global @var{b}-function
                   4376: of @var{f}, and @var{list} is a list of polynomials obtained by
                   4377: substituting @code{s} in @code{ann(@var{f})} with @var{a}.
1.7       noro     4378: @item See [Saito,Sturmfels,Takayama] for the details.
1.6       noro     4379: \E
                   4380: @end itemize
                   4381:
                   4382: @example
                   4383: [0] load("bfct")$
                   4384: [216] bfunction(x^3+y^3+z^3+x^2*y^2*z^2+x*y*z);
                   4385: -9*s^5-63*s^4-173*s^3-233*s^2-154*s-40
                   4386: [217] fctr(@@);
                   4387: [[-1,1],[s+2,1],[3*s+4,1],[3*s+5,1],[s+1,2]]
                   4388: [218] F = [4*x^3*dt+y*z*dt+dx,x*z*dt+4*y^3*dt+dy,
                   4389: x*y*dt+5*z^4*dt+dz,-x^4-z*y*x-y^4-z^5+t]$
                   4390: [219] generic_bfct(F,[t,z,y,x],[dt,dz,dy,dx],[1,0,0,0]);
                   4391: 20000*s^10-70000*s^9+101750*s^8-79375*s^7+35768*s^6-9277*s^5
                   4392: +1278*s^4-72*s^3
1.10      noro     4393: [220] P=x^3-y^2$
                   4394: [221] ann(P);
                   4395: [2*dy*x+3*dx*y^2,-3*dx*x-2*dy*y+6*s]
                   4396: [222] ann0(P);
                   4397: [-1,[2*dy*x+3*dx*y^2,-3*dx*x-2*dy*y-6]]
1.6       noro     4398: @end example
                   4399:
                   4400: @table @t
                   4401: \JP @item $B;2>H(B
                   4402: \EG @item References
                   4403: \JP @fref{Weyl $BBe?t(B}.
                   4404: \EG @fref{Weyl algebra}.
                   4405: @end table
1.5       noro     4406:

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