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

Annotation of OpenXM/src/asir-doc/parts/algnum.texi, Revision 1.8

1.8     ! noro        1: @comment $OpenXM: OpenXM/src/asir-doc/parts/algnum.texi,v 1.7 2003/04/20 08:01:24 noro Exp $
1.2       noro        2: \BJP
1.1       noro        3: @node $BBe?tE*?t$K4X$9$k1i;;(B,,, Top
                      4: @chapter $BBe?tE*?t$K4X$9$k1i;;(B
1.2       noro        5: \E
                      6: \BEG
                      7: @node Algebraic numbers,,, Top
                      8: @chapter Algebraic numbers
                      9: \E
1.1       noro       10:
                     11: @menu
1.2       noro       12: \BJP
1.1       noro       13: * $BBe?tE*?t$NI=8=(B::
1.8     ! noro       14: * $BJ,;6B?9`<0$K$h$kBe?tE*?t$NI=8=(B::
1.1       noro       15: * $BBe?tE*?t$N1i;;(B::
                     16: * $BBe?tBN>e$G$N(B 1 $BJQ?tB?9`<0$N1i;;(B::
                     17: * $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B::
1.2       noro       18: \E
                     19: \BEG
                     20: * Representation of algebraic numbers::
1.8     ! noro       21: * Representation of algebraic numbers by distributed polynomials::
1.2       noro       22: * Operations over algebraic numbers::
                     23: * Operations for uni-variate polynomials over an algebraic number field::
                     24: * Summary of functions for algebraic numbers::
                     25: \E
1.1       noro       26: @end menu
                     27:
1.2       noro       28: \BJP
1.1       noro       29: @node $BBe?tE*?t$NI=8=(B,,, $BBe?tE*?t$K4X$9$k1i;;(B
                     30: @section $BBe?tE*?t$NI=8=(B
1.2       noro       31: \E
                     32: \BEG
                     33: @node Representation of algebraic numbers,,, Algebraic numbers
                     34: @section Representation of algebraic numbers
                     35: \E
1.1       noro       36:
                     37: @noindent
1.2       noro       38: \BJP
1.1       noro       39: @b{Asir} $B$K$*$$$F$O(B, $BBe?tBN$H$$$&BP>]$ODj5A$5$l$J$$(B.
                     40: $BFHN)$7$?BP>]$H$7$FDj5A$5$l$k$N$O(B, $BBe?tE*?t$G$"$k(B.
                     41: $BBe?tBN$O(B, $BM-M}?tBN$K(B, $BBe?tE*?t$rM-8B8D(B
                     42: $B=g<!E:2C$7$?BN$H$7$F2>A[E*$KDj5A$5$l$k(B. $B?7$?$JBe?tE*?t$O(B, $BM-M}?t$*$h$S(B
                     43: $B$3$l$^$GDj5A$5$l$?Be?tE*?t$NB?9`<0$r78?t$H$9$k(B 1 $BJQ?tB?9`<0(B
                     44: $B$rDj5AB?9`<0$H$7$FDj5A$5$l$k(B. $B0J2<(B, $B$"$kDj5AB?9`<0$N:,$H$7$F(B
                     45: $BDj5A$5$l$?Be?tE*?t$r(B, @code{root} $B$H8F$V$3$H$K$9$k(B.
1.2       noro       46: \E
                     47: \BEG
                     48: In @b{Asir} algebraic number fields are not defined
                     49: as independent objects.
                     50: Instead, individual algebraic numbers are defined by some
                     51: means. In @b{Asir} an algebraic number field is
                     52: defined virtually as a number field obtained by adjoining a finite number
                     53: of algebraic numbers to the rational number field.
                     54:
                     55: A new algebraic number is introduced in @b{Asir} in such a way where
                     56: it is defined as a root of an uni-variate polynomial
                     57: whose coefficients include already defined algebraic numbers
                     58: as well as rational numbers.
                     59: We shall call such a newly defined algebraic number a @b{root}.
                     60: Also, we call such an uni-variate polynomial the defining polynomial
                     61: of that @b{root}.
                     62: \E
1.1       noro       63:
                     64: @example
                     65: [0] A0=newalg(x^2+1);
                     66: (#0)
                     67: [1] A1=newalg(x^3+A0*x+A0);
                     68: (#1)
                     69: [2]  [type(A0),ntype(A0)];
                     70: [1,2]
                     71: @end example
                     72:
                     73: @noindent
1.2       noro       74: \BJP
1.1       noro       75: $B$3$NNc$G$O(B, @code{A0} $B$O(B @code{x^2+1=0} $B$N:,(B, @code{A1} $B$O(B, $B$=$N(B @code{A0}
                     76: $B$r78?t$K4^$`(B @code{x^3+A0*x+A0=0} $B$N:,$H$7$FDj5A$5$l$F$$$k(B.
1.2       noro       77: \E
                     78: \BEG
                     79: In this example, the algebraic number assigned to @code{A0} is defined
                     80: as a @b{root} of a polynomial @code{x^2+1};
                     81: that of @code{A1} is defined as a @b{root} of a polynomial
                     82: @code{x^3+A0*x+A0}, which you see contains the previously defined
                     83: @b{root} (@code{A0}) in its coefficients.
                     84: \E
1.1       noro       85:
                     86: @noindent
1.2       noro       87: \JP @code{newalg()} $B$N0z?t$9$J$o$ADj5AB?9`<0$K$O<!$N$h$&$J@)8B$,$"$k(B.
                     88: \BEG
                     89: The argument to @code{newalg()}, i.e., the defining polynomial,
                     90: must satisfy the following conditions.
                     91: \E
1.1       noro       92:
                     93: @enumerate
                     94: @item
1.2       noro       95: \JP $BDj5AB?9`<0$O(B 1 $BJQ?tB?9`<0$G$J$1$l$P$J$i$J$$(B.
                     96: \EG A defining polynomial must be an uni-variate polynomial.
1.1       noro       97:
                     98: @item
1.2       noro       99: \BJP
1.1       noro      100: @code{newalg()} $B$N0z?t$G$"$kDj5AB?9`<0$O(B, $BBe?tE*?t$r4^$`<0$N4JC12=$N$?(B
                    101: $B$a$KMQ$$$i$l$k(B. $B$3$N4JC12=$O(B, $BAH$_9~$_H!?t(B @code{srem()} $B$KAjEv$9$kFb(B
                    102: $BIt%k!<%A%s$rMQ$$$F9T$o$l$k(B. $B$3$N$?$a(B, $BDj5AB?9`<0$N<g78?t$O(B, $BM-M}?t$K(B
                    103: $B$J$C$F$$$kI,MW$,$"$k(B.
1.2       noro      104: \E
                    105: \BEG
                    106: A defining polynomial is used
                    107: to simplify expressions containing that algebraic number.
                    108: The procedure of such simplification is performed by an internal routine
                    109: similar to the built-in function @code{srem()}, where the defining
                    110: polynomial is used for the second argument, the divisor.
                    111: By this reason, the leading coefficient of the defining polynomial
                    112: must be a rational number (must not be an algebraic number.)
                    113: \E
1.1       noro      114:
                    115: @item
1.2       noro      116: \BJP
1.1       noro      117: $BDj5AB?9`<0$N78?t$O(B $B$9$G$KDj5A$5$l$F$$$k(B @code{root} $B$NM-M}?t78?tB?9`<0(B
                    118: $B$G$J$1$l$P$J$i$J$$(B.
1.2       noro      119: \E
                    120: \BEG
                    121: Every coefficients of a defining polynomial must be
                    122: a `(multi-variate) polynomial' in already defined @b{root}'s.
                    123: Here, `(multi-variate) polynomial' means a mathematical concept,
                    124: not the object type `polynomial' in @b{Asir}.
                    125: \E
1.1       noro      126: @item
1.2       noro      127: \BJP
1.1       noro      128: $BDj5AB?9`<0$O(B, $B$=$N78?t$K4^$^$l$kA4$F$N(B @code{root} $B$rM-M}?t$KE:2C$7$?(B
                    129: $BBN>e$G4{Ls$G$J$1$l$P$J$i$J$$(B.
1.2       noro      130: \E
                    131: \BEG
                    132: A defining polynomial must be irreducible over the field that is obtained
                    133: by adjoining all @b{root}'s contained in its coefficients
                    134: to the rational number field.
                    135: \E
1.1       noro      136: @end enumerate
                    137:
                    138: @noindent
1.2       noro      139: \BJP
1.1       noro      140: @code{newalg()} $B$,9T$&0z?t%A%'%C%/$O(B, 1 $B$*$h$S(B 2 $B$N$_$G$"$k(B.
                    141: $BFC$K(B, $B0z?t$NDj5AB?9`<0$N4{Ls@-$OA4$/%A%'%C%/$5$l$J$$(B. $B$3$l$O(B
                    142: $B4{Ls@-$N%A%'%C%/$,B?Bg$J7W;;NL$rI,MW$H$9$k$?$a$G(B, $B$3$NE@$K4X$7$F$O(B,
                    143: $B%f!<%6$N@UG$$KG$$5$l$F$$$k(B.
1.2       noro      144: \E
                    145: \BEG
                    146: Only the first two conditions (1 and 2) are checked
                    147: by function @code{newalg()}.
                    148: Among all, it should be emphasized that no check is done for the
                    149: irreducibility at all.
                    150: The reason is that the irreducibility test requires enormously much
                    151: computation time.  You are trusted whether to check it at your own risk.
                    152: \E
1.1       noro      153:
                    154: @noindent
1.2       noro      155: \BJP
1.1       noro      156: $B0lC6(B @code{newalg()} $B$K$h$C$FDj5A$5$l$?Be?tE*?t$O(B, $B?t$H$7$F$N<1JL;R$r;}$A(B,
                    157: $B$^$?(B, $B?t$NCf$G$OBe?tE*?t$H$7$F$N<1JL;R$r;}$D(B. (@code{type()}, @code{vtype()}
                    158: $B;2>H(B.) $B$5$i$K(B, $BM-M}?t$H(B, @code{root} $B$NM-M}<0$bF1MM$KBe?tE*?t$H$J$k(B.
1.2       noro      159: \E
                    160: \BEG
                    161: Once a @b{root} has been defined by @code{newalg()} function,
                    162: it is given the type identifier for a number, and furthermore,
                    163: the sub-type identifier for an algebraic number.
                    164: (@xref{type}, @ref{ntype}.)
                    165: Also, any rational combination of rational numbers and @b{root}'s
                    166: is an algebraic number.
                    167: \E
1.1       noro      168:
                    169: @example
                    170: [87] N=(A0^2+A1)/(A1^2-A0-1);
                    171: ((#1+#0^2)/(#1^2-#0-1))
                    172: [88] [type(N),ntype(N)];
                    173: [1,2]
                    174: @end example
                    175:
                    176: @noindent
1.2       noro      177: \BJP
1.1       noro      178: $BNc$+$i$o$+$k$h$&$K(B, @code{root}$B$O(B @code{#@var{n}}
                    179: $B$HI=<($5$l$k(B. $B$7$+$7(B, $B%f!<%6$O$3$N7A$G$OF~NO$G$-$J$$(B. @code{root} $B$O(B
                    180: $BJQ?t$K3JG<$7$FMQ$$$k$+(B, $B$"$k$$$O(B @code{alg(@var{n})} $B$K$h$j<h$j=P$9(B.
                    181: $B$^$?(B, $B8zN($OMn$A$k$,(B, $BA4$/F1$80z?t(B ($BJQ?t$O0[$J$C$F$$$F$b$h$$(B) $B$K$h$j(B
                    182: @code{newalg()} $B$r8F$Y$P(B, $B?7$7$$Be?tE*?t$ODj5A$5$l$:$K4{$KDj5A$5$l$?(B
                    183: $B$b$N$,F@$i$l$k(B.
1.2       noro      184: \E
                    185: \BEG
                    186: As you see it in the example, a @b{root} is displayed as
                    187: @code{#@var{n}}.  But, you cannot input that @b{root} in
                    188: its immediate output form.
                    189: You have to refer to a @b{root} by a program variable assigned
                    190: to the @b{root}, or to get it by @code{alg(@var{n})} function, or by
                    191: several other indirect means.
                    192: A strange use of @code{newalg()}, with a same argument polynomial
                    193: (except for the name of its main variable), will yield the old
                    194: @b{root} instead of a new @b{root} though it is apparently inefficient.
                    195: \E
1.1       noro      196:
                    197: @example
                    198: [90] alg(0);
                    199: (#0)
                    200: [91] newalg(t^2+1);
                    201: (#0)
                    202: @end example
                    203:
                    204: @noindent
1.2       noro      205: \JP @code{root} $B$NDj5AB?9`<0$O(B, @code{defpoly()} $B$K$h$j<h$j=P$;$k(B.
                    206: \BEG
                    207: The defining polynomial of a @b{root} can be obtained by
                    208: @code{defpoly()} function.
                    209: \E
1.1       noro      210:
                    211: @example
                    212: [96] defpoly(A0);
                    213: t#0^2+1
                    214: [97] defpoly(A1);
                    215: t#1^3+t#0*t#1+t#0
                    216: @end example
                    217:
                    218: @noindent
1.2       noro      219: \BJP
1.1       noro      220: $B$3$3$G8=$l$?(B, @code{t#0}, @code{t#1} $B$O$=$l$>$l(B @code{#0}, @code{#1} $B$K(B
                    221: $BBP1~$9$kITDj85$G$"$k(B. $B$3$l$i$b%f!<%6$,F~NO$9$k$3$H$O$G$-$J$$(B.
                    222: @code{var()} $B$G<h$j=P$9$+(B, $B$"$k$$$O(B @code{algv(@var{n})} $B$K$h$j<h$j=P$9(B.
1.2       noro      223: \E
                    224: \BEG
                    225: Here, you see a strange expression, @code{t#0} and @code{t#1}.
                    226: They are a specially indeterminates generated and maintained
                    227: by @b{Asir} internally.  Indeterminate @code{t#0} corresponds to
                    228: @b{root} @code{#0}, and @code{t#0} to @code{#1}.  These indeterminates
                    229: also cannot be input directly by a user in their immediate forms.
                    230: You can get them by several ways: by @code{var()} function,
                    231: or @code{algv(@var{n})} function.
                    232: \E
1.1       noro      233:
                    234: @example
                    235: [98] var(@@);
                    236: t#1
                    237: [99] algv(0);
                    238: t#0
                    239: [100]
                    240: @end example
                    241:
1.8     ! noro      242:
        !           243: @example
        !           244: @end example
        !           245:
1.2       noro      246: \BJP
1.1       noro      247: @node $BBe?tE*?t$N1i;;(B,,, $BBe?tE*?t$K4X$9$k1i;;(B
                    248: @section $BBe?tE*?t$N1i;;(B
1.2       noro      249: \E
                    250: \BEG
                    251: @node Operations over algebraic numbers,,, Algebraic numbers
                    252: @section Operations over algebraic numbers
                    253: \E
1.1       noro      254:
                    255: @noindent
1.2       noro      256: \BJP
1.1       noro      257: $BA0@a$G(B, $BBe?tE*?t$NI=8=(B, $BDj5A$K$D$$$F=R$Y$?(B. $B$3$3$G$O(B, $BBe?tE*?t$rMQ$$$?(B
                    258: $B1i;;$K$D$$$F=R$Y$k(B. $BBe?tE*?t$K4X$7$F$O(B, $BAH$_9~$_H!?t$H$7$FDs6!$5$l$F$$$k(B
                    259: $B5!G=$O$4$/>/?t$G(B, $BBgItJ,$O%f!<%6Dj5AH!?t$K$h$j<B8=$5$l$F$$$k(B. $B%U%!%$%k(B
                    260: $B$O(B, @samp{sp} $B$G(B, @samp{gr} $B$HF1MM(B @b{Asir} $B$NI8=`%i%$%V%i%j%G%#%l%/%H%j(B
                    261: $B$K$*$+$l$F$$$k(B.
1.2       noro      262: \E
                    263: \BEG
                    264: In the previous section, we explained about the
                    265: representation of algebraic numbers and their defining method.
                    266: Here, we describe operations on algebraic numbers.
                    267: Only a few functions are built-in, and almost all functions are provided
                    268: as user defined functions.  The file containing their definitions is
                    269: @samp{sp}, and it is placed under the same directory
                    270: as @samp{gr} is placed, i.e., the standard library directory of @b{Asir}.
                    271: \E
1.1       noro      272:
                    273: @example
                    274: [0] load("gr")$
                    275: [1] load("sp")$
                    276: @end example
                    277:
                    278: @noindent
1.2       noro      279: \JP $B$"$k$$$O(B, $B>o$KMQ$$$k$J$i$P(B, @samp{$HOME/.asirrc} $B$K=q$$$F$*$/$N$b$h$$(B.
                    280: \BEG
                    281: Or if you always need them, it is more convenient to include the
                    282: @code{load} commands in @samp{$HOME/.asirrc}.
                    283: \E
1.1       noro      284:
                    285: @noindent
1.2       noro      286: \BJP
1.1       noro      287: @code{root} $B$O(B $B$=$NB>$N?t$HF1MM(B, $B;MB'1i;;$,2DG=$H$J$k(B. $B$7$+$7(B, $BDj5AB?(B
                    288: $B9`<0$K$h$k4JC12=$O<+F0E*$K$O9T$o$l$J$$$N$G(B, $B%f!<%6$NH=CG$GE,599T$o(B
                    289: $B$J$1$l$P$J$i$J$$(B. $BFC$K(B, $BJ,Jl$,(B 0 $B$K$J$k>l9g$KCWL?E*$J%(%i!<$H$J$k$?$a(B,
                    290: $B<B:]$KJ,Jl$r;}$DBe?tE*?t$r@8@.$9$k>l9g$K$O:Y?4$NCm0U$,I,MW$H$J$k(B.
1.2       noro      291: \E
                    292: \BEG
                    293: Like the other numbers, algebraic numbers can get arithmetic operations
                    294: applied. Simplification, however, by defining polynomials are
                    295: not automatically performed.  It is left to users to simplify their
                    296: expressions.  A fatal error shall result if the denominator expression
                    297: will be simplified to 0.  Therefore, be careful enough when you
                    298: will create and deal with algebraic numbers which may denominators
                    299: in their expressions.
                    300: \E
                    301:
                    302: \JP $BBe?tE*?t$N(B, $BDj5AB?9`<0$K$h$k4JC12=$O(B, @code{simpalg()} $B$G9T$&(B.
                    303: \BEG
                    304: Use @code{simpalg()} function for simplification of algebraic numbers
                    305: by defining polynomials.
                    306: \E
1.1       noro      307:
                    308: @example
                    309: [49] T=A0^2+1;
                    310: (#0^2+1)
                    311: [50] simpalg(T);
                    312: 0
                    313: @end example
                    314:
                    315: @noindent
1.2       noro      316: \JP @code{simpalg()} $B$OM-M}<0$N7A$r$7$?Be?tE*?t$r(B, $BB?9`<0$N7A$K4JC12=$9$k(B.
                    317: \BEG
                    318: Function @code{simpalg()} simplifies algebraic numbers which have
                    319: the same structures as rational expressions in their appearances.
                    320: \E
1.1       noro      321:
                    322: @example
                    323: [39] A0=newalg(x^2+1);
                    324: (#0)
                    325: [40] T=(A0^2+A0+1)/(A0+3);
                    326: ((#0^2+#0+1)/(#0+3))
                    327: [41] simpalg(T);
                    328: (3/10*#0+1/10)
                    329: [42] T=1/(A0^2+1);
                    330: ((1)/(#0^2+1))
                    331: [43] simpalg(T);
                    332: div : division by 0
                    333: stopped in invalgp at line 258 in file "/usr/local/lib/asir/sp"
                    334: 258                     return 1/A;
                    335: (debug)
                    336: @end example
                    337:
                    338: @noindent
1.2       noro      339: \BJP
1.1       noro      340: $B$3$NNc$G$O(B, $BJ,Jl$,(B 0 $B$NBe?tE*?t$r4JC12=$7$h$&$H$7$F(B 0 $B$K$h$k=|;;$,@8$8(B
                    341: $B$?$?$a(B, $B%f!<%6Dj5AH!?t$G$"$k(B @code{simpalg()} $B$NCf$G%G%P%C%,$,8F$P$l$?(B
                    342: $B$3$H$r<($9(B. @code{simpalg()} $B$O(B, $BBe?tE*?t$r78?t$H$9$kB?9`<0$N(B
                    343: $B3F78?t$r4JC12=$G$-$k(B.
1.2       noro      344: \E
                    345: \BEG
                    346: This example shows an error caused by zero division in the course of
                    347: program execution of @code{simpalg()}, which attempted to simplify
                    348: an algebraic number expression of which the denominator is 0.
                    349:
                    350: Function @code{simpalg()} also can take a polynomial as its argument
                    351: and simplifies algebraic numbers in its coefficients.
                    352: \E
1.1       noro      353:
                    354: @example
                    355: [43] simpalg(1/A0*x+1/(A0+1));
                    356: (-#0)*x+(-1/2*#0+1/2)
                    357: @end example
                    358:
                    359: @noindent
1.2       noro      360: \BJP
1.1       noro      361: $BBe?tE*?t$r78?t$H$9$kB?9`<0$N4pK\1i;;$O(B, $BE,59(B @code{simpalg()} $B$r8F$V$3$H$r(B
                    362: $B=|$1$PDL>o$N>l9g$HF1MM$G$"$k$,(B, $B0x?tJ,2r$J$I$GIQHK$KMQ$$$i$l$k%N%k%`$N(B
                    363: $B7W;;$J$I$K$*$$$F$O(B, @code{root} $B$rITDj85$KCV$-49$($kI,MW$,=P$F$/$k(B.
                    364: $B$3$N>l9g(B, @code{algptorat()} $B$rMQ$$$k(B.
1.2       noro      365: \E
                    366: \BEG
                    367: Thus, you can operate in polynomials which contain algebraic numbers
                    368: as you do usually in ordinary polynomials,
                    369: except for proper simplification by @code{simpalg()}.
                    370: You may sometimes feel needs to convert @b{root}'s into indeterminates,
                    371: especially when you are working for norm computation in algorithms for
                    372: algebraic factorization.
                    373: Function @code{algptorat()} is used for such cases.
                    374: \E
1.1       noro      375:
                    376: @example
                    377: [83] A0=newalg(x^2+1);
                    378: (#0)
                    379: [84] A1=newalg(x^3+A0*x+A0);
                    380: (#1)
                    381: [85] T=(2*A0+A1*A0+A1^2)*x+(1+A1)/(2+A0);
                    382: (#1^2+#0*#1+2*#0)*x+((#1+1)/(#0+2))
                    383: [86] S=algptorat(T);
                    384: (((t#0+2)*t#1^2+(t#0^2+2*t#0)*t#1+2*t#0^2+4*t#0)*x+t#1+1)/(t#0+2)
                    385: [87] algptorat(coef(T,1));
                    386: t#1^2+t#0*t#1+2*t#0
                    387: @end example
                    388:
                    389: @noindent
1.2       noro      390: \BJP
1.1       noro      391: $B$3$N$h$&$K(B, @code{algptorat()} $B$O(B, $BB?9`<0(B, $B?t$K4^$^$l$k(B @code{root}
                    392: $B$r(B, $BBP1~$9$kITDj85(B, $B$9$J$o$A(B @code{#@var{n}} $B$KBP$9$k(B @code{t#@var{n}}
                    393: $B$KCV$-49$($k(B. $B4{$K=R$Y$?$h$&$K(B, $B$3$NITDj85$O%f!<%6$,F~NO$9$k$3$H$O$G$-$J$$(B.
                    394: $B$3$l$O(B, $B%f!<%6$NF~NO$7$?ITDj85$H(B, @code{root} $B$KBP1~$9$kITDj85$,0lCW(B
                    395: $B$7$J$$$h$&$K$9$k$?$a$G$"$k(B.
1.2       noro      396: \E
                    397: \BEG
                    398: As you see by the example,
                    399: function @code{algptorat()} converts @b{root}'s, @code{#@var{n}},
                    400: in polynomials and numbers into its associated indeterminates,
                    401: @code{t#@var{n}}.  As was already mentioned those indeterminates cannot
                    402: be directly input in their immediate form.
                    403: The restriction is adopted to avoid the confusion that might happen
                    404: if the user could input such internally generatable indeterminates.
                    405: \E
1.1       noro      406:
                    407: @noindent
1.2       noro      408: \BJP
1.1       noro      409: $B5U$K(B, @code{root} $B$KBP1~$9$kITDj85$r(B, $BBP1~$9$k(B @code{root} $B$KCV$-49$($k(B
                    410: $B$?$a$K$O(B @code{rattoalgp()} $B$rMQ$$$k(B.
1.2       noro      411: \E
                    412: \BEG
                    413: The associated indeterminate to a @b{root} is reversely converted
                    414: into the @b{root} by @code{rattoalgp()} function.
                    415: \E
1.1       noro      416:
                    417: @example
                    418: [88] rattoalgp(S,[alg(0)]);
1.7       noro      419: (((#0+2)/(#0+2))*t#1^2+((#0^2+2*#0)/(#0+2))*t#1
                    420: +((2*#0^2+4*#0)/(#0+2)))*x+((1)/(#0+2))*t#1+((1)/(#0+2))
1.1       noro      421: [89] rattoalgp(S,[alg(0),alg(1)]);
1.7       noro      422: (((#0^3+6*#0^2+12*#0+8)*#1^2+(#0^4+6*#0^3+12*#0^2+8*#0)*#1
                    423: +2*#0^4+12*#0^3+24*#0^2+16*#0)/(#0^3+6*#0^2+12*#0+8))*x
                    424: +(((#0+2)*#1+#0+2)/(#0^2+4*#0+4))
1.1       noro      425: [90] rattoalgp(S,[alg(1),alg(0)]);
1.7       noro      426: (((#0+2)*#1^2+(#0^2+2*#0)*#1+2*#0^2+4*#0)/(#0+2))*x
                    427: +((#1+1)/(#0+2))
1.1       noro      428: [91] simpalg(@@89);
                    429: (#1^2+#0*#1+2*#0)*x+((-1/5*#0+2/5)*#1-1/5*#0+2/5)
                    430: [92] simpalg(@@90);
                    431: (#1^2+#0*#1+2*#0)*x+((-1/5*#0+2/5)*#1-1/5*#0+2/5)
                    432: @end example
                    433:
                    434: @noindent
1.2       noro      435: \BJP
1.1       noro      436: @code{rattoalgp()} $B$O(B, $BCV49$NBP>]$H$J$k(B @code{root} $B$N%j%9%H$rBh(B 2 $B0z?t(B
                    437: $B$K$H$j(B, $B:8$+$i=g$K(B, $BBP1~$9$kITDj85$rCV$-49$($F9T$/(B. $B$3$NNc$O(B,
                    438: $BCV49$9$k=g=x$r49$($k$H4JC12=$r9T$o$J$$$3$H$K$h$j7k2L$,0l8+0[$J$k$,(B,
                    439: $B4JC12=$K$h$j<B$O0lCW$9$k$3$H$r<($7$F$$$k(B. @code{algptorat()},
                    440: @code{rattoalgp()} $B$O(B, $B%f!<%6$,FH<+$N4JC12=$r9T$$$?$$>l9g$J$I$K$b(B
                    441: $BMQ$$$k$3$H$,$G$-$k(B.
1.2       noro      442: \E
                    443: \BEG
                    444: Function @code{rattoalgp()} takes as the second argument
                    445: a list consisting of @b{root}'s that you want to convert,
                    446: and converts them successively from the left.
                    447: This example shows that apparent difference of the results due to
                    448: the order of such conversion will vanish by simplification yielding
                    449: the same result.
                    450: Functions @code{algptorat()} and @code{rattoalgp()} can be conveniently
                    451: used for your own simplification.
                    452: \E
1.1       noro      453:
1.2       noro      454: \BJP
1.8     ! noro      455: @node $BJ,;6B?9`<0$K$h$kBe?tE*?t$NI=8=(B,,, $BBe?tE*?t$K4X$9$k1i;;(B
        !           456: @section $BJ,;6B?9`<0$K$h$kBe?tE*?t$NI=8=(B
        !           457: \E
        !           458: \BEG
        !           459: @node Representation of algebraic numbers by distributed polynomials,,, Algebraic numbers
        !           460: @section Representation of algebraic numbers by distributed polynomials
        !           461: \E
        !           462:
        !           463: @noindent
        !           464: \BJP
        !           465: $BA0@a$G=R$Y$?$h$&$K(B, @code{root} $B$r4^$`Be?tE*?t$KBP$9$k4JC12=$O(B
        !           466: $B%f!<%6$NH=CG$G9T$&I,MW$,$"$k(B. $B$3$l$KBP$7(B, $B$3$3$G2r@b$9$k$b$&0l$D$NBe?tE*?t$N(B
        !           467: $BI=8=$K$D$$$F$O(B, $B2C8:>h=|(B, $B%Y%-$J$I$r9T$C$?$"$H<+F0E*$K4JC12=$,9T$o$l$k(B.
        !           468: $B$3$NI=8=$O(B, $BC`<!3HBg$N>l9g$KFC$K8zN($h$/7W;;$,9T$o$l$k$h$&@_7W$5$l$F$*$j(B,
        !           469: $B%0%l%V%J!<4pDl4X78$N4X?t$K$*$1$k78?tBN$H$7$FMQ$$$k$3$H$,$G$-$k(B. $B$3$NI=8=$O(B
        !           470: $BFbItE*$K$O(B, @code{DAlg} $B$H8F$P$l$k%*%V%8%'%/%H$H$7$FDj5A$5$l$F$$$k(B.
        !           471: @code{DAlg} $B$OJ,?t<0$N7A$GJ];}$5$l$k(B. $BJ,Jl$O@0?t(B, $BJ,;R$O@0?t78?t$NJ,;6B?9`<0$G$"$k(B.
        !           472: \E
        !           473: \BEG
        !           474: Simplification of algebraic numbers containing @code{root}
        !           475: is not done automatically and should be done by users.
        !           476: There is another representation of algebraic numbers, for which the
        !           477: results of fundamental operations are automatically simplified.
        !           478: This representations are designed so that operations are efficiently
        !           479: performed especially when the field is a successive extension and
        !           480: it can be used as a ground field for Groebner basis related functions.
        !           481: Internally an algebraic number of this type is defined as an object
        !           482: called @code{DAlg}. A @code{DAlg} is represented as a fraction. The
        !           483: denominator is an integer and the numerator is a distributed polynomial
        !           484: with integral coefficients.
        !           485: \E
        !           486:
        !           487: \BJP
        !           488: @code{DAlg} $B$O!$(B@code{set_field()} $B$K$h$j$"$i$+$8$a@_Dj$5$l$?Be?tBN$N(B
        !           489: $B85$H$7$F@8@.$5$l$k(B. $B@8@.J}K!$O(B, @code{newalg()} $B$G@8@.$5$l$?Be?tE*?t$r(B
        !           490: $B4^$`?t$+$i(B @code{algtodalg()} $B$GJQ49$9$k(B, $B$"$k$$$OJ,;6B?9`<0$+$iD>@\(B
        !           491: @code{dptodalg()} $B$GJQ49$9$k!$$N(B 2 $BDL$j$"$k(B.
        !           492: $B0lC6(B @code{DAlg} $B7A<0$KJQ49$5$l$l$P(B, $B1i;;8e$K<+F0E*$K4JC12=$5$l$k(B.
        !           493: \E
        !           494: \BEG
        !           495: @code{DAlg} is generated as an element of an algebraic number field
        !           496: set by @code{set_field()}. There are two methods to generate a @code{DAlg}.
        !           497: @code{algtodalg()} converts an algebraic number containing @code{root}
        !           498: to @code{DAlg}. @code{dptodalg()} directly converts a distributed polynomial to
        !           499: @code{DAlg}.
        !           500: \E
        !           501: @example
        !           502: [0] A=newalg(x^2+1);
        !           503: (#0)
        !           504: [1] B=newalg(x^3+A*x+A);
        !           505: (#1)
        !           506: [2] set_field([B,A]);
        !           507: 0
        !           508: [3] C=algtodalg(A+B);
        !           509: ((1)*<<1,0>>+(1)*<<0,1>>)
        !           510: [4] C^5;
        !           511: ((-11)*<<2,1>>+(5)*<<2,0>>+(10)*<<1,1>>+(9)*<<1,0>>+(11)*<<0,1>>
        !           512: +(-1)*<<0,0>>)
        !           513: [5] 1/C;
        !           514: ((2)*<<2,1>>+(-1)*<<2,0>>+(1)*<<1,1>>+(2)*<<1,0>>+(-3)*<<0,1>>
        !           515: +(-1)*<<0,0>>)/5
        !           516: @end example
        !           517: \BJP
        !           518: $B$3$NNc$G$O(B, Q(a,b) (a^2+1=0, b^3+ab+b=0) $B$K$*$$$F(B, (a+b)^5 $B$*$h$S(B 1/(a+b) $B$r(B
        !           519: $B7W;;(B ($B4JC12=(B) $B$7$F$$$k(B. $BJ,;R$G$"$kJ,;6B?9`<0$NI=<($O(B, $BJ,;6B?9`<0$NI=<($r$=$N$^$^N.MQ$7$F$$$k(B.
        !           520: \E
        !           521: \BEG
        !           522: In this example Q(a,b) (a^2+1=0, b^3+ab+b=0) is set as the current ground field,
        !           523: and (a+b)^5 and 1/(a+b) are simplified in the field. The numerators of the results
        !           524: are printed as distributed polynomials.
        !           525: \E
        !           526:
        !           527: \BJP
1.1       noro      528: @node $BBe?tBN>e$G$N(B 1 $BJQ?tB?9`<0$N1i;;(B,,, $BBe?tE*?t$K4X$9$k1i;;(B
                    529: @section $BBe?tBN>e$G$N(B 1 $BJQ?tB?9`<0$N1i;;(B
1.2       noro      530: \E
                    531: \BEG
                    532: @node Operations for uni-variate polynomials over an algebraic number field,,, Algebraic numbers
                    533: @section Operations for uni-variate polynomials over an algebraic number field
                    534: \E
1.1       noro      535:
                    536: @noindent
1.2       noro      537: \BJP
1.1       noro      538: @samp{sp} $B$G$O(B, 1 $BJQ?tB?9`<0$K8B$j(B, GCD, $B0x?tJ,2r$*$h$S$=$l$i$N1~MQ$H$7$F(B
                    539: $B:G>.J,2rBN$r5a$a$kH!?t$rDs6!$7$F$$$k(B.
1.2       noro      540: \E
                    541: \BEG
                    542: In the file @samp{sp} are provided functions for uni-variate polynomial
                    543: factorization and uni-variate polynomial GCD computation
                    544: over algebraic numbers,
                    545: and furthermore, as an application of them,
                    546: functions to compute splitting fields of univariate polynomials.
                    547: \E
1.1       noro      548:
                    549: @menu
                    550: * GCD::
1.2       noro      551: \BJP
1.1       noro      552: * $BL5J?J}J,2r(B $B0x?tJ,2r(B::
                    553: * $B:G>.J,2rBN(B::
1.2       noro      554: \E
                    555: \BEG
                    556: * Square-free factorization and Factorization::
                    557: * Splitting fields::
                    558: \E
1.1       noro      559: @end menu
                    560:
1.2       noro      561: \JP @node GCD,,, $BBe?tBN>e$G$N(B 1 $BJQ?tB?9`<0$N1i;;(B
                    562: \EG @node GCD,,, Operations for uni-variate polynomials over an algebraic number field
1.1       noro      563: @subsection GCD
                    564:
                    565: @noindent
1.2       noro      566: \BJP
                    567: $BBe?tBN>e$G$N(B GCD $B$O(B @code{cr_gcda()} $B$K$h$j7W;;$5$l$k(B.
1.1       noro      568: $B$3$NH!?t$O%b%8%e%i1i;;$*$h$SCf9q>jM>DjM}$K$h$jBe?tBN>e$N(B GCD $B$r(B
                    569: $B7W;;$9$k$b$N$G(B, $BC`<!3HBg$KBP$7$F$bM-8z$G$"$k(B.
1.2       noro      570: \E
                    571: \BEG
                    572: Greatest common divisors (GCD) over algebraic number fields are computed
                    573: by @code{cr_gcda()} function. This function computes GCD by using modular
                    574: computation and Chinese remainder theorem and it works for the case
                    575: where the ground field is a multiple extension.
                    576: \E
1.1       noro      577:
                    578: @example
                    579: [63] A=newalg(t^9-15*t^6-87*t^3-125);
                    580: (#0)
                    581: [64] B=newalg(75*s^2+(10*A^7-175*A^4-470*A)*s+3*A^8-45*A^5-261*A^2);
                    582: (#1)
1.7       noro      583: [65] P1=75*x^2+(150*B+10*A^7-175*A^4-395*A)*x
                    584: +(75*B^2+(10*A^7-175*A^4-395*A)*B+13*A^8-220*A^5-581*A^2)$
1.1       noro      585: [66] P2=x^2+A*x+A^2$
1.3       noro      586: [67] cr_gcda(P1,P2);
1.1       noro      587: 27*x+((#0^6-19*#0^3-65)*#1-#0^7+19*#0^4+38*#0)
                    588: @end example
                    589:
1.2       noro      590: \BJP
1.1       noro      591: @node $BL5J?J}J,2r(B $B0x?tJ,2r(B,,, $BBe?tBN>e$G$N(B 1 $BJQ?tB?9`<0$N1i;;(B
                    592: @subsection $BL5J?J}J,2r(B, $B0x?tJ,2r(B
1.2       noro      593: \E
                    594: \BEG
                    595: @node Square-free factorization and Factorization,,, Operations for uni-variate polynomials over an algebraic number field
                    596: @subsection Square-free factorization and Factorization
                    597: \E
1.1       noro      598:
                    599: @noindent
1.2       noro      600: \BJP
1.1       noro      601: $BL5J?J}J,2r$O(B, $BB?9`<0$H$=$NHyJ,$H$N(B GCD $B$N7W;;$+$i;O$^$k$b$C$H$b0lHLE*$J(B
                    602: $B%"%k%4%j%:%`$r:NMQ$7$F$$$k(B. $BH!?t$O(B @code{asq()} $B$G$"$k(B.
1.2       noro      603: \E
                    604: \BEG
                    605: For square-free factorization (of uni-variate polynomials over algebraic
                    606: number fields), we employ the most fundamental algorithm which begins
                    607: first to compute GCD of a polynomial and its derivative.
                    608: The function to do this factorization is @code{asq()}.
                    609: \E
1.1       noro      610:
                    611: @example
                    612: [116] A=newalg(x^2+x+1);
                    613: (#4)
                    614: [117] T=simpalg((x+A+1)*(x^2-2*A-3)^2*(x^3-x-A)^2);
1.7       noro      615: x^11+(#4+1)*x^10+(-4*#4-8)*x^9+(-10*#4-4)*x^8+(16*#4+20)*x^7
                    616: +(24*#4-6)*x^6+(-29*#4-31)*x^5+(-15*#4+28)*x^4+(38*#4+29)*x^3
                    617: +(#4-23)*x^2+(-21*#4-7)*x+(3*#4+8)
1.1       noro      618: [118] asq(T);
                    619: [[x^5+(-2*#4-4)*x^3+(-#4)*x^2+(2*#4+3)*x+(#4-2),2],[x+(#4+1),1]]
                    620: @end example
                    621:
                    622: @noindent
1.2       noro      623: \BJP
1.1       noro      624: $B7k2L$ODL>o$HF1MM$K(B, [@b{$B0x;R(B}, @b{$B=EJ#EY(B}] $B$N%j%9%H$H$J$k$,(B, $BA4$F$N0x;R(B
                    625: $B$N@Q$O(B, $B$b$H$NB?9`<0$HDj?tG\$N:9$O$"$jF@$k(B. $B$3$l$O(B, $B0x;R$r@0?t78?t$K$7(B
                    626: $B$F8+$d$9$/$9$k$?$a$G(B, $B0x?tJ,2r$G$bF1MM$G$"$k(B.
1.2       noro      627: \E
                    628: \BEG
                    629: Like factorization over the rational number field,
                    630: the result is presented,
                    631: commonly to both square-free factorization and factorization,
                    632: as a list whose elements are pairs (list of two elements) in the form
                    633:  [@b{factor}, @b{multiplicity}]
                    634: without the constant multiple part.
                    635:
                    636: Here, it should be noticed that the products of all factors of the
                    637: result may DIFFER from the input polynomial by a constant.
                    638: The reason is that the factors are normalized so that they have
                    639: integral leading coefficients for the sake of readability.
                    640:
                    641: This incongruity may happen to square-free factorization and
                    642: factorization commonly.
                    643: \E
1.1       noro      644:
                    645: @noindent
1.2       noro      646: \BJP
1.1       noro      647: $BBe?tBN>e$G$N0x?tJ,2r$O(B, Trager $B$K$h$k%N%k%`K!$r2~NI$7$?$b$N$G(B, $BFC$K(B
                    648: $B$"$kB?9`<0$KBP$7(B, $B$=$N:,$rE:2C$7$?BN>e$G$=$NB?9`<0<+?H$r0x?tJ,2r$9$k(B
                    649: $B>l9g$KFC$KM-8z$G$"$k(B.
1.2       noro      650: \E
                    651: \BEG
                    652: The algorithm employed for factorization over algebraic number fields
                    653: is an improvement of the norm method by Trager.
                    654: It is especially very effective to factorize a polynomial over a field
                    655: obtained by adjoining some of its @b{root}'s to the base field.
                    656: \E
1.1       noro      657:
                    658: @example
                    659: [119] af(T,[A]);
                    660: [[x^3-x+(-#4),2],[x^2+(-2*#4-3),2],[x+(#4+1),1]]
                    661: @end example
                    662:
                    663: @noindent
1.2       noro      664: \BJP
1.1       noro      665: $B0z?t$O(B 2 $B$D$G(B, $BBh(B 2 $B0z?t$O(B, @code{root} $B$N%j%9%H$G$"$k(B. $B0x?tJ,2r$O(B
                    666: $BM-M}?tBN$K(B, $B$=$l$i$N(B @code{root} $B$rE:2C$7$?BN>e$G9T$o$l$k(B.
                    667: @code{root} $B$N=g=x$K$O@)8B$,$"$k(B. $B$9$J$o$A(B, $B8e$GDj5A$5$l$?$b$N$[$I(B
                    668: $BA0$NJ}$K$3$J$1$l$P(B
                    669: $B$J$i$J$$(B. $BJB$Y49$($O(B, $B<+F0E*$K$O9T$o$l$J$$(B. $B%f!<%6$N@UG$$H$J$k(B.
1.2       noro      670: \E
                    671: \BEG
                    672: The function takes two arguments: The second argument is a list of
                    673: @b{root}'s.  Factorization is performed over a field obtained by
                    674: adjoining the @b{root}'s to the rational number field.
                    675: It is important to keep in mind that the ordering of the @b{root}'s
                    676: must obey a restriction: Last defined should come first.
                    677: The automatic re-ordering is not done.
                    678: It should be done by yourself.
                    679: \E
1.1       noro      680:
                    681: @noindent
1.2       noro      682: \BJP
1.1       noro      683: $B%N%k%`$rMQ$$$?0x?tJ,2r$K$*$$$F$O(B, $B%N%k%`$N7W;;$H@0?t78?t(B 1 $BJQ?tB?9`<0$N(B
                    684: $B0x?tJ,2r$N8zN($,(B, $BA4BN$N8zN($r:81&$9$k(B. $B$3$N$&$A(B, $BFC$K9b<!$NB?9`<0(B
                    685: $B$N>l9g$K8e<T$K$*$$$FAH9g$;GzH/$K$h$j7W;;ITG=$K$J$k>l9g$,$7$P$7$P@8$:$k(B.
1.2       noro      686: \E
                    687: \BEG
                    688: The efficiency of factorization via norm depends on the efficiency
                    689: of the norm computation and univariate factorization over the rationals.
                    690: Especially the latter often causes combinatorial explosion and the
                    691: computation will stick in such a case.
                    692: \E
1.1       noro      693:
                    694: @example
                    695: [120] B=newalg(x^2-2*A-3);
                    696: (#5)
                    697: [121] af(T,[B,A]);
                    698: [[x+(#5),2],[x^3-x+(-#4),2],[x+(-#5),2],[x+(#4+1),1]]
                    699: @end example
                    700:
1.2       noro      701: \BJP
1.1       noro      702: @node $B:G>.J,2rBN(B,,, $BBe?tBN>e$G$N(B 1 $BJQ?tB?9`<0$N1i;;(B
                    703: @subsection $B:G>.J,2rBN(B
1.2       noro      704: \E
                    705: \BEG
                    706: @node Splitting fields,,, Operations for uni-variate polynomials over an algebraic number field
                    707: @subsection Splitting fields
                    708: \E
1.1       noro      709:
                    710: @noindent
1.2       noro      711: \BJP
1.1       noro      712: $B$d$dFC<l$J1i;;$G$O$"$k$,(B, $BA0@a$N0x?tJ,2r$rH?I|E,MQ$9$k$3$H$K$h$j(B,
                    713: $BB?9`<0$N:G>.J,2rBN$r5a$a$k$3$H$,$G$-$k(B. $BH!?t$O(B @code{sp()} $B$G$"$k(B.
1.2       noro      714: \E
                    715: \BEG
                    716: This operation may be somewhat unusual and for specific interest.
                    717: (Galois Group for example.)  Procedurally, however, it is easy to
                    718: obtain the splitting field of a polynomial by repeated application
                    719: of algebraic factorization described in the previous section.
                    720: The function is @code{sp()}.
                    721: \E
1.1       noro      722:
                    723: @example
                    724: [103] sp(x^5-2);
1.7       noro      725: [[x+(-#1),2*x+(#0^3*#1^3+#0^4*#1^2+2*#1+2*#0),2*x+(-#0^4*#1^2),
                    726: 2*x+(-#0^3*#1^3),x+(-#0)],
                    727: [[(#1),t#1^4+t#0*t#1^3+t#0^2*t#1^2+t#0^3*t#1+t#0^4],[(#0),t#0^5-2]]]
1.1       noro      728: @end example
                    729:
                    730: @noindent
1.2       noro      731: \BJP
1.1       noro      732: @code{sp()} $B$O(B 1 $B0z?t$G(B, $B7k2L$O(B @code{[1 $B<!0x;R$N%j%9%H(B, [[root,
                    733: algptorat($BDj5AB?9`<0(B)] $B$N%j%9%H(B]} $B$J$k%j%9%H$G$"$k(B.
                    734: $BBh(B 2 $BMWAG$N(B @code{[root,algptorat($BDj5AB?9`<0(B)]} $B$N%j%9%H$O(B,
                    735: $B1&$+$i=g$K(B, $B:G>.J,2rBN$,F@$i$l$k$^$GE:2C$7$F$$$C$?(B @code{root} $B$r<($9(B.
                    736: $B$=$NDj5AB?9`<0$O(B, $B$=$ND>A0$^$G$N(B @code{root} $B$rE:2C$7$?BN>e$G4{Ls$G$"$k$3$H(B
                    737: $B$,J]>Z$5$l$F$$$k(B.
1.2       noro      738: \E
                    739: \BEG
                    740: Function @code{sp()} takes only one argument.
                    741: The result is a list of two element: The first element is
                    742: a list of linear factors, and the second one is a list whose elements
                    743: are pairs (list of two elements) in the form
                    744: @code{[@b{root}, algptorat(@b{defining polynomial})]}.
                    745: The second element, a list of pairs of form
                    746: @code{[@b{root},algptorat(@b{defining polynomial})]},
                    747: corresponds to the @b{root}'s which are adjoined to eventually obtain
                    748: the splitting field.  They are listed in the reverse order of adjoining.
                    749: Each of the defining polynomials in the list is, of course,
                    750: guaranteed to be irreducible over the field obtained by adjoining all
                    751: @b{root}'s defined before it.
                    752: \E
1.1       noro      753:
                    754: @noindent
1.2       noro      755: \BJP
1.1       noro      756: $B7k2L$NBh(B 1 $BMWAG$G$"$k(B 1 $B<!0x;R$N%j%9%H$O(B, $BBh(B 2 $BMWAG$N(B @code{root} $B$rA4$F(B
                    757: $BE:2C$7$?BN>e$G$N(B, @code{sp()} $B$N0z?t$NB?9`<0$NA4$F$N0x;R$rI=$9(B. $B$=$NBN$O(B
                    758: $B:G>.J,2rBN$H$J$C$F$$$k$N$G(B, $B0x;R$OA4$F(B 1 $B<!$H$J$k$o$1$G$"$k(B. @code{af()}
                    759: $B$HF1MM(B, $BA4$F$N0x;R$N@Q$O(B, $B$b$H$NB?9`<0$HDj?tG\$N:9$O$"$jF@$k(B.
1.2       noro      760: \E
                    761: \BEG
                    762: The first element of the result, a list of linear factors, contains
                    763: all irreducible factors of the input polynomial over the field
                    764: obtained by adjoining all @b{root}'s in the second element of the result.
                    765: Because such field is the splitting field of the input polynomial,
                    766: factors in the result are all linear as the consequence.
                    767:
                    768: Similarly to function @code{af()}, the product of all resulting factors
                    769: may yield a polynomial which differs by a constant.
                    770: \E
1.1       noro      771:
1.2       noro      772: \BJP
1.1       noro      773: @node $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B,,, $BBe?tE*?t$K4X$9$k1i;;(B
                    774: @section $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
1.2       noro      775: \E
                    776: \BEG
                    777: @node Summary of functions for algebraic numbers,,, Algebraic numbers
                    778: @section Summary of functions for algebraic numbers
                    779: \E
1.1       noro      780: @menu
                    781: * newalg::
                    782: * defpoly::
                    783: * alg::
                    784: * algv::
                    785: * simpalg::
                    786: * algptorat::
                    787: * rattoalgp::
1.2       noro      788: * cr_gcda::
1.1       noro      789: * sp_norm::
1.4       noro      790: * asq af af_noalg::
                    791: * sp sp_noalg::
1.8     ! noro      792: * set_field::
        !           793: * algtodalg dalgtoalg dptodalg dalgtodp::
1.1       noro      794: @end menu
                    795:
1.2       noro      796: \JP @node newalg,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                    797: \EG @node newalg,,, Summary of functions for algebraic numbers
1.1       noro      798: @subsection @code{newalg}
                    799: @findex newalg
                    800:
                    801: @table @t
                    802: @item newalg(@var{defpoly})
1.2       noro      803: \JP :: @code{root} $B$r@8@.$9$k(B.
                    804: \EG :: Creates a new @b{root}.
1.1       noro      805: @end table
                    806:
                    807: @table @var
                    808: @item return
1.2       noro      809: \JP $BBe?tE*?t(B (@code{root})
                    810: \EG algebraic number (@b{root})
1.1       noro      811: @item defpoly
1.2       noro      812: \JP $BB?9`<0(B
                    813: \EG polynomial
1.1       noro      814: @end table
                    815:
                    816: @itemize @bullet
                    817: @item
1.2       noro      818: \JP @var{defpoly} $B$rDj5AB?9`<0$H$9$kBe?tE*?t(B (@code{root}) $B$r@8@.$9$k(B.
                    819: \BEG
                    820: Creates a new @b{root} (algebraic number) with its defining
                    821: polynomial @var{defpoly}.
                    822: \E
                    823: @item
                    824: \JP @var{defpoly} $B$KBP$9$k@)8B$K4X$7$F$O(B, @xref{$BBe?tE*?t$NI=8=(B}.
                    825: \BEG
                    826: For constraints on @var{defpoly},
                    827: @xref{Representation of algebraic numbers}.
                    828: \E
1.1       noro      829: @end itemize
                    830:
                    831: @example
                    832: [0] A0=newalg(x^2-2);
                    833: (#0)
                    834: @end example
                    835:
                    836: @table @t
1.2       noro      837: \JP @item $B;2>H(B
                    838: \EG @item Reference
1.1       noro      839: @fref{defpoly}
                    840: @end table
                    841:
1.2       noro      842: \JP @node defpoly,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                    843: \EG @node defpoly,,, Summary of functions for algebraic numbers
1.1       noro      844: @subsection @code{defpoly}
                    845: @findex defpoly
                    846:
                    847: @table @t
                    848: @item defpoly(@var{alg})
1.2       noro      849: \JP :: @code{root} $B$NDj5AB?9`<0$rJV$9(B.
                    850: \EG :: Returns the defining polynomial of @b{root} @var{alg}.
1.1       noro      851: @end table
                    852:
                    853: @table @var
                    854: @item return
1.2       noro      855: \JP $BB?9`<0(B
                    856: \EG polynomial
1.1       noro      857: @item alg
1.2       noro      858: \JP $BBe?tE*?t(B (@code{root})
                    859: \EG algebraic number (@code{root})
1.1       noro      860: @end table
                    861:
                    862: @itemize @bullet
                    863: @item
1.2       noro      864: \JP @code{root} @var{alg} $B$NDj5AB?9`<0$rJV$9(B.
                    865: \EG Returns the defining polynomial of @b{root} @var{alg}.
1.1       noro      866: @item
1.2       noro      867: \BJP
1.1       noro      868: @code{root} $B$r(B @code{#@var{n}} $B$H$9$l$P(B, $BDj5AB?9`<0$N<gJQ?t$O(B
                    869: @code{t#@var{n}} $B$H$J$k(B.
1.2       noro      870: \E
                    871: \BEG
                    872: If the argument @var{alg}, a @b{root}, is @code{#@var{n}},
                    873: then the main variable of its defining polynomial is
                    874: @code{t#@var{n}}.
                    875: \E
1.1       noro      876: @end itemize
                    877:
                    878: @example
                    879: [1] defpoly(A0);
                    880: t#0^2-2
                    881: @end example
                    882:
                    883: @table @t
1.2       noro      884: \JP @item $B;2>H(B
                    885: \EG @item Reference
1.1       noro      886: @fref{newalg}, @fref{alg}, @fref{algv}
                    887: @end table
                    888:
1.2       noro      889: \JP @node alg,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                    890: \EG @node alg,,, Summary of functions for algebraic numbers
1.1       noro      891: @subsection @code{alg}
                    892: @findex alg
                    893:
                    894: @table @t
                    895: @item alg(@var{i})
1.2       noro      896: \JP :: $B%$%s%G%C%/%9$KBP1~$9$k(B @code{root} $B$rJV$9(B.
                    897: \EG :: Returns a @b{root} which correspond to the index @var{i}.
1.1       noro      898: @end table
                    899:
                    900: @table @var
                    901: @item return
1.2       noro      902: \JP $BBe?tE*?t(B (@code{root})
                    903: \EG algebraic number (@code{root})
1.1       noro      904: @item i
1.2       noro      905: \JP $B@0?t(B
                    906: \EG integer
1.1       noro      907: @end table
                    908:
                    909: @itemize @bullet
                    910: @item
1.2       noro      911: \JP @code{root} @code{#@var{i}} $B$rJV$9(B.
                    912: \EG Returns @code{#@var{i}}, a @b{root}.
1.1       noro      913: @item
1.2       noro      914: \BJP
1.1       noro      915: @code{#@var{i}} $B$O%f!<%6$,D>@\F~NO$G$-$J$$$?$a(B, @code{alg(@var{i})} $B$H(B
                    916: $B$$$&7A$GF~NO$9$k(B.
1.2       noro      917: \E
                    918: \BEG
                    919: Because @code{#@var{i}} cannot be input directly,
                    920: this function provides an alternative way: input @code{alg(@var{i})}.
                    921: \E
1.1       noro      922: @end itemize
                    923:
                    924: @example
                    925: [2] x+#0;
                    926: syntax error
                    927: 0
                    928: [3] alg(0);
                    929: (#0)
                    930: @end example
                    931:
                    932: @table @t
1.2       noro      933: \JP @item $B;2>H(B
                    934: \EG @item Reference
1.1       noro      935: @fref{newalg}, @fref{algv}
                    936: @end table
                    937:
1.2       noro      938: \JP @node algv,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                    939: \EG @node algv,,, Summary of functions for algebraic numbers
1.1       noro      940: @subsection @code{algv}
                    941: @findex algv
                    942:
                    943: @table @t
                    944: @item algv(@var{i})
1.2       noro      945: \JP :: @code{alg(@var{i})} $B$KBP1~$9$kITDj85$rJV$9(B.
                    946: \EG :: Returns the associated indeterminate with @code{alg(@var{i})}.
1.1       noro      947: @end table
                    948:
                    949: @table @var
                    950: @item return
1.2       noro      951: \JP $BB?9`<0(B
                    952: \EG polynomial
1.1       noro      953: @item i
1.2       noro      954: \JP $B@0?t(B
                    955: \EG integer
1.1       noro      956: @end table
                    957:
                    958: @itemize @bullet
                    959: @item
1.2       noro      960: \JP $BB?9`<0(B @code{t#@var{i}} $B$rJV$9(B.
                    961: \EG Returns an indeterminate @code{t#@var{i}}
1.1       noro      962: @item
1.2       noro      963: \BJP
1.1       noro      964: @code{t#@var{i}} $B$O%f!<%6$,D>@\F~NO$G$-$J$$$?$a(B, @code{algv(@var{i})} $B$H(B
                    965: $B$$$&7A$GF~NO$9$k(B.
1.2       noro      966: \E
                    967: \BEG
                    968: Since indeterminate @code{t#@var{i}} cannot be input directly,
                    969: it is input by @code{algv(@var{i})}.
                    970: \E
1.1       noro      971: @end itemize
                    972:
                    973: @example
                    974: [4] var(defpoly(A0));
                    975: t#0
                    976: [5] t#0;
                    977: syntax error
                    978: 0
                    979: [6] algv(0);
                    980: t#0
                    981: @end example
                    982:
                    983: @table @t
1.2       noro      984: \JP @item $B;2>H(B
                    985: \EG @item Reference
1.1       noro      986: @fref{newalg}, @fref{defpoly}, @fref{alg}
                    987: @end table
                    988:
1.2       noro      989: \JP @node simpalg,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                    990: \EG @node simpalg,,, Summary of functions for algebraic numbers
1.1       noro      991: @subsection @code{simpalg}
                    992: @findex simpalg
                    993:
                    994: @table @t
                    995: @item simpalg(@var{rat})
1.2       noro      996: \JP :: $BM-M}<0$K4^$^$l$kBe?tE*?t$r4JC12=$9$k(B.
                    997: \EG :: Simplifies algebraic numbers in a rational expression.
1.1       noro      998: @end table
                    999:
                   1000: @table @var
                   1001: @item return
1.2       noro     1002: \JP $BM-M}<0(B
                   1003: \EG rational expression
1.1       noro     1004: @item rat
1.2       noro     1005: \JP $BM-M}<0(B
                   1006: \EG rational expression
1.1       noro     1007: @end table
                   1008:
                   1009: @itemize @bullet
                   1010: @item
1.2       noro     1011: \JP @samp{sp} $B$GDj5A$5$l$F$$$k(B.
                   1012: \EG Defined in the file @samp{sp}.
1.1       noro     1013: @item
1.2       noro     1014: \BJP
1.1       noro     1015: $B?t(B, $BB?9`<0(B, $BM-M}<0$K4^$^$l$kBe?tE*?t$r(B, $B4^$^$l$k(B @code{root} $B$NDj5A(B
                   1016: $BB?9`<0$K$h$j4JC12=$9$k(B.
1.2       noro     1017: \E
                   1018: \BEG
                   1019: Simplifies algebraic numbers contained in numbers,
                   1020: polynomials, and rational expressions by the defining
                   1021: polynomials of @b{root}'s contained in them.
                   1022: \E
                   1023: @item
                   1024: \JP $B?t$N>l9g(B, $BJ,Jl$,$"$l$PM-M}2=$5$l(B, $B7k2L$O(B @code{root} $B$NB?9`<0$H$J$k(B.
                   1025: \BEG
                   1026: If the argument is a number having the denominator, it is
                   1027: rationalized and the result is a polynomial in @b{root}'s.
                   1028: \E
                   1029: @item
                   1030: \JP $BB?9`<0$N>l9g(B, $B3F78?t$,4JC12=$5$l$k(B.
                   1031: \EG If the argument is a polynomial, each coefficient is simplified.
                   1032: @item
                   1033: \JP $BM-M}<0$N>l9g(B, $BJ,JlJ,;R$,B?9`<0$H$7$F4JC12=$5$l$k(B.
                   1034: \BEG
                   1035: If the argument is a rational expression, its denominator and
                   1036: numerator are simplified as a polynomial.
                   1037: \E
1.1       noro     1038: @end itemize
                   1039:
                   1040: @example
                   1041: [7] simpalg((1+A0)/(1-A0));
                   1042: simpalg undefined
                   1043: return to toplevel
                   1044: [7] load("sp")$
                   1045: [46] simpalg((1+A0)/(1-A0));
                   1046: (-2*#0-3)
                   1047: [47] simpalg((2-A0)/(2+A0)*x^2-1/(3+A0));
                   1048: (-2*#0+3)*x^2+(1/7*#0-3/7)
                   1049: [48] simpalg((x+1/(A0-1))/(x-1/(A0+1)));
                   1050: (x+(#0+1))/(x+(-#0+1))
                   1051: @end example
                   1052:
1.2       noro     1053: \JP @node algptorat,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                   1054: \EG @node algptorat,,, Summary of functions for algebraic numbers
1.1       noro     1055: @subsection @code{algptorat}
                   1056: @findex algptorat
                   1057:
                   1058: @table @t
                   1059: @item algptorat(@var{poly})
1.2       noro     1060: \JP :: $BB?9`<0$K4^$^$l$k(B @code{root} $B$r(B, $BBP1~$9$kITDj85$KCV$-49$($k(B.
                   1061: \EG :: Substitutes the associated indeterminate for every @b{root}
1.1       noro     1062: @end table
                   1063:
                   1064: @table @var
                   1065: @item return
1.2       noro     1066: \JP $BB?9`<0(B
                   1067: \EG polynomial
1.1       noro     1068: @item poly
1.2       noro     1069: \JP $BB?9`<0(B
                   1070: \EG polynomial
1.1       noro     1071: @end table
                   1072:
                   1073: @itemize @bullet
                   1074: @item
1.2       noro     1075: \JP @samp{sp} $B$GDj5A$5$l$F$$$k(B.
                   1076: \EG Defined in the file @samp{sp}.
1.1       noro     1077: @item
1.2       noro     1078: \BJP
1.1       noro     1079: $BB?9`<0$K4^$^$l$k(B @code{root} @code{#@var{n}} $B$rA4$F(B @code{t#@var{n}} $B$K(B
                   1080: $BCV$-49$($k(B.
1.2       noro     1081: \E
                   1082: \BEG
                   1083: Substitutes the associated indeterminate @code{t#@var{n}}
                   1084: for every @b{root} @code{#@var{n}} in a polynomial.
                   1085: \E
1.1       noro     1086: @end itemize
                   1087:
                   1088: @example
                   1089: [49] algptorat((-2*alg(0)+3)*x^2+(1/7*alg(0)-3/7));
                   1090: (-2*t#0+3)*x^2+1/7*t#0-3/7
                   1091: @end example
                   1092:
                   1093: @table @t
1.2       noro     1094: \JP @item $B;2>H(B
                   1095: \EG @item Reference
1.1       noro     1096: @fref{defpoly}, @fref{algv}
                   1097: @end table
                   1098:
1.2       noro     1099: \JP @node rattoalgp,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                   1100: \EG @node rattoalgp,,, Summary of functions for algebraic numbers
1.1       noro     1101: @subsection @code{rattoalgp}
                   1102: @findex rattoalgp
                   1103:
                   1104: @table @t
                   1105: @item rattoalgp(@var{poly},@var{alglist})
1.2       noro     1106: \BJP
1.1       noro     1107: :: $BB?9`<0$K4^$^$l$k(B @code{root} $B$KBP1~$9$kITDj85$r(B @code{root} $B$K(B
                   1108: $BCV$-49$($k(B.
1.2       noro     1109: \E
                   1110: \BEG
                   1111: :: Substitutes a @b{root} for the associated indeterminate with the
                   1112:  @b{root}.
                   1113: \E
1.1       noro     1114: @end table
                   1115:
                   1116: @table @var
                   1117: @item return
1.2       noro     1118: \JP $BB?9`<0(B
                   1119: \EG polynomial
1.1       noro     1120: @item poly
1.2       noro     1121: \JP $BB?9`<0(B
                   1122: \EG polynomial
1.1       noro     1123: @item alglist
1.2       noro     1124: \JP $B%j%9%H(B
                   1125: \EG list
1.1       noro     1126: @end table
                   1127:
                   1128: @itemize @bullet
                   1129: @item
1.2       noro     1130: \JP @samp{sp} $B$GDj5A$5$l$F$$$k(B.
                   1131: \EG Defined in the file @samp{sp}.
1.1       noro     1132: @item
1.2       noro     1133: \BJP
1.1       noro     1134: $BBh(B 2 $B0z?t$O(B @code{root} $B$N%j%9%H$G$"$k(B. @code{rattoalgp()} $B$O(B, $B$3$N(B @code{root}
                   1135: $B$KBP1~$9$kITDj85$r(B, $B$=$l$>$l(B @code{root} $B$KCV$-49$($k(B.
1.2       noro     1136: \E
                   1137: \BEG
                   1138: The second argument is a list of @b{root}'s. Function @code{rattoalgp()}
                   1139: substitutes a @b{root} for the associated indeterminate of the @b{root}.
                   1140: \E
1.1       noro     1141: @end itemize
                   1142:
                   1143: @example
                   1144: [51] rattoalgp((-2*algv(0)+3)*x^2+(1/7*algv(0)-3/7),[alg(0)]);
                   1145: (-2*#0+3)*x^2+(1/7*#0-3/7)
                   1146: @end example
                   1147:
                   1148: @table @t
1.2       noro     1149: \JP @item $B;2>H(B
                   1150: \EG @item Reference
1.1       noro     1151: @fref{alg}, @fref{algv}
                   1152: @end table
                   1153:
1.2       noro     1154: \JP @node cr_gcda,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                   1155: \EG @node cr_gcda,,, Summary of functions for algebraic numbers
                   1156: @subsection @code{cr_gcda}
                   1157: @findex cr_gcda
1.1       noro     1158:
                   1159: @table @t
1.3       noro     1160: @item cr_gcda(@var{poly1},@var{poly2})
1.2       noro     1161: \JP :: $BBe?tBN>e$N(B 1 $BJQ?tB?9`<0$N(B GCD
                   1162: \EG :: GCD of two uni-variate polynomials over an algebraic number field.
1.1       noro     1163: @end table
                   1164:
                   1165: @table @var
                   1166: @item return
1.2       noro     1167: \JP $BB?9`<0(B
                   1168: \EG polynomial
1.6       noro     1169: @item poly1  poly2
1.2       noro     1170: \JP $BB?9`<0(B
                   1171: \EG polynomial
1.1       noro     1172: @end table
                   1173:
                   1174: @itemize @bullet
                   1175: @item
1.2       noro     1176: \JP @samp{sp} $B$GDj5A$5$l$F$$$k(B.
                   1177: \EG Defined in the file @samp{sp}.
1.1       noro     1178: @item
1.2       noro     1179: \JP 2 $B$D$N(B 1 $BJQ?tB?9`<0$N(B GCD $B$r5a$a$k(B.
                   1180: \EG Finds the GCD of two uni-variate polynomials.
1.1       noro     1181: @end itemize
                   1182:
                   1183: @example
                   1184: [76] X=x^6+3*x^5+6*x^4+x^3-3*x^2+12*x+16$
                   1185: [77] Y=x^6+6*x^5+24*x^4+8*x^3-48*x^2+384*x+1024$
                   1186: [78] A=newalg(X);
                   1187: (#0)
1.3       noro     1188: [79] cr_gcda(X,subst(Y,x,x+A));
1.1       noro     1189: x+(-#0)
                   1190: @end example
                   1191:
                   1192: @table @t
1.2       noro     1193: \JP @item $B;2>H(B
                   1194: \EG @item Reference
1.4       noro     1195: @fref{gr hgr gr_mod}, @fref{asq af af_noalg}
1.1       noro     1196: @end table
                   1197:
1.2       noro     1198: \JP @node sp_norm,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                   1199: \EG @node sp_norm,,, Summary of functions for algebraic numbers
1.1       noro     1200: @subsection @code{sp_norm}
                   1201: @findex sp_norm
                   1202:
                   1203: @table @t
                   1204: @item sp_norm(@var{alg},@var{var},@var{poly},@var{alglist})
1.2       noro     1205: \JP :: $BBe?tBN>e$G$N%N%k%`$N7W;;(B
                   1206: \EG :: Norm computation over an algebraic number field.
1.1       noro     1207: @end table
                   1208:
                   1209: @table @var
                   1210: @item return
1.2       noro     1211: \JP $BB?9`<0(B
                   1212: \EG polynomial
1.1       noro     1213: @item var
1.2       noro     1214: \JP @var{poly} $B$N<gJQ?t(B
                   1215: \EG The main variable of @var{poly}
1.1       noro     1216: @item poly
1.2       noro     1217: \JP 1 $BJQ?tB?9`<0(B
                   1218: \EG univariate polynomial
1.1       noro     1219: @item alg
                   1220: @code{root}
                   1221: @item alglist
1.2       noro     1222: \JP @code{root} $B$N%j%9%H(B
                   1223: \EG @code{root} list
1.1       noro     1224: @end table
                   1225:
                   1226: @itemize @bullet
                   1227: @item
1.2       noro     1228: \JP @samp{sp} $B$GDj5A$5$l$F$$$k(B.
                   1229: \EG Defined in the file @samp{sp}.
1.1       noro     1230: @item
1.2       noro     1231: \BJP
1.1       noro     1232: @var{poly} $B$N(B, @var{alg} $B$K4X$9$k%N%k%`$r$H$k(B. $B$9$J$o$A(B,
                   1233: @b{K} = @b{Q}(@var{alglist} \ @{@var{alg}@}) $B$H$9$k$H$-(B,
                   1234: @var{poly} $B$K8=$l$k(B @var{alg} $B$r(B, @var{alg} $B$N(B @b{K} $B>e$N6&Lr$KCV$-49$($?$b$N(B
                   1235: $BA4$F$N@Q$rJV$9(B.
1.2       noro     1236: \E
                   1237: \BEG
                   1238: Computes the norm of @var{poly} with respect to @var{alg}.
                   1239: Namely, if we write
                   1240: @b{K} = @b{Q}(@var{alglist} \ @{@var{alg}@}),
                   1241: The function returns a product of all conjugates of @var{poly},
                   1242: where the conjugate of polynomial @var{poly} is a polynomial
                   1243: in which the algebraic number @var{alg} is substituted
                   1244: for its conjugate over @b{K}.
                   1245: \E
1.1       noro     1246: @item
1.2       noro     1247: \JP $B7k2L$O(B @b{K} $B>e$NB?9`<0$H$J$k(B.
                   1248: \EG The result is a polynomial over @b{K}.
1.1       noro     1249: @item
1.2       noro     1250: \BJP
1.1       noro     1251: $B<B:]$K$OF~NO$K$h$j>l9g$o$1$,9T$o$l(B, $B=*7k<0$ND>@\7W;;$dCf9q>jM>DjM}$K(B
                   1252: $B$h$j7W;;$5$l$k$,(B, $B:GE,$JA*Br$,9T$o$l$F$$$k$H$O8B$i$J$$(B.
                   1253: $BBg0hJQ?t(B @code{USE_RES} $B$r(B 1 $B$K@_Dj$9$k$3$H$K$h$j(B, $B>o$K=*7k<0$K$h$j7W;;(B
                   1254: $B$5$;$k$3$H$,$G$-$k(B.
1.2       noro     1255: \E
                   1256: \BEG
                   1257: The method of computation depends on the input. Currently
                   1258: direct computation of resultant and Chinese remainder theorem
                   1259: are used but the selection is not necessarily optimal.
                   1260: By setting the global variable @code{USE_RES} to 1, the builtin function
                   1261: @code{res()} is always used.
                   1262: \E
1.1       noro     1263: @end itemize
                   1264:
                   1265: @example
                   1266: [0] load("sp")$
                   1267: [39] A0=newalg(x^2+1)$
                   1268: [40] A1=newalg(x^2+A0)$
                   1269: [41] sp_norm(A1,x,x^3+A0*x+A1,[A1,A0]);
                   1270: x^6+(2*#0)*x^4+(#0^2)*x^2+(#0)
                   1271: [42] sp_norm(A0,x,@@@@,[A0]);
                   1272: x^12+2*x^8+5*x^4+1
                   1273: @end example
                   1274:
                   1275: @table @t
1.2       noro     1276: \JP @item $B;2>H(B
                   1277: \EG @item Reference
1.4       noro     1278: @fref{res}, @fref{asq af af_noalg}
1.1       noro     1279: @end table
                   1280:
1.4       noro     1281: \JP @node asq af af_noalg,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                   1282: \EG @node asq af af_noalg,,, Summary of functions for algebraic numbers
                   1283: @subsection @code{asq}, @code{af}, @code{af_noalg}
1.1       noro     1284: @findex asq
                   1285: @findex af
1.4       noro     1286: @findex af_noalg
1.1       noro     1287:
                   1288: @table @t
                   1289: @item asq(@var{poly})
1.2       noro     1290: \JP :: $BBe?tBN>e$N(B 1 $BJQ?tB?9`<0$NL5J?J}J,2r(B
                   1291: \BEG
                   1292: :: Square-free factorization of polynomial @var{poly} over an
                   1293: algebraic number field.
                   1294: \E
1.1       noro     1295: @item af(@var{poly},@var{alglist})
1.4       noro     1296: @itemx af_noalg(@var{poly},@var{defpolylist})
1.2       noro     1297: \JP :: $BBe?tBN>e$N(B 1 $BJQ?tB?9`<0$N0x?tJ,2r(B
                   1298: \BEG
                   1299: :: Factorization of polynomial @var{poly} over an
                   1300: algebraic number field.
                   1301: \E
1.1       noro     1302: @end table
                   1303:
                   1304: @table @var
                   1305: @item return
1.2       noro     1306: \JP $B%j%9%H(B
                   1307: \EG list
1.1       noro     1308: @item poly
1.2       noro     1309: \JP $BB?9`<0(B
                   1310: \EG polynomial
1.1       noro     1311: @item alglist
1.2       noro     1312: \JP @code{root} $B$N%j%9%H(B
                   1313: \EG @code{root} list
1.4       noro     1314: @item defpolylist
                   1315: \JP @code{root} $B$rI=$9ITDj85$HDj5AB?9`<0$N%Z%"$N%j%9%H(B
                   1316: \EG @code{root} list of pairs of an indeterminate and a polynomial
1.1       noro     1317: @end table
                   1318:
                   1319: @itemize @bullet
                   1320: @item
1.2       noro     1321: \JP $B$$$:$l$b(B @samp{sp} $B$GDj5A$5$l$F$$$k(B.
                   1322: \EG Both defined in the file @samp{sp}.
1.1       noro     1323: @item
1.2       noro     1324: \BJP
1.1       noro     1325: @code{root} $B$r4^$^$J$$>l9g$O@0?t>e$NH!?t$,8F$S=P$5$l9bB.$G$"$k$,(B,
1.2       noro     1326: @code{root} $B$r4^$`>l9g$K$O(B, @code{cr_gcda()} $B$,5/F0$5$l$k$?$a$7$P$7$P(B
1.1       noro     1327: $B;~4V$,$+$+$k(B.
1.2       noro     1328: \E
                   1329: \BEG
                   1330: If the inputs contain no @b{root}'s, these functions run fast
                   1331: since they invoke functions over the integers.
                   1332: In contrast to this, if the inputs contain @b{root}'s, they sometimes
                   1333: take a long time, since @code{cr_gcda()} is invoked.
                   1334: \E
1.1       noro     1335: @item
1.2       noro     1336: \BJP
1.1       noro     1337: @code{af()} $B$O(B, $B4pACBN$N;XDj(B, $B$9$J$o$ABh(B 2 $B0z?t$N(B, @code{root} $B$N%j%9%H(B
                   1338: $B$N;XDj$,I,MW$G$"$k(B.
1.2       noro     1339: \E
                   1340: \BEG
                   1341: Function @code{af()} requires the specification of base field,
                   1342: i.e., list of @b{root}'s for its second argument.
                   1343: \E
1.1       noro     1344: @item
1.2       noro     1345: \BJP
1.1       noro     1346: @code{alglist} $B$G;XDj$5$l$k(B @code{root} $B$O(B, $B8e$GDj5A$5$l$?$b$N$[$IA0$N(B
                   1347: $BJ}$KMh$J$1$l$P$J$i$J$$(B.
1.2       noro     1348: \E
                   1349: \BEG
                   1350: In the second argument @code{alglist}, @b{root} defined last must come
                   1351: first.
                   1352: \E
                   1353: @item
1.4       noro     1354: \BJP
1.5       noro     1355: @code{af(F,AL)} $B$K$*$$$F(B, @code{AL} $B$OBe?tE*?t$N%j%9%H$G$"$j(B, $BM-M}?tBN$N(B
                   1356: $BBe?t3HBg$rI=$9(B. @code{AL=[An,...,A1]} $B$H=q$/$H$-(B, $B3F(B @code{Ak} $B$O(B, $B$=$l$h$j(B
                   1357: $B1&$K$"$kBe?tE*?t$r78?t$H$7$?(B, $B%b%K%C%/$JDj5AB?9`<0$GDj5A$5$l$F$$$J$1$l$P(B
                   1358: $B$J$i$J$$(B.
                   1359: \E
                   1360: \BEG
                   1361: In @code{af(F,AL)}, @code{AL} denotes a list of @code{roots} and it
                   1362: represents an algebraic number field. In @code{AL=[An,...,A1]} each
                   1363: @code{Ak} should be defined as a root of a defining polynomial
                   1364: whose coefficients are in @code{Q(A(k+1),...,An)}.
                   1365: \E
                   1366:
                   1367: @example
                   1368: [1] A1 = newalg(x^2+1);
                   1369: [2] A2 = newalg(x^2+A1);
                   1370: [3] A3 = newalg(x^2+A2*x+A1);
                   1371: [4] af(x^2+A2*x+A1,[A2,A1]);
                   1372: [[x^2+(#1)*x+(#0),1]]
                   1373: @end example
                   1374:
                   1375: \BJP
                   1376: @code{af_noalg} $B$G$O(B, @var{poly} $B$K4^$^$l$kBe?tE*?t(B @var{ai} $B$rITDj85(B @var{vi}
1.6       noro     1377: $B$GCV$-49$($k(B. @code{defpolylist} $B$O(B, [[vn,dn(vn,...,v1)],...,[v1,d(v1)]]
                   1378: $B$J$k%j%9%H$G$"$k(B. $B$3$3$G(B @var{di}(vi,...,v1) $B$O(B @var{ai} $B$NDj5AB?9`<0$K$*$$$F(B
1.4       noro     1379: $BBe?tE*?t$rA4$F(B @var{vj} $B$KCV$-49$($?$b$N$G$"$k(B.
                   1380: \E
                   1381: \BEG
                   1382: To call @code{sp_noalg}, one should replace each algebraic number
                   1383: @var{ai} in @var{poly} with an indeterminate @var{vi}. @code{defpolylist}
1.6       noro     1384: is a list [[vn,dn(vn,...,v1)],...,[v1,d(v1)]]. In this expression
                   1385: @var{di}(vi,...,v1) is a defining polynomial of @var{ai} represented
1.4       noro     1386: as a multivariate polynomial.
                   1387: \E
1.5       noro     1388:
                   1389: @example
                   1390: [1] af_noalg(x^2+a2*x+a1,[[a2,a2^2+a1],[a1,a1^2+1]]);
                   1391: [[x^2+a2*x+a1,1]]
                   1392: @end example
                   1393:
1.4       noro     1394: @item
                   1395: \BJP
                   1396: $B7k2L$O(B, $BDL>o$NL5J?J}J,2r(B, $B0x?tJ,2r$HF1MM(B [@b{$B0x;R(B}, @b{$B=EJ#EY(B}]
                   1397: $B$N%j%9%H$G$"$k(B. @code{af_noalg} $B$N>l9g(B, @b{$B0x;R(B} $B$K8=$l$kBe?tE*?t$O(B,
                   1398: @var{defpolylist} $B$K=>$C$FITDj85$KCV$-49$($i$l$k(B.
                   1399: \E
1.2       noro     1400: \BEG
                   1401: The result is a list, as a result of usual factorization, whose elements
1.4       noro     1402: is of the form [@b{factor}, @b{multiplicity}].
                   1403: In the result of @code{af_noalg}, algebraic numbers in @v{factor} are
                   1404: replaced by the indeterminates according to @var{defpolylist}.
1.2       noro     1405: \E
                   1406: @item
                   1407: \JP $B=EJ#EY$r9~$a$?0x;R$NA4$F$N@Q$O(B, @var{poly} $B$HDj?tG\$N0c$$$,$"$jF@$k(B.
                   1408: \BEG
                   1409: The product of all factors with multiplicities counted may differ from
                   1410: the input polynomial by a constant.
                   1411: \E
1.1       noro     1412: @end itemize
                   1413:
                   1414: @example
1.5       noro     1415: [98] A = newalg(t^2-2);
                   1416: (#0)
1.1       noro     1417: [99] asq(-x^4+6*x^3+(2*alg(0)-9)*x^2+(-6*alg(0))*x-2);
                   1418: [[-x^2+3*x+(#0),2]]
                   1419: [100] af(-x^2+3*x+alg(0),[alg(0)]);
                   1420: [[x+(#0-1),1],[-x+(#0+2),1]]
1.5       noro     1421: [101] af_noalg(-x^2+3*x+a,[[a,x^2-2]]);
                   1422: [[x+a-1,1],[-x+a+2,1]]
1.1       noro     1423: @end example
                   1424:
                   1425: @table @t
1.2       noro     1426: \JP @item $B;2>H(B
                   1427: \EG @item Reference
                   1428: @fref{cr_gcda}, @fref{fctr sqfr}
1.1       noro     1429: @end table
                   1430:
1.4       noro     1431: \JP @node sp sp_noalg,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
                   1432: \EG @node sp sp_noalg,,, Summary of functions for algebraic numbers
                   1433: @subsection @code{sp}, @code{sp_noalg}
1.1       noro     1434: @findex sp
                   1435:
                   1436: @table @t
                   1437: @item sp(@var{poly})
1.4       noro     1438: @itemx sp_noalg(@var{poly})
1.2       noro     1439: \JP :: $B:G>.J,2rBN$r5a$a$k(B.
                   1440: \EG :: Finds the splitting field of polynomial @var{poly} and splits.
1.1       noro     1441: @end table
                   1442:
                   1443: @table @var
                   1444: @item return
1.2       noro     1445: \JP $B%j%9%H(B
                   1446: \EG list
1.1       noro     1447: @item poly
1.2       noro     1448: \JP $BB?9`<0(B
                   1449: \EG polynomial
1.1       noro     1450: @end table
                   1451:
                   1452: @itemize @bullet
                   1453: @item
1.2       noro     1454: \JP @samp{sp} $B$GDj5A$5$l$F$$$k(B.
                   1455: \EG Defined in the file @samp{sp}.
1.1       noro     1456: @item
1.2       noro     1457: \BJP
1.1       noro     1458: $BM-M}?t78?t$N(B 1 $BJQ?tB?9`<0(B @var{poly} $B$N:G>.J,2rBN(B, $B$*$h$S$=$NBN>e$G$N(B
                   1459: @var{poly} $B$N(B 1 $B<!0x;R$X$NJ,2r$r5a$a$k(B.
1.2       noro     1460: \E
                   1461: \BEG
                   1462: Finds the splitting field of @var{poly}, an uni-variate polynomial
                   1463: over with rational coefficients, and splits it into its linear factors
                   1464: over the field.
                   1465: \E
1.1       noro     1466: @item
1.2       noro     1467: \BJP
1.1       noro     1468: $B7k2L$O(B, @var{poly} $B$N0x;R$N%j%9%H$H(B, $B:G>.J,2rBN$N(B, $BC`<!3HBg$K$h$kI=8=(B
1.4       noro     1469: $B$+$i$J$k%j%9%H$G$"$k(B. @code{sp_noalg} $B$G$O(B, $BA4$F$NBe?tE*?t$,(B, $BBP1~$9$k(B
                   1470: $BITDj85(B ($BB($A(B @code{#i} $B$KBP$9$k(B @code{t#i}) $B$KCV$-49$($i$l$k(B. $B$3$l$K(B
                   1471: $B$h$j(B, @code{sp_noalg} $B$N=PNO$O(B, $B@0?t78?tB?JQ?tB?9`<0$N%j%9%H$H$J$k(B.
1.2       noro     1472: \E
                   1473: \BEG
                   1474: The result consists of a two element list: The first element is
                   1475: the list of all linear factors of @var{poly}; the second element is
                   1476: a list which represents the successive extension of the field.
1.4       noro     1477: In the result of @code{sp_noalg} all the algebraic numbers are replaced
                   1478: by the special indeterminate associated with it, that is @code{t#i}
                   1479: for @code{#i}. By this operation the result of @code{sp_noalg}
                   1480: is a list containing only integral polynomials.
1.2       noro     1481: \E
1.1       noro     1482: @item
1.2       noro     1483: \BJP
1.1       noro     1484: $B:G>.J,2rBN$O(B, @code{[root,algptorat(defpoly(root))]} $B$N%j%9%H$H$7$F(B
                   1485: $BI=8=$5$l$F$$$k(B. $B$9$J$o$A(B, $B5a$a$k:G>.J,2rBN$O(B, $BM-M}?tBN$K(B, $B$3$N(B @code{root}
                   1486: $B$rA4$FE:2C$7$?BN$H$7$FF@$i$l$k(B. $BE:2C$O(B, $B1&$NJ}$N(B @code{root} $B$+$i=g$K(B
                   1487: $B9T$o$l$k(B.
1.2       noro     1488: \E
                   1489: \BEG
                   1490: The splitting field is represented as a list of pairs of form
1.7       noro     1491: @code{[root,} @code{algptorat(defpoly(root))]}.
1.2       noro     1492: In more detail, the list is interpreted as a representation
                   1493: of successive extension obtained by adjoining @b{root}'s
                   1494: to the rational number field.  Adjoining is performed from the right
                   1495: @b{root} to the left.
                   1496: \E
1.1       noro     1497: @item
1.2       noro     1498: \BJP
1.1       noro     1499: @code{sp()} $B$O(B, $BFbIt$G%N%k%`$N7W;;$N$?$a$K(B @code{sp_norm()} $B$r$7$P$7$P(B
                   1500: $B5/F0$9$k(B. $B%N%k%`$N7W;;$O(B, $B>u67$K1~$8$F$5$^$6$^$JJ}K!$G9T$o$l$k$,(B,
                   1501: $B$=$3$GMQ$$$i$l$kJ}K!$,:GA1$H$O8B$i$:(B, $BC1=c$J=*7k<0$N7W;;$NJ}$,9bB.(B
                   1502: $B$G$"$k>l9g$b$"$k(B.
                   1503: $BBg0hJQ?t(B @code{USE_RES} $B$r(B 1 $B$K@_Dj$9$k$3$H$K$h$j(B, $B>o$K=*7k<0$K$h$j7W;;(B
                   1504: $B$5$;$k$3$H$,$G$-$k(B.
1.2       noro     1505: \E
                   1506: \BEG
                   1507: @code{sp()} invokes @code{sp_norm()} internally. Computation of norm
                   1508: is done by several methods according to the situation but the algorithm
                   1509: selection is not always optimal and a simple resultant computation is
                   1510: often superior to the other methods.
                   1511: By setting the global variable @code{USE_RES} to 1,
                   1512: the builtin function @code{res()} is always used.
                   1513: \E
1.1       noro     1514: @end itemize
                   1515:
                   1516: @example
                   1517: [101] L=sp(x^9-54);
1.7       noro     1518: [[x+(-#2),-54*x+(#1^6*#2^4),54*x+(#1^6*#2^4+54*#2),
                   1519: 54*x+(-#1^8*#2^2),-54*x+(#1^5*#2^5),54*x+(#1^5*#2^5+#1^8*#2^2),
                   1520: -54*x+(-#1^7*#2^3-54*#1),54*x+(-#1^7*#2^3),x+(-#1)],
                   1521: [[(#2),t#2^6+t#1^3*t#2^3+t#1^6],[(#1),t#1^9-54]]]
1.1       noro     1522: [102] for(I=0,M=1;I<9;I++)M*=L[0][I];
                   1523: [111] M=simpalg(M);
                   1524: -1338925209984*x^9+72301961339136
                   1525: [112] ptozp(M);
                   1526: -x^9+54
                   1527: @end example
                   1528:
                   1529: @table @t
1.2       noro     1530: \JP @item $B;2>H(B
                   1531: \EG @item Reference
1.4       noro     1532: @fref{asq af af_noalg}, @fref{defpoly}, @fref{algptorat}, @fref{sp_norm}.
1.1       noro     1533: @end table
                   1534:
1.8     ! noro     1535: \JP @node set_field,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
        !          1536: \EG @node set_field,,, Summary of functions for algebraic numbers
        !          1537: @subsection @code{set_field}
        !          1538: @findex set_field
        !          1539:
        !          1540: @table @t
        !          1541: @item set_field(@var{rootlist})
        !          1542: \JP :: $BBe?tBN$r4pACBN$H$7$F@_Dj$9$k(B.
        !          1543: \EG :: Set an algebraic number field as the currernt ground field.
        !          1544: @end table
        !          1545:
        !          1546: @table @var
        !          1547: @item return
        !          1548: 0
        !          1549: @item rootlist
        !          1550: \JP @code{root} $B$N%j%9%H(B
        !          1551: \EG A list of @code{root}
        !          1552: @end table
        !          1553:
        !          1554: @itemize @bullet
        !          1555: @item
        !          1556: \JP @code{root} $B$N%j%9%H(B @var{rootlist} $B$G@8@.$5$l$kBe?tBN$r4pACBN$H$7$F@_Dj$9$k(B.
        !          1557: \BEG
        !          1558: @code{set_field()} sets an algebraic number field generated by @code{root} in
        !          1559: @var{rootlist} over Q.
        !          1560: \E
        !          1561: @item
        !          1562: \BJP
        !          1563: @code{root} $B$OFbItE*$K=g=x$E$1$i$l$F$$$k$N$G(B, @var{rootlist} $B$O=89g$H$7$F;XDj(B
        !          1564: $B$9$l$P$h$$(B. ($B=g=x$O5$$K$7$J$/$F$h$$(B.)
        !          1565: \E
        !          1566: \BEG
        !          1567: You don't care about the order of @code{root} in @var{rootlist}, because
        !          1568: @code{root} are automatically ordered internally.
        !          1569: \E
        !          1570: @end itemize
        !          1571:
        !          1572: @example
        !          1573: [0] A=newalg(x^2+1);
        !          1574: (#0)
        !          1575: [1] B=newalg(x^3+A);
        !          1576: (#1)
        !          1577: [2] C=newalg(x^4+B);
        !          1578: (#1)
        !          1579: [3] set_field([C,B,A]);
        !          1580: 0
        !          1581: @end example
        !          1582:
        !          1583: @table @t
        !          1584: \JP @item $B;2>H(B
        !          1585: \EG @item Reference
        !          1586: @fref{algtodalg dalgtoalg dptodalg dalgtodp}
        !          1587: @end table
        !          1588:
        !          1589: \JP @node algtodalg dalgtoalg dptodalg dalgtodp,,, $BBe?tE*?t$K4X$9$kH!?t$N$^$H$a(B
        !          1590: \EG @node algtodalg dalgtoalg dptodalg dalgtodp,,, Summary of functions for algebraic numbers
        !          1591: @subsection @code{algtodalg}, @code{dalgtoalg}, @code{dptodalg}, @code{dalgtodp}
        !          1592: @findex algtodalg
        !          1593: @findex dalgtoalg
        !          1594: @findex dpodalg
        !          1595: @findex dalgtodp
        !          1596:
        !          1597: @table @t
        !          1598: @item algtodalg(@var{alg})
        !          1599: \JP :: $BBe?tE*?t(B @var{alg} $B$r(B @code{DAlg} $B$KJQ49$9$k(B.
        !          1600: \EG :: Converts an algebraic number @var{alg} to a @code{DAlg}.
        !          1601: @item dalgtoalg(@var{dalg})
        !          1602: \JP :: @code{DAlg} @code{dalg} $B$rBe?tE*?t$KJQ49$9$k(B.
        !          1603: \EG :: Converts a @code{DAlg} @code{dalg} to an algebraic number.
        !          1604: @item dptodalg(@var{dp})
        !          1605: \JP :: $BJ,;6B?9`<0(B @var{dp} $B$r(B @code{DAlg} $B$KJQ49$9$k(B.
        !          1606: \EG :: Converts an algebraic number @var{alg} to a @code{DAlg}.
        !          1607: @item dalgtodp(@var{dalg})
        !          1608: \JP :: @code{DAlg} @code{dalg} $B$rJ,;6B?9`<0$KJQ49$9$k(B.
        !          1609: \EG :: Converts a @code{DAlg} @code{dalg} to an algebraic number.
        !          1610: @end table
        !          1611:
        !          1612: @table @var
        !          1613: @item return
        !          1614: \JP $BBe?tE*?t(B, @code{DAlg} $B$^$?$O(B [$BJ,;6B?9`<0(B,$BJ,Jl(B] $B$J$k%j%9%H(B
        !          1615: \EG An algebraic number, a @code{DAlg} or a list [distributed polynomial,denominator]
        !          1616: @item alg
        !          1617: \JP  @code{root} $B$r4^$`Be?tE*?t(B
        !          1618: \EG an algebraic number containing @code{root}
        !          1619: @item dp
        !          1620: \JP  $BM-M}?t78?tJ,;6B?9`<0(B
        !          1621: \EG a distributed polynomial over Q
        !          1622: @end table
        !          1623:
        !          1624: @itemize @bullet
        !          1625: @item
        !          1626: \JP @code{root} $B$r4^$`Be?tE*?t(B, @code{DAlg} $B$*$h$SJ,;6B?9`<04V$NJQ49$r9T$&(B.
        !          1627: \BEG
        !          1628: These functions are converters between @code{DAlg} and an algebraic number
        !          1629: containing @code{root}, or a distributed polynomial.
        !          1630: \E
        !          1631: @item
        !          1632: \BJP
        !          1633: @code{DAlg} $B$,B0$9$Y$-Be?tBN$O(B, @code{set_field()} $B$K$h$j(B
        !          1634: $B$"$i$+$8$a@_Dj$7$F$*$/I,MW$,$"$k(B.
        !          1635: \E
        !          1636: \BEG
        !          1637: A ground field to which a @code{DAlg} belongs must be set by @code{set_field()}
        !          1638: in advance.
        !          1639: \E
        !          1640: @item
        !          1641: \BJP
        !          1642: @code{dalgtodp()} $B$O(B, $BJ,;R$G$"$k@0?t78?tJ,;6B?9`<0$H(B, $BJ,Jl$G$"$k@0?t$rMWAG$K;}$D(B
        !          1643: $B%j%9%H$rJV$9(B.
        !          1644: \E
        !          1645: \BEG
        !          1646: @code{dalgtodp()} returns a list containing the numerator (a distributed polynomial)
        !          1647: and the denominator (an integer).
        !          1648: \E
        !          1649: @item
        !          1650: \BJP
        !          1651: @code{algtodalg()}, @code{dptodalg()} $B$O4JC12=$5$l$?7k2L$rJV$9(B.
        !          1652: \E
        !          1653: \BEG
        !          1654: @code{algtodalg()}, @code{dptodalg()} return the simplified result.
        !          1655: \E
        !          1656: @end itemize
        !          1657:
        !          1658: @example
        !          1659: [0] A=newalg(x^2+1);
        !          1660: (#0)
        !          1661: [1] B=newalg(x^3+A*x+A);
        !          1662: (#1)
        !          1663: [2] set_field([B,A]);
        !          1664: 0
        !          1665: [3] C=algtodalg((A+B)^10);
        !          1666: ((408)*<<2,1>>+(103)*<<2,0>>+(-36)*<<1,1>>+(-446)*<<1,0>>
        !          1667: +(-332)*<<0,1>>+(-218)*<<0,0>>)
        !          1668: [4] dalgtoalg(C);
        !          1669: ((408*#0+103)*#1^2+(-36*#0-446)*#1-332*#0-218)
        !          1670: [5] D=dptodalg(<<10,10>>/10+2*<<5,5>>+1/3*<<0,0>>);
        !          1671: ((-9)*<<2,1>>+(57)*<<2,0>>+(-63)*<<1,1>>+(-12)*<<1,0>>
        !          1672: +(-60)*<<0,1>>+(1)*<<0,0>>)/30
        !          1673: [6] dalgtodp(D);
        !          1674: [(-9)*<<2,1>>+(57)*<<2,0>>+(-63)*<<1,1>>+(-12)*<<1,0>>
        !          1675: +(-60)*<<0,1>>+(1)*<<0,0>>,30]
        !          1676: @end example
        !          1677:
        !          1678: @table @t
        !          1679: \JP @item $B;2>H(B
        !          1680: \EG @item Reference
        !          1681: @fref{set_field}
        !          1682: @end table

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