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