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

Annotation of OpenXM/src/asir-doc/parts/ff.texi, Revision 1.4

1.4     ! noro        1: @comment $OpenXM: OpenXM/src/asir-doc/parts/ff.texi,v 1.3 2000/01/13 08:29:56 noro Exp $
1.2       noro        2: \BJP
1.1       noro        3: @node $BM-8BBN$K4X$9$k1i;;(B,,, Top
                      4: @chapter $BM-8BBN$K4X$9$k1i;;(B
1.2       noro        5: \E
                      6: \BEG
                      7: @node Finite fields,,, Top
                      8: @chapter Finite fields
                      9: \E
1.1       noro       10:
                     11: @menu
1.2       noro       12: \BJP
1.1       noro       13: * $BM-8BBN$NI=8=$*$h$S1i;;(B::
                     14: * $BM-8BBN>e$G$N(B 1 $BJQ?tB?9`<0$N1i;;(B::
                     15: * $BM-8BBN>e$NBJ1_6J@~$K4X$9$k1i;;(B::
                     16: * $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B::
1.2       noro       17: \E
                     18: \BEG
                     19: * Representation of finite fields::
                     20: * Univariate polynomials on finite fields::
                     21: * Elliptic curves on finite fields::
                     22: * Functions for Finite fields::
                     23: \E
1.1       noro       24: @end menu
                     25:
1.2       noro       26: \BJP
1.1       noro       27: @node $BM-8BBN$NI=8=$*$h$S1i;;(B,,, $BM-8BBN$K4X$9$k1i;;(B
                     28: @section $BM-8BBN$NI=8=$*$h$S1i;;(B
1.2       noro       29: \E
                     30: \BEG
                     31: @node Representation of finite fields,,, Finite fields
                     32: @section Representation of finite fields
                     33: \E
1.1       noro       34:
                     35: @noindent
1.2       noro       36: \BJP
1.4     ! noro       37: @b{Asir} $B$K$*$$$F$O(B, $BM-8BBN$O(B, $B@5I8?tAGBN(B GF(p), $BI8?t(B 2 $B$NM-8BBN(B GF(2^n),
        !            38: GF(p) $B$N(B n $B<!3HBg(B GF(p^n)
1.1       noro       39: $B$,Dj5A$G$-$k(B. $B$3$l$i$OA4$F(B, @code{setmod_ff()} $B$K$h$jDj5A$5$l$k(B.
1.2       noro       40: \E
                     41: \BEG
1.4     ! noro       42: On @b{Asir} @var{GF(p)}, @var{GF(2^n)}, @var{GF(p^n} can be defined, where
        !            43: @var{GF(p)} is a finite prime field of charateristic @var{p},
        !            44: @var{GF(2^n)} is a finite field of characteristic 2 and
        !            45: @var{GF(p^n} is a finite extension of @var{GF(p)}. These are
1.2       noro       46: all defined by @code{setmod_ff()}.
                     47: \E
1.1       noro       48:
                     49: @example
                     50: [0] P=pari(nextprime,2^50);
                     51: 1125899906842679
                     52: [1] setmod_ff(P);
                     53: 1125899906842679
                     54: [2] field_type_ff();
                     55: 1
                     56: [3] load("fff");
                     57: 1
                     58: [4] F=defpoly_mod2(50);
                     59: x^50+x^4+x^3+x^2+1
                     60: [5] setmod_ff(F);
                     61: x^50+x^4+x^3+x^2+1
                     62: [6] field_type_ff();
                     63: 2
1.4     ! noro       64: [7] setmod_ff(x^3+x+1,1125899906842679);
        !            65: [1*x^3+1*x+1,1125899906842679]
        !            66: [8] field_type_ff();
        !            67: 3
        !            68: [9] setmod_ff(3,5);
        !            69: [3,x^5+2*x+1,x]
        !            70: [10] field_type_ff();
        !            71: 4
1.1       noro       72: @end example
1.2       noro       73: \BJP
1.4     ! noro       74: @code{setmod_ff()} $B$O(B, $B$5$^$6$^$J%?%$%W$NM-8BBN$r4pACBN$H$7$F%;%C%H$9$k(B.
        !            75: $B0z?t$,@5@0?t(B p $B$N>l9g(B GF(p), n $B<!B?9`<0(B f(x) $B$N>l(B
1.1       noro       76: $B9g(B, f(x) mod 2 $B$rDj5AB?9`<0$H$9$k(B GF(2^n) $B$r$=$l$>$l4pACBN$H$7$F%;%C%H$9(B
1.4     ! noro       77: $B$k(B. $B$^$?(B, $BM-8BAGBN$NM-8B<!3HBg$bDj5A$G$-$k(B. $B>\$7$/$O(B @xref{$B?t$N7?(B}.
        !            78: @code{setmod_ff()} $B$K$*$$$F$O0z?t$N4{Ls%A%'%C%/$O9T$o$:(B, $B8F$S=P$7B&(B
1.1       noro       79: $B$,@UG$$r;}$D(B.
                     80:
                     81: $B4pACBN$H$O(B, $B$"$/$^$GM-8BBN$N85$H$7$F@k8@$"$k$$$ODj5A$5$l$?%*%V%8%'%/%H$,(B,
                     82: $B%;%C%H$5$l$?4pACBN$N1i;;$K=>$&$H$$$&0UL#$G$"$k(B. $BB($A(B, $BM-M}?t$I$&$7$N1i;;(B
                     83: $B$N7k2L$OM-M}?t$H$J$k(B. $BC"$7(B, $B;MB'1i;;$K$*$$$F0lJ}$N%*%Z%i%s%I$,M-8BBN$N85(B
                     84: $B$N>l9g$K$O(B, $BB>$N85$b<+F0E*$KF1$8M-8BBN$N85$H8+$J$5$l(B, $B1i;;7k2L$bF1MM$K$J(B
                     85: $B$k(B.
                     86:
                     87: 0 $B$G$J$$M-8BBN$N85$O(B, $B?t%*%V%8%'%/%H$G$"$j(B, $B<1JL;R$NCM$O(B 1 $B$G$"$k(B.
                     88: $B$5$i$K(B, 0 $B$G$J$$M-8BBN$N85$N?t<1JL;R$O(B, GF(p) $B$N>l9g(B 6, GF(2^n) $B$N>l9g(B 7
                     89: $B$H$J$k(B.
                     90:
                     91: $BM-8BBN$N85$NF~NOJ}K!$O(B, $BM-8BBN$N<oN`$K$h$jMM!9$G$"$k(B. GF(p) $B$N>l9g(B,
                     92: @code{simp_ff()} $B$K$h$k(B.
1.2       noro       93: \E
                     94:
                     95: \BEG
                     96: If @var{p} is a positive integer, @code{setmod_ff(@var{p})} sets
                     97: @var{GF(p)} as the current base field.
                     98: If @var{f} is a univariate polynomial of degree @var{n},
                     99: @code{setmod_ff(@var{f})} sets @var{GF(2^n)} as the current
                    100: base field.  @var{GF(2^n)} is represented
                    101: as an algebraic extension of @var{GF(2)} with the defining polynomial
1.4     ! noro      102: @var{f mod 2}. Furthermore, finite extensions of prime finite fields
        !           103: can be defined. @xref{Types of numbers}.
        !           104: In all cases the primality check of the argument is
1.2       noro      105: not done and the caller is responsible for it.
                    106:
                    107: Correctly speaking there is no actual object corresponding to a 'base field'.
                    108: Setting a base field means that operations on elements of finite fields
                    109: are done according to the arithmetics of the base field. Thus, if
                    110: operands of an arithmetic operation are both rational numbers, then the result
                    111: is also a rational number. However, if one of the operands is in
                    112: a finite field, then the other is automatically regarded as in the
                    113: same finite field and the operation is done in the finite field.
                    114:
                    115: A non zero element of a finite field belongs to the number and has object
                    116: identifier 1. Its number identifier is 6 if the finite field is @var{GF(p)},
                    117: 7 if it is @var{GF(2^n)}.
                    118:
                    119: There are several methods to input an element of a finite field.
                    120: An element of @var{GF(p)} can be input by @code{simp_ff()}.
                    121: \E
1.1       noro      122:
                    123: @example
                    124: [0] P=pari(nextprime,2^50);
                    125: 1125899906842679
                    126: [1] setmod_ff(P);
                    127: 1125899906842679
                    128: [2] A=simp_ff(2^100);
                    129: 3025
                    130: [3] ntype(@@@@);
                    131: 6
                    132: @end example
                    133:
1.2       noro      134: \JP $B$^$?(B, GF(2^n) $B$N>l9g$$$/$D$+$NJ}K!$,$"$k(B.
                    135: \EG In the case of @var{GF(2^n)} the following methods are available.
                    136:
1.1       noro      137: @example
                    138: [0] setmod_ff(x^50+x^4+x^3+x^2+1);
                    139: x^50+x^4+x^3+x^2+1
                    140: [1] A=@@;
                    141: (@@)
                    142: [2] ptogf2n(x^50+1);
                    143: (@@^50+1)
                    144: [3] simp_ff(@@@@);
                    145: (@@^4+@@^3+@@^2)
                    146: [4] ntogf2n(2^10-1);
                    147: (@@^9+@@^8+@@^7+@@^6+@@^5+@@^4+@@^3+@@^2+@@+1)
                    148: @end example
                    149:
1.2       noro      150: \BJP
1.1       noro      151: $BM-8BBN$N85$O?t$G$"$j(B, $BBN1i;;$,2DG=$G$"$k(B. @code{@@} $B$O(B
                    152: GF(2^n) $B$N(B, GF(2)$B>e$N@8@.85$G$"$k(B. $B>\$7$/$O(B @xref{$B?t$N7?(B}.
1.2       noro      153: \E
                    154: \BEG
                    155: Elements of finite fields are numbers and one can apply field arithmetics
                    156: to them. @code{@@} is a generator of @var{GF(2^n)} over @var{GF(2)}.
                    157: @xref{Types of numbers}.
                    158: \E
1.1       noro      159:
                    160: @noindent
                    161:
1.2       noro      162: \BJP
1.1       noro      163: @node $BM-8BBN>e$G$N(B 1 $BJQ?tB?9`<0$N1i;;(B,,, $BM-8BBN$K4X$9$k1i;;(B
                    164: @section $BM-8BBN>e$G$N(B 1 $BJQ?tB?9`<0$N1i;;(B
1.2       noro      165: \E
                    166: \BEG
                    167: @node Univariate polynomials on finite fields,,, Finite fields
                    168: @section Univariate polynomials on finite fields
                    169: \E
1.1       noro      170:
                    171: @noindent
1.2       noro      172: \BJP
1.1       noro      173: @samp{fff} $B$G$O(B, $BM-8BBN>e$N(B 1 $BJQ?tB?9`<0$KBP$7(B, $BL5J?J}J,2r(B, DDF, $B0x?tJ,2r(B,
                    174: $BB?9`<0$N4{LsH=Dj$J$I$N4X?t$,Dj5A$5$l$F$$$k(B.
                    175:
                    176: $B$$$:$l$b(B, $B7k2L$O(B [@b{$B0x;R(B}, @b{$B=EJ#EY(B}] $B$N%j%9%H$H$J$k$,(B, $B0x;R$O(B monic
                    177: $B$H$J$j(B, $BF~NOB?9`<0$N<g78?t$O<N$F$i$l$k(B.
                    178:
                    179: $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
                    180: $B%"%k%4%j%:%`$r:NMQ$7$F$$$k(B.
                    181:
                    182: $BM-8BBN>e$G$N0x?tJ,2r$O(B, DDF $B$N8e(B, $B<!?tJL0x;R$NJ,2r$N:]$K(B, Berlekamp
                    183: $B%"%k%4%j%:%`$GNm6u4V$r5a$a(B, $B4pDl%Y%/%H%k$N:G>.B?9`<0$r5a$a(B, $B$=$N:,(B
                    184: $B$r(B Cantor-Zassenhaus $B%"%k%4%j%:%`$K$h$j5a$a$k(B, $B$H$$$&J}K!$r<BAu$7$F$$$k(B.
1.2       noro      185: \E
                    186: \BEG
                    187: In @samp{fff} square-free factorization, DDF (distinct degree factorization),
                    188: irreducible factorization and primality check are implemented for
                    189: univariate polynomials over finite fields.
                    190:
                    191: Factorizers return lists of [@b{factor},@b{multiplicity}]. The factor
                    192: part is monic and the information on the leading coefficient of the
                    193: input polynomial is abandoned.
                    194:
                    195: The algorithm used in square-free factorization is the most primitive one.
                    196:
                    197: The irreducible factorization proceeds as follows.
1.1       noro      198:
1.2       noro      199: @enumerate
                    200: @item DDF
                    201: @item Nullspace computation by Berlekamp algorithm
                    202: @item Root finding of minimal polynomials of bases of the nullspace
                    203: @item Separation of irreducible factors by the roots
                    204: @end enumerate
                    205: \E
1.1       noro      206:
1.2       noro      207: \BJP
1.1       noro      208: @node $BM-8BBN>e$NBJ1_6J@~$K4X$9$k1i;;(B,,, $BM-8BBN$K4X$9$k1i;;(B
                    209: @section $BM-8BBN>e$NBJ1_6J@~$K4X$9$k1i;;(B
1.2       noro      210: \E
                    211: \BEG
                    212: @node Elliptic curves on finite fields,,, Finite fields
                    213: @section Elliptic curves on finite fields
                    214: \E
1.1       noro      215:
1.2       noro      216: \BJP
1.1       noro      217: $BM-8BBN>e$NBJ1_6J@~$K4X$9$k$$$/$D$+$N4pK\E*$J1i;;$,(B, $BAH$_9~$_4X?t$H$7$F(B
                    218: $BDs6!$5$l$F$$$k(B.
                    219:
                    220: $BBJ1_6J@~$N;XDj$O(B, $BD9$5(B 2 $B$N%Y%/%H%k(B @var{[a b]} $B$G9T$&(B. @var{a}, @var{b}
                    221: $B$OM-8BBN$N85$G(B,
                    222: @code{setmod_ff} $B$GDj5A$5$l$F$$$kM-8BBN$,AGBN$N>l9g(B, @var{y^2=x^3+ax+b},
                    223: $BI8?t(B 2 $B$NBN$N>l9g(B @var{y^2+xy=x^3+ax^2+b} $B$rI=$9(B.
                    224:
                    225: $BBJ1_6J@~>e$NE@$O(B, $BL58B1sE@$b9~$a$F2CK!72$r$J$9(B. $B$3$N1i;;$K4X$7$F(B, $B2C;;(B
                    226: (@code{ecm_add_ff()}), $B8:;;(B (@code{ecm_sub_ff()}) $B$*$h$S5U857W;;$N$?$a$N(B
                    227: $B4X?t(B (@code{ecm_chsgn_ff()}) $B$,Ds6!$5$l$F$$$k(B. $BCm0U$9$Y$-$O(B, $B1i;;$NBP>](B
                    228: $B$H$J$kE@$NI=8=$,(B,
                    229:
                    230: @itemize @bullet
                    231: @item $BL58B1sE@$O(B 0.
                    232: @item $B$=$l0J30$NE@$O(B, $BD9$5(B 3 $B$N%Y%/%H%k(B @var{[x y z]}. $B$?$@$7(B, @var{z} $B$O(B
                    233: 0 $B$G$J$$(B.
                    234: @end itemize
                    235:
                    236: $B$H$$$&E@$G$"$k(B. @var{[x y z]} $B$O@F<!:BI8$K$h$kI=8=$G$"$j(B, $B%"%U%#%s:BI8(B
                    237: $B$G$O(B @var{[x/z y/z]} $B$J$kE@$rI=$9(B. $B$h$C$F(B, $B%"%U%#%s:BI8(B @var{[x y]} $B$G(B
                    238: $BI=8=$5$l$?E@$r1i;;BP>]$H$9$k$K$O(B, @var{[x y 1]} $B$J$k%Y%/%H%k$r(B
                    239: $B@8@.$9$kI,MW$,$"$k(B.
                    240: $B1i;;7k2L$b@F<!:BI8$GF@$i$l$k$,(B, @var{z} $B:BI8$,(B 1 $B$H$O8B$i$J$$$?$a(B,
                    241: $B%"%U%#%s:BI8$r5a$a$k$?$a$K$O(B @var{x}, @var{y} $B:BI8$r(B @var{z} $B:BI8$G(B
                    242: $B3d$kI,MW$,$"$k(B.
1.2       noro      243: \E
                    244:
                    245: \BEG
                    246: Several fundamental operations on elliptic curves over finite fields
                    247: are provided as built-in functions.
                    248:
                    249: An elliptic curve is specified by a vector @var{[a b]} of length 2,
                    250: where @var{a}, @var{b} are elements of finite fields.
                    251: If the current base field is a prime field, then @var{[a b]} represents
                    252: @var{y^2=x^3+ax+b}. If the current base field is a finite field of
                    253: characteristic 2, then @var{[a b]} represents @var{y^2+xy=x^3+ax^2+b}.
                    254:
                    255: Points on an elliptic curve together with the point at infinity
                    256: forms an additive group. The addition, the subtraction and the
                    257: additive inverse operation are provided as @code{ecm_add_ff()},
                    258: @code{ecm_sub_ff()} and @code{ecm_chsgn_ff()} respectively.
                    259: Here the representation of points are as follows.
                    260:
                    261: @itemize @bullet
                    262: @item 0 denotes the point at infinity.
                    263: @item The other points are represented by vectors @var{[x y z]} of
                    264: length 3 with non-zero @var{z}.
                    265: @end itemize
                    266:
                    267: @var{[x y z]} represents a projective coordinate and
                    268: it corresponds to @var{[x/z y/z]} in the affine coordinate.
                    269: To apply the above operations to a point @var{[x y]},
                    270: @var{[x y 1]} should be used instead as an argument.
                    271: The result of an operation is also represented by the projective
                    272: coordinate. As the third coordinate is not always equal to 1,
                    273: one has to divide the first and the scond coordinate by the third
                    274: one to obtain the affine coordinate.
                    275: \E
1.1       noro      276:
1.2       noro      277: \BJP
1.1       noro      278: @node $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B,,, $BM-8BBN$K4X$9$k1i;;(B
                    279: @section $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
1.2       noro      280: \E
                    281: \BEG
                    282: @node Functions for Finite fields,,, Finite fields
                    283: @section Functions for Finite fields
                    284: \E
1.1       noro      285:
                    286: @menu
                    287: * setmod_ff::
                    288: * field_type_ff::
                    289: * field_order_ff::
                    290: * characteristic_ff::
                    291: * extdeg_ff::
                    292: * simp_ff::
                    293: * random_ff::
                    294: * lmptop::
                    295: * ntogf2n::
                    296: * gf2nton::
                    297: * ptogf2n::
                    298: * gf2ntop::
                    299: * defpoly_mod2::
                    300: * fctr_ff::
                    301: * irredcheck_ff::
                    302: * randpoly_ff::
                    303: * ecm_add_ff ecm_sub_ff ecm_chsgn_ff::
                    304: * extdeg_ff::
                    305: @end menu
                    306:
1.2       noro      307: \JP @node setmod_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    308: \EG @node setmod_ff,,, Functions for Finite fields
1.1       noro      309: @subsection @code{setmod_ff}
                    310: @findex setmod_ff
                    311:
                    312: @table @t
                    313: @item setmod_ff([@var{prime}|@var{poly}])
1.2       noro      314: \JP :: $BM-8BBN$N@_Dj(B, $B@_Dj$5$l$F$$$kM-8BBN$NK!(B, $BDj5AB?9`<0$NI=<((B
                    315: \EG :: Sets/Gets the current base fields.
1.1       noro      316: @end table
                    317:
                    318: @table @var
                    319: @item return
1.2       noro      320: \JP $B?t$^$?$OB?9`<0(B
                    321: \EG number or polynomial
1.1       noro      322: @item prime
1.2       noro      323: \JP $BAG?t(B
                    324: \EG prime
1.1       noro      325: @item poly
1.2       noro      326: \JP GF(2) $B>e4{Ls$J(B 1 $BJQ?tB?9`<0(B
                    327: \EG univariate polynomial irreducible over GF(2)
1.1       noro      328: @end table
                    329:
                    330: @itemize @bullet
1.2       noro      331: \BJP
1.1       noro      332: @item
                    333: $B0z?t$,@5@0?t(B @var{prime} $B$N;~(B, GF(@var{prime}) $B$r4pACBN$H$7$F@_Dj$9$k(B.
                    334: @item
                    335: $B0z?t$,B?9`<0(B @var{poly} $B$N;~(B,
1.2       noro      336: GF(2^deg(@var{poly} mod 2)) = GF(2)[t]/(@var{poly}(t) mod 2)
1.1       noro      337: $B$r4pACBN$H$7$F@_Dj$9$k(B.
                    338: @item
                    339: $BL50z?t$N;~(B, $B@_Dj$5$l$F$$$k4pACBN$,(B GF(@var{prime}) $B$N>l9g(B @var{prime},
                    340: GF(2^n) $B$N>l9gDj5AB?9`<0$rJV$9(B.
                    341: @item
                    342: GF(2^n) $B$NDj5AB?9`<0$O(B, GF(2) $B>e(B n $B<!4{Ls$J$i$J$s$G$bNI$$$,(B, $B8zN($K(B
                    343: $B1F6A$9$k$?$a(B, @code{defpoly_mod2()} $B$G@8@.$9$k$N$,$h$$(B.
1.2       noro      344: \E
                    345: \BEG
                    346: @item
                    347: If the argument is a non-negative integer @var{prime}, GF(@var{prime})
                    348: is set as the current base field.
                    349: @item
                    350: If the argument is a polynomial @var{poly},
                    351: GF(2^deg(@var{poly} mod 2)) = GF(2)[t]/(@var{poly}(t) mod2)
                    352: is set as the current base field.
                    353: @item
                    354: If no argument is specified, the modulus indicating the current base field
                    355: is returned. If the current base field is GF(@var{prime}), @var{prime} is
                    356: returned. If it is GF(2^n), the defining polynomial is returned.
                    357: @item
                    358: Any irreducible univariate polynomial over GF(2) is available to
                    359: set GF(2^n). However the use of @code{defpoly_mod2()} is recommended
                    360: for efficiency.
                    361: \E
1.1       noro      362: @end itemize
                    363:
                    364: @example
                    365: [174] defpoly_mod2(100);
                    366: x^100+x^15+1
                    367: [175] setmod_ff(@@@@);
                    368: x^100+x^15+1
                    369: [176] setmod_ff();
                    370: x^100+x^15+1
                    371: @end example
                    372:
                    373: @table @t
1.2       noro      374: \JP @item $B;2>H(B
                    375: \EG @item References
1.1       noro      376: @fref{defpoly_mod2}
                    377: @end table
                    378:
1.2       noro      379: \JP @node field_type_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    380: \EG @node field_type_ff,,, Functions for Finite fields
1.1       noro      381: @subsection @code{field_type_ff}
                    382: @findex field_type_ff
                    383:
                    384: @table @t
                    385: @item field_type_ff()
1.2       noro      386: \JP :: $B@_Dj$5$l$F$$$k4pACBN$N<oN`(B
                    387: \EG :: Type of the current base field.
1.1       noro      388: @end table
                    389:
                    390: @table @var
                    391: @item return
1.2       noro      392: \JP $B@0?t(B
                    393: \EG integer
1.1       noro      394: @end table
                    395:
                    396: @itemize @bullet
1.2       noro      397: \BJP
1.1       noro      398: @item
                    399: $B@_Dj$5$l$F$$$k4pACBN$N<oN`$rJV$9(B.
                    400: @item
                    401: $B@_Dj$J$7$J$i(B 0, GF(p) $B$J$i(B 1, GF(2^n) $B$J$i(B 2 $B$rJV$9(B.
1.2       noro      402: \E
                    403: \BEG
                    404: @item
                    405: Returns the type of the current base field.
                    406: @item
                    407: If no field is set, 0 is returned. If GF(p) is set, 1 is returned.
                    408: If GF(2^n) is set, 2 is returned.
                    409: \E
1.1       noro      410: @end itemize
                    411:
                    412: @example
                    413: [0] field_type_ff();
                    414: 0
                    415: [1] setmod_ff(3);
                    416: 3
                    417: [2] field_type_ff();
                    418: 1
                    419: [3] setmod_ff(x^2+x+1);
                    420: x^2+x+1
                    421: [4] field_type_ff();
                    422: 2
                    423: @end example
                    424:
                    425: @table @t
1.2       noro      426: \JP @item $B;2>H(B
                    427: \EG @item References
1.1       noro      428: @fref{setmod_ff}
                    429: @end table
                    430:
1.2       noro      431: \JP @node field_order_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    432: \EG @node field_order_ff,,, Functions for Finite fields
1.1       noro      433: @subsection @code{field_order_ff}
                    434: @findex field_order_ff
                    435:
                    436: @table @t
                    437: @item field_order_ff()
1.2       noro      438: \JP :: $B@_Dj$5$l$F$$$k4pACBN$N0L?t(B
                    439: \EG :: Order of the current base field.
1.1       noro      440: @end table
                    441:
                    442: @table @var
                    443: @item return
1.2       noro      444: \JP $B@0?t(B
                    445: \EG integer
1.1       noro      446: @end table
                    447:
                    448: @itemize @bullet
1.2       noro      449: \BJP
1.1       noro      450: @item
                    451: $B@_Dj$5$l$F$$$k4pACBN$N0L?t(B ($B85$N8D?t(B) $B$rJV$9(B.
                    452: @item
                    453: $B@_Dj$5$l$F$$$kBN$,(B GF(q) $B$J$i$P(B q $B$rJV$9(B.
1.2       noro      454: \E
                    455: \BEG
                    456: @item
                    457: Returns the order of the current base field.
                    458: @item
                    459: @var{q} is returned if the current base field is GF(q).
                    460: \E
1.1       noro      461: @end itemize
                    462:
                    463: @example
                    464: [0] field_order_ff();
                    465: field_order_ff : current_ff is not set
                    466: return to toplevel
                    467: [0] setmod_ff(3);
                    468: 3
                    469: [1] field_order_ff();
                    470: 3
                    471: [2] setmod_ff(x^2+x+1);
                    472: x^2+x+1
                    473: [3] field_order_ff();
                    474: 4
                    475: @end example
                    476:
                    477: @table @t
1.2       noro      478: \JP @item $B;2>H(B
                    479: \EG @item References
1.1       noro      480: @fref{setmod_ff}
                    481: @end table
                    482:
1.2       noro      483: \JP @node characteristic_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    484: \EG @node characteristic_ff,,, Functions for Finite fields
1.1       noro      485: @subsection @code{characteristic_ff}
                    486: @findex characteristic_ff
                    487:
                    488: @table @t
                    489: @item characteristic_ff()
1.2       noro      490: \JP :: $B@_Dj$5$l$F$$$kBN$NI8?t(B
                    491: \EG :: Characteristic of the current base field.
1.1       noro      492: @end table
                    493:
                    494: @table @var
                    495: @item return
1.2       noro      496: \JP $B@0?t(B
                    497: \EG integer
1.1       noro      498: @end table
                    499:
                    500: @itemize @bullet
1.2       noro      501: \BJP
1.1       noro      502: @item
                    503: $B@_Dj$5$l$F$$$kBN$NI8?t$rJV$9(B.
                    504: @item
                    505: GF(p) $B$N>l9g(B p, GF(2^n) $B$N>l9g(B 2 $B$rJV$9(B.
1.2       noro      506: \E
                    507: \BEG
                    508: @item
                    509: Returns the characteristic of the current base field.
                    510: @item
                    511: @var{p} is returned if @var{GF(p)}, where @var{p} is a prime, is set.
                    512: @var{2} is returned if @var{GF(2^n)} is set.
                    513: \E
1.1       noro      514: @end itemize
                    515:
                    516: @example
                    517: [0] characteristic_ff();
                    518: characteristic_ff : current_ff is not set
                    519: return to toplevel
                    520: [0] setmod_ff(3);
                    521: 3
                    522: [1] characteristic_ff();
                    523: 3
                    524: [2] setmod_ff(x^2+x+1);
                    525: x^2+x+1
                    526: [3] characteristic_ff();
                    527: 2
                    528: @end example
                    529:
                    530: @table @t
1.2       noro      531: \JP @item $B;2>H(B
                    532: \EG @item References
1.1       noro      533: @fref{setmod_ff}
                    534: @end table
                    535:
1.2       noro      536: \JP @node extdeg_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    537: \EG @node extdeg_ff,,, Functions for Finite fields
1.1       noro      538: @subsection @code{extdeg_ff}
                    539: @findex extdeg_ff
                    540:
                    541: @table @t
                    542: @item extdeg_ff()
1.2       noro      543: \JP :: $B@_Dj$5$l$F$$$k4pACBN$N(B, $BAGBN$KBP$9$k3HBg<!?t(B
                    544: \EG :: Extension degree of the current base field over the prime field.
1.1       noro      545: @end table
                    546:
                    547: @table @var
                    548: @item return
1.2       noro      549: \JP $B@0?t(B
                    550: \EG integer
1.1       noro      551: @end table
                    552:
                    553: @itemize @bullet
1.2       noro      554: \BJP
1.1       noro      555: @item
                    556: $B@_Dj$5$l$F$$$k4pACBN$N(B, $BAGBN$KBP$9$k3HBg<!?t$rJV$9(B.
                    557: @item
                    558: GF(p) $B$N>l9g(B 1, GF(2^n) $B$N>l9g(B n $B$rJV$9(B.
1.2       noro      559: \E
                    560: \BEG
                    561: @item
                    562: Returns the extension degree of the current base field over the prime field.
                    563: @item
                    564: GF(p) $B$N>l9g(B 1, GF(2^n) $B$N>l9g(B n $B$rJV$9(B.
                    565: 1 is returned if @var{GF(p)}, where @var{p} is a prime, is set.
                    566: @var{n} is returned if @var{GF(2^n)} is set.
                    567: \E
1.1       noro      568: @end itemize
                    569:
                    570: @example
                    571: [0] extdeg_ff();
                    572: extdeg_ff : current_ff is not set
                    573: return to toplevel
                    574: [0] setmod_ff(3);
                    575: 3
                    576: [1] extdeg_ff();
                    577: 1
                    578: [2] setmod_ff(x^2+x+1);
                    579: x^2+x+1
                    580: [3] extdeg_ff();
                    581: 2
                    582: @end example
                    583:
                    584: @table @t
1.2       noro      585: \JP @item $B;2>H(B
                    586: \EG @item References
1.1       noro      587: @fref{setmod_ff}
                    588: @end table
                    589:
1.2       noro      590: \JP @node simp_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    591: \EG @node simp_ff,,, Functions for Finite fields
1.1       noro      592: @subsection @code{simp_ff}
                    593: @findex simp_ff
                    594:
                    595: @table @t
                    596: @item simp_ff(@var{obj})
1.2       noro      597: \JP :: $B?t(B, $B$"$k$$$OB?9`<0$N78?t$rM-8BBN$N85$KJQ49(B
                    598: \BEG
                    599: :: Converts numbers or coefficients of polynomials into elements
                    600: in finite fields.
                    601: \E
1.1       noro      602: @end table
                    603:
                    604: @table @var
                    605: @item return
1.2       noro      606: \JP $B?t$^$?$OB?9`<0(B
                    607: \EG number or polynomial
1.1       noro      608: @item obj
1.2       noro      609: \JP $B?t$^$?$OB?9`<0(B
                    610: \EG number or polynomial
1.1       noro      611: @end table
                    612:
                    613: @itemize @bullet
1.2       noro      614: \BJP
1.1       noro      615: @item
                    616: $B?t(B, $B$"$k$$$OB?9`<0$N78?t$rM-8BBN$N85$KJQ49$9$k(B.
                    617: @item
                    618: $B@0?t(B, $B$"$k$$$O@0?t78?tB?9`<0$r(B, $BM-8BBN(B, $B$"$k$$$OM-8BBN78?t$KJQ49$9$k$?$a$K(B
                    619: $BMQ$$$k(B.
                    620: @item
                    621: $BM-8BBN$N85$KBP$7(B, $BK!$"$k$$$ODj5AB?9`<0$K$h$k(B reduction $B$r9T$&>l9g$K$b(B
                    622: $BMQ$$$k(B.
1.2       noro      623: \E
                    624: \BEG
                    625: @item
                    626: Converts numbers or coefficients of polynomials into elements in finite
                    627: fields.
                    628: @item
                    629: It is used to convert integers or intrgral polynomials int
                    630: elements of finite fields or polynomials over finite fields.
                    631: @item
                    632: An element of a finite field may not have the reduced representation.
                    633: In such case an application of @code{simp_ff} assures the output has
                    634: the reduced representation.
                    635: \E
1.1       noro      636: @end itemize
                    637:
                    638: @example
                    639: [0] simp_ff((x+1)^10);
                    640: x^10+10*x^9+45*x^8+120*x^7+210*x^6+252*x^5+210*x^4+120*x^3+45*x^2+10*x+1
                    641: [1] setmod_ff(3);
                    642: 3
                    643: [2] simp_ff((x+1)^10);
                    644: 1*x^10+1*x^9+1*x+1
                    645: [3] ntype(coef(@@@@,10));
                    646: 6
                    647: @end example
                    648:
                    649: @table @t
1.2       noro      650: \JP @item $B;2>H(B
                    651: \EG @item References
1.1       noro      652: @fref{setmod_ff}, @fref{lmptop}, @fref{gf2nton}
                    653: @end table
                    654:
1.2       noro      655: \JP @node random_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    656: \EG @node random_ff,,, Functions for Finite fields
1.1       noro      657: @subsection @code{random_ff}
                    658: @findex random_ff
                    659:
                    660: @table @t
                    661: @item random_ff()
1.2       noro      662: \JP :: $BM-8BBN$N85$NMp?t@8@.(B
                    663: \EG :: Random generation of an element of a finite field.
1.1       noro      664: @end table
                    665:
                    666: @table @var
                    667: @item return
1.2       noro      668: \JP $BM-8BBN$N85(B
                    669: \EG element of a finite field
1.1       noro      670: @end table
                    671:
                    672: @itemize @bullet
1.2       noro      673: \BJP
1.1       noro      674: @item
                    675: $BM-8BBN$N85$rMp?t@8@.$9$k(B.
                    676: @item
1.2       noro      677: @code{random()}, @code{lrandom()} $B$HF1$8(B 32bit $BMp?tH/@84o$r;HMQ$7$F$$$k(B.
                    678: \E
                    679: \BEG
                    680: @item
                    681: Generates an element of the current base field randomly.
1.1       noro      682: @item
1.2       noro      683: The same random generator as in @code{random()}, @code{lrandom()}
                    684: is used.
                    685: \E
1.1       noro      686: @end itemize
                    687:
                    688: @example
                    689: [0] random_ff();
                    690: random_ff : current_ff is not set
                    691: return to toplevel
                    692: [0] setmod_ff(pari(nextprime,2^40));
                    693: 1099511627791
                    694: [1] random_ff();
                    695: 561856154357
                    696: [2] random_ff();
                    697: 45141628299
                    698: @end example
                    699:
                    700: @table @t
1.2       noro      701: \JP @item $B;2>H(B
                    702: \EG @item References
1.1       noro      703: @fref{setmod_ff}, @fref{random}, @fref{lrandom}
                    704: @end table
                    705:
1.2       noro      706: \JP @node lmptop,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    707: \EG @node lmptop,,, Functions for Finite fields
1.1       noro      708: @subsection @code{lmptop}
                    709: @findex lmptop
                    710:
                    711: @table @t
                    712: @item lmptop(@var{obj})
1.2       noro      713: \JP :: GF(p) $B78?tB?9`<0$N78?t$r@0?t$KJQ49(B
                    714: \EG :: Converts the coefficients of a polynomial over GF(p) into integers.
1.1       noro      715: @end table
                    716:
                    717: @table @var
                    718: @item return
1.2       noro      719: \JP $B@0?t78?tB?9`<0(B
                    720: \EG integral polynomial
1.1       noro      721: @item obj
1.2       noro      722: \JP GF(p) $B78?tB?9`<0(B
                    723: \EG polynomial over GF(p)
1.1       noro      724: @end table
                    725:
                    726: @itemize @bullet
1.2       noro      727: \BJP
1.1       noro      728: @item
                    729: GF(p) $B78?tB?9`<0$N78?t$r@0?t$KJQ49$9$k(B.
                    730: @item
                    731: GF(p) $B$N85$O(B, 0 $B0J>e(B p $BL$K~$N@0?t$GI=8=$5$l$F$$$k(B.
                    732: $BB?9`<0$N3F78?t$O(B, $B$=$NCM$r@0?t%*%V%8%'%/%H(B($B?t<1JL;R(B 0)$B$H$7$?$b$N$K(B
                    733: $BJQ49$5$l$k(B.
1.2       noro      734: \E
                    735: \BEG
                    736: @item
                    737: Converts the coefficients of a polynomial over GF(p) into integers.
1.1       noro      738: @item
1.2       noro      739: An element of GF(p) is represented by a non-negative integer @var{r} less than
                    740: @var{p}.
                    741: Each coefficient of a polynomial is converted into an integer object
                    742: whose value is @var{r}.
                    743: \E
1.1       noro      744: @end itemize
                    745:
                    746: @example
                    747: [0] setmod_ff(pari(nextprime,2^40));
                    748: 1099511627791
                    749: [1] F=simp_ff((x-1)^10);
                    750: 1*x^10+1099511627781*x^9+45*x^8+1099511627671*x^7+210*x^6
                    751: +1099511627539*x^5+210*x^4+1099511627671*x^3+45*x^2+1099511627781*x+1
                    752: [2] setmod_ff(547);
                    753: 547
                    754: [3] F=simp_ff((x-1)^10);
                    755: 1*x^10+537*x^9+45*x^8+427*x^7+210*x^6+295*x^5+210*x^4+427*x^3+45*x^2+537*x+1
                    756: [4] lmptop(F);
                    757: x^10+537*x^9+45*x^8+427*x^7+210*x^6+295*x^5+210*x^4+427*x^3+45*x^2+537*x+1
                    758: [5] lmptop(coef(F,1));
                    759: 537
                    760: [6] ntype(@@@@);
                    761: 0
                    762: @end example
                    763:
                    764: @table @t
1.2       noro      765: \JP @item $B;2>H(B
                    766: \EG @item References
1.1       noro      767: @fref{simp_ff}
                    768: @end table
                    769:
1.2       noro      770: \JP @node ntogf2n,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    771: \EG @node ntogf2n,,, Functions for Finite fields
1.1       noro      772: @subsection @code{ntogf2n}
                    773: @findex ntogf2n
                    774:
                    775: @table @t
                    776: @item ntogf2n(@var{m})
1.2       noro      777: \JP :: $B<+A3?t$r(B GF(2^n) $B$N85$KJQ49(B
                    778: \EG :: Converts a non-negative integer into an element of GF(2^n).
1.1       noro      779: @end table
                    780:
                    781: @table @var
                    782: @item return
1.2       noro      783: \JP GF(2^n) $B$N85(B
                    784: \EG element of GF(2^n)
1.1       noro      785: @item m
1.2       noro      786: \JP $BHsIi@0?t(B
                    787: \EG non-negative integer
1.1       noro      788: @end table
                    789:
                    790: @itemize @bullet
1.2       noro      791: \BJP
1.1       noro      792: @item
                    793: $B<+A3?t(B @var{m} $B$N(B 2 $B?JI=8=(B @var{m}=@var{m0}+@var{m1}*2+...+@var{mk}*2^k
                    794: $B$KBP$7(B, GF(2^n)=GF(2)[t]/(g(t)) $B$N85(B
                    795: @var{m0}+@var{m1}*t+...+@var{mk}*t^k mod g(t) $B$rJV$9(B.
                    796: @item
                    797: $BDj5AB?9`<0$K$h$k>jM>$O<+F0E*$K$O7W;;$5$l$J$$$?$a(B, @code{simp_ff()} $B$r(B
                    798: $BE,MQ$9$kI,MW$,$"$k(B.
1.2       noro      799: \E
                    800: \BEG
                    801: @item
                    802: Let @var{m} be a non-negative integer.
                    803: @var{m} has the binary representation
                    804: @var{m}=@var{m0}+@var{m1}*2+...+@var{mk}*2^k.
                    805: This function returns an element of  GF(2^n)=GF(2)[t]/(g(t)),
                    806: @var{m0}+@var{m1}*t+...+@var{mk}*t^k mod g(t).
                    807: @item
                    808: Apply @code{simp_ff()} to reduce the result.
                    809: \E
1.1       noro      810: @end itemize
                    811:
                    812: @example
                    813: [1] setmod_ff(x^30+x+1);
                    814: x^30+x+1
                    815: [2] N=ntogf2n(2^100);
                    816: (@@^100)
                    817: [3] simp_ff(N);
                    818: (@@^13+@@^12+@@^11+@@^10)
                    819: @end example
                    820:
                    821: @table @t
1.2       noro      822: \JP @item $B;2>H(B
                    823: \EG @item References
1.1       noro      824: @fref{gf2nton}
                    825: @end table
                    826:
1.2       noro      827: \JP @node gf2nton,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    828: \EG @node gf2nton,,, Functions for Finite fields
1.1       noro      829: @subsection @code{gf2nton}
                    830: @findex gf2nton
                    831:
                    832: @table @t
                    833: @item gf2nton(@var{m})
1.2       noro      834: \JP :: GF(2^n) $B$N85$r<+A3?t$KJQ49(B
                    835: \EG :: Converts an element of GF(2^n) into a non-negative integer.
1.1       noro      836: @end table
                    837:
                    838: @table @var
                    839: @item return
1.2       noro      840: \JP $BHsIi@0?t(B
                    841: \EG non-negative integer
1.1       noro      842: @item m
1.2       noro      843: \JP GF(2^n) $B$N85(B
                    844: \EG element of GF(2^n)
1.1       noro      845: @end table
                    846:
                    847: @itemize @bullet
                    848: @item
1.2       noro      849: \JP @code{gf2nton} $B$N5UJQ49$G$"$k(B.
                    850: \EG The inverse of @code{gf2nton}.
1.1       noro      851: @end itemize
                    852:
                    853: @example
                    854: [1] setmod_ff(x^30+x+1);
                    855: x^30+x+1
                    856: [2] N=gf2nton(2^100);
                    857: (@@^100)
                    858: [3] simp_ff(N);
                    859: (@@^13+@@^12+@@^11+@@^10)
                    860: [4] gf2nton(N);
                    861: 1267650600228229401496703205376
                    862: [5] gf2nton(simp_ff(N));
                    863: 15360
                    864: @end example
                    865:
                    866: @table @t
1.2       noro      867: \JP @item $B;2>H(B
                    868: \EG @item References
1.1       noro      869: @fref{gf2nton}
                    870: @end table
                    871:
1.2       noro      872: \JP @node ptogf2n,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    873: \EG @node ptogf2n,,, Functions for Finite fields
1.1       noro      874: @subsection @code{ptogf2n}
                    875: @findex ptogf2n
                    876:
                    877: @table @t
                    878: @item ptogf2n(@var{poly})
1.2       noro      879: \JP :: $B0lJQ?tB?9`<0$r(B GF(2^n) $B$N85$KJQ49(B
                    880: \EG :: Converts a univariate polynomial into an element of GF(2^n).
1.1       noro      881: @end table
                    882:
                    883: @table @var
                    884: @item return
1.2       noro      885: \JP GF(2^n) $B$N85(B
                    886: \EG element of GF(2^n)
1.1       noro      887: @item poly
1.2       noro      888: \JP $B0lJQ?tB?9`<0(B
                    889: \EG univariate polynomial
1.1       noro      890: @end table
                    891:
                    892: @itemize @bullet
                    893: @item
1.2       noro      894: \BJP
1.1       noro      895: @var{poly} $B$NI=$9(B GF(2^n) $B$N85$r@8@.$9$k(B. $B78?t$O(B, 2 $B$G3d$C$?M>$j$K(B
                    896: $BJQ49$5$l$k(B.
                    897: @var{poly} $B$NJQ?t$K(B @code{@@} $B$rBeF~$7$?7k2L$HEy$7$$(B.
1.2       noro      898: \E
                    899: \BEG
                    900: Generates an element of GF(2^n) represented by @var{poly}.
                    901: The coefficients are reduced modulo 2.
                    902: The output is equal to the result by substituting @code{@@} for
                    903: the variable of @var{poly}.
                    904: \E
1.1       noro      905: @end itemize
                    906:
                    907: @example
                    908: [1] setmod_ff(x^30+x+1);
                    909: x^30+x+1
                    910: [2] ptogf2n(x^100);
                    911: (@@^100)
                    912: @end example
                    913:
                    914: @table @t
1.2       noro      915: \JP @item $B;2>H(B
                    916: \EG @item References
1.1       noro      917: @fref{gf2ntop}
                    918: @end table
                    919:
1.2       noro      920: \JP @node gf2ntop,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    921: \EG @node gf2ntop,,, Functions for Finite fields
1.1       noro      922: @subsection @code{gf2ntop}
                    923: @findex gf2ntop
                    924:
                    925: @table @t
                    926: @item gf2ntop(@var{m}[,@var{v}])
1.2       noro      927: \JP :: GF(2^n) $B$N85$rB?9`<0$KJQ49(B
                    928: \EG :: Converts an element of GF(2^n) into a polynomial.
1.1       noro      929: @end table
                    930:
                    931: @table @var
                    932: @item return
1.2       noro      933: \JP $B0lJQ?tB?9`<0(B
                    934: \EG univariate polynomial
1.1       noro      935: @item m
1.2       noro      936: \JP GF(2^n) $B$N85(B
                    937: \EG an element of GF(2^n)
1.1       noro      938: @item v
1.2       noro      939: \JP $BITDj85(B
                    940: \EG indeterminate
1.1       noro      941: @end table
                    942:
                    943: @itemize @bullet
1.2       noro      944: \BJP
1.1       noro      945: @item
                    946: @var{m} $B$rI=$9B?9`<0$r(B, $B@0?t78?t$NB?9`<0%*%V%8%'%/%H$H$7$FJV$9(B.
1.2       noro      947: @item
                    948: @var{v} $B$N;XDj$,$J$$>l9g(B, $BD>A0$N(B @code{ptogf2n()} $B8F$S=P$7(B
1.1       noro      949: $B$K$*$1$k0z?t$NJQ?t(B ($B%G%U%)%k%H$O(B @code{x}), $B;XDj$,$"$k>l9g$K$O(B
                    950: $B;XDj$5$l$?ITDj85$rJQ?t$H$9$kB?9`<0$rJV$9(B.
1.2       noro      951: \E
                    952: \BEG
                    953: @item
                    954: Returns a polynomial representing @var{m}.
                    955: @item
                    956: If @var{v} is used as the variable of the output.
                    957: If @var{v} is not specified, the variable of the argument
                    958: of the latest @code{ptogf2n()} call. The default variable is @code{x}.
                    959: \E
1.1       noro      960: @end itemize
                    961:
                    962: @example
                    963: [1] setmod_ff(x^30+x+1);
                    964: x^30+x+1
                    965: [2] N=simp_ff(gf2ntop(2^100));
                    966: (@@^13+@@^12+@@^11+@@^10)
                    967: [5] gf2ntop(N);
                    968: [207] gf2ntop(N);
                    969: x^13+x^12+x^11+x^10
                    970: [208] gf2ntop(N,t);
                    971: t^13+t^12+t^11+t^10
                    972: @end example
                    973:
                    974: @table @t
1.2       noro      975: \JP @item $B;2>H(B
                    976: \EG @item References
1.1       noro      977: @fref{ptogf2n}
                    978: @end table
                    979:
1.2       noro      980: \JP @node defpoly_mod2,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                    981: \EG @node defpoly_mod2,,, Functions for Finite fields
1.1       noro      982: @subsection @code{defpoly_mod2}
                    983: @findex defpoly_mod2
                    984:
                    985: @table @t
                    986: @item defpoly_mod2(@var{d})
1.2       noro      987: \JP :: GF(2) $B>e4{Ls$J0lJQ?tB?9`<0$N@8@.(B
                    988: \EG :: Generates an irreducible univariate polynomial over GF(2).
1.1       noro      989: @end table
                    990:
                    991: @table @var
                    992: @item return
1.2       noro      993: \JP $BB?9`<0(B
                    994: \EG univariate polynomial
1.1       noro      995: @item d
1.2       noro      996: \JP $B@5@0?t(B
                    997: \EG positive integer
1.1       noro      998: @end table
                    999:
                   1000: @itemize @bullet
1.2       noro     1001: \BJP
1.1       noro     1002: @item
                   1003: @samp{fff} $B$GDj5A$5$l$F$$$k(B.
                   1004: @item
                   1005: $BM?$($i$l$?<!?t(B @var{d} $B$KBP$7(B, GF(2) $B>e(B @var{d} $B<!$N4{LsB?9`<0$rJV$9(B.
                   1006: @item
                   1007: $B$b$7(B $B4{Ls(B 3 $B9`<0$,B8:_$9$l$P(B, $BBh(B 2 $B9`$N<!?t$,$b$C$H$b>.$5$$(B 3 $B9`<0(B, $B$b$7(B $B4{Ls(B
                   1008: 3 $B9`<0$,B8:_$7$J$1$l$P(B, $B4{Ls(B 5 $B9`<0$NCf$G(B, $BBh(B 2 $B9`$N<!?t$,$b$C$H$b>.$5$/(B,
                   1009: $B$=$NCf$GBh(B 3 $B9`$N<!?t$,$b$C$H$b>.$5$/(B, $B$=$NCf$GBh(B 4 $B9`$N<!?t$,$b$C$H$b(B
                   1010: $B>.$5$$$b$N$rJV$9(B.
1.2       noro     1011: \E
                   1012: \BEG
                   1013: @item
                   1014: Defined in @samp{fff}.
                   1015: @item
                   1016: An irreducible univariate polynomial of degree @var{d} is returned.
                   1017: @item
                   1018: If an irreducible trinomial @var{x^d+x^m+1} exists, then the one
                   1019: with the smallest @var{m} is returned.
                   1020: Otherwise, an irreducible pentanomial @var{x^d+x^m1+x^m2+x^m3+1}
                   1021: (@var{m1>m2>m3} is returned.
                   1022: @var{m1}, @var{m2} and @var{m3} are determined as follows:
                   1023: Fix @var{m1} as small as possible. Then fix @var{m2} as small as possible.
                   1024: Then fix @var{m3} as small as possible.
                   1025: \E
1.1       noro     1026: @end itemize
                   1027:
                   1028: @example
                   1029: @end example
                   1030:
                   1031: @table @t
1.2       noro     1032: \JP @item $B;2>H(B
                   1033: \EG @item References
1.1       noro     1034: @fref{setmod_ff}
                   1035: @end table
                   1036:
1.2       noro     1037: \JP @node fctr_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                   1038: \EG @node fctr_ff,,, Functions for Finite fields
1.1       noro     1039: @subsection @code{fctr_ff}
                   1040: @findex fctr_ff
                   1041:
                   1042: @table @t
                   1043: @item fctr_ff(@var{poly})
1.2       noro     1044: \JP :: 1 $BJQ?tB?9`<0$NM-8BBN>e$G$N4{LsJ,2r(B
                   1045: \EG :: Irreducible univariate factorization over a finite field.
1.1       noro     1046: @end table
                   1047:
                   1048: @table @var
                   1049: @item return
1.2       noro     1050: \JP $B%j%9%H(B
                   1051: \EG list
1.1       noro     1052: @item poly
1.2       noro     1053: \JP $BM-8BBN>e$N(B 1 $BJQ?tB?9`<0(B
                   1054: \EG univariate polynomial over a finite field
1.1       noro     1055: @end table
                   1056:
                   1057: @itemize @bullet
1.2       noro     1058: \BJP
1.1       noro     1059: @item
                   1060: @samp{fff} $B$GDj5A$5$l$F$$$k(B.
                   1061: @item
                   1062: $B0lJQ?tB?9`<0$r(B, $B8=:_@_Dj$5$l$F$$$kM-8BBN>e$G4{LsJ,2r$9$k(B.
                   1063: @item
                   1064: $B7k2L$O(B, [[@var{f1},@var{m1}],[@var{f2},@var{m2}],...] $B$J$k(B
                   1065: $B%j%9%H$G$"$k(B. $B$3$3$G(B, @var{fi} $B$O(B monic $B$J4{Ls0x;R(B, @var{mi} $B$O$=$N(B
                   1066: $B=EJ#EY$G$"$k(B.
                   1067: @item
                   1068: @var{poly} $B$N<g78?t$O<N$F$i$l$k(B.
1.2       noro     1069: \E
                   1070: \BEG
                   1071: @item
                   1072: Defined in @samp{fff}.
                   1073: @item
                   1074: Factorize @var{poly} into irreducible factors over the current base field.
                   1075: @item
                   1076: The result is a list [[@var{f1},@var{m1}],[@var{f2},@var{m2}],...],
                   1077: where @var{fi} is a monic irreducible factor and @var{mi} is its
                   1078: multiplicity.
                   1079: @item
                   1080: The leading coefficient of @var{poly} is abandoned.
                   1081: \E
1.1       noro     1082: @end itemize
                   1083:
                   1084: @example
                   1085: [178] setmod_ff(2^64-95);
                   1086: 18446744073709551521
                   1087: [179]  fctr_ff(x^5+x+1);
                   1088: [[1*x+14123390394564558010,1],[1*x+6782485570826905238,1],
                   1089: [1*x+15987612182027639793,1],[1*x^2+1*x+1,1]]
                   1090: @end example
                   1091:
                   1092: @table @t
1.2       noro     1093: \JP @item $B;2>H(B
                   1094: \EG @item References
1.1       noro     1095: @fref{setmod_ff}
                   1096: @end table
                   1097:
1.2       noro     1098: \JP @node irredcheck_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                   1099: \EG @node irredcheck_ff,,, Functions for Finite fields
1.1       noro     1100: @subsection @code{irredcheck_ff}
                   1101: @findex irredcheck_ff
                   1102:
                   1103: @table @t
                   1104: @item irredcheck_ff(@var{poly})
1.2       noro     1105: \JP :: 1 $BJQ?tB?9`<0$NM-8BBN>e$G$N4{LsH=Dj(B
                   1106: \EG :: Primality check of a univariate polynomial over a finite field.
1.1       noro     1107: @end table
                   1108:
                   1109: @table @var
                   1110: @item return
                   1111: 0|1
                   1112: @item poly
1.2       noro     1113: \JP $BM-8BBN>e$N(B 1 $BJQ?tB?9`<0(B
                   1114: \EG univariate polynomial over a finite field
1.1       noro     1115: @end table
                   1116:
                   1117: @itemize @bullet
1.2       noro     1118: \BJP
1.1       noro     1119: @item
                   1120: @samp{fff} $B$GDj5A$5$l$F$$$k(B.
                   1121: @item
                   1122: $BM-8BBN>e$N(B 1 $BJQ?tB?9`<0$N4{LsH=Dj$r9T$$(B, $B4{Ls$N>l9g(B 1, $B$=$l0J30$O(B 0 $B$rJV$9(B.
1.2       noro     1123: \E
                   1124: \BEG
                   1125: @item
                   1126: Defined in @samp{fff}.
                   1127: @item
                   1128: Returns 1 if @var{poly} is irreducible over the current base field.
                   1129: Returns 0 otherwise.
                   1130: \E
1.1       noro     1131: @end itemize
                   1132:
                   1133: @example
                   1134: [178] setmod_ff(2^64-95);
                   1135: 18446744073709551521
                   1136: [179] ] F=x^10+random_ff();
                   1137: x^10+14687973587364016969
                   1138: [180] irredcheck_ff(F);
                   1139: 1
                   1140: @end example
                   1141:
                   1142: @table @t
1.2       noro     1143: \JP @item $B;2>H(B
                   1144: \EG @item References
1.1       noro     1145: @fref{setmod_ff}
                   1146: @end table
                   1147:
1.2       noro     1148: \JP @node randpoly_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                   1149: \EG @node randpoly_ff,,, Functions for Finite fields
1.1       noro     1150: @subsection @code{randpoly_ff}
                   1151: @findex randpoly_ff
                   1152:
                   1153: @table @t
                   1154: @item randpoly_ff(@var{d},@var{v})
1.2       noro     1155: \JP :: $BM-8BBN>e$N(B $BMp?t78?t(B 1 $BJQ?tB?9`<0$N@8@.(B
                   1156: \EG :: Generation of a random univariate polynomial over a finite field.
1.1       noro     1157: @end table
                   1158:
                   1159: @table @var
                   1160: @item return
1.2       noro     1161: \JP $BB?9`<0(B
                   1162: \EG polynomial
1.1       noro     1163: @item d
1.2       noro     1164: \JP $B@5@0?t(B
                   1165: \EG positive integer
1.1       noro     1166: @item v
1.2       noro     1167: \JP $BITDj85(B
                   1168: \EG indeterminate
1.1       noro     1169: @end table
                   1170:
                   1171: @itemize @bullet
1.2       noro     1172: \BJP
1.1       noro     1173: @item
                   1174: @samp{fff} $B$GDj5A$5$l$F$$$k(B.
                   1175: @item
                   1176: @var{d} $B<!L$K~(B, $BJQ?t$,(B @var{v}, $B78?t$,8=:_@_Dj$5$l$F$$$kM-8BBN$KB0$9$k(B
                   1177: 1 $BJQ?tB?9`<0$r@8@.$9$k(B. $B78?t$O(B @code{random_ff()} $B$K$h$j@8@.$5$l$k(B.
1.2       noro     1178: \E
                   1179: \BEG
                   1180: @item
                   1181: Defined in @samp{fff}.
                   1182: @item
                   1183: Generates a polynomial of @var{v} such that the degree is less than @var{d}
                   1184: and the coefficients are in the current base field.
                   1185: The coefficients are generated by @code{random_ff()}.
                   1186: \E
1.1       noro     1187: @end itemize
                   1188:
                   1189: @example
                   1190: [178] setmod_ff(2^64-95);
                   1191: 18446744073709551521
                   1192: [179] ] F=x^10+random_ff();
                   1193: [180] randpoly_ff(3,x);
                   1194: 17135261454578964298*x^2+4766826699653615429*x+18317369440429479651
                   1195: [181] randpoly_ff(3,x);
                   1196: 7565988813172050604*x^2+7430075767279665339*x+4699662986224873544
                   1197: [182] randpoly_ff(3,x);
                   1198: 10247781277095450395*x^2+10243690944992524936*x+4063829049268845492
                   1199: @end example
                   1200:
                   1201: @table @t
1.2       noro     1202: \JP @item $B;2>H(B
                   1203: \EG @item References
1.1       noro     1204: @fref{setmod_ff}, @fref{random_ff}
                   1205: @end table
                   1206:
1.2       noro     1207: \JP @node ecm_add_ff ecm_sub_ff ecm_chsgn_ff,,, $BM-8BBN$K4X$9$kH!?t$N$^$H$a(B
                   1208: \EG @node ecm_add_ff ecm_sub_ff ecm_chsgn_ff,,, Functions for Finite fields
1.1       noro     1209: @subsection @code{ecm_add_ff}, @code{ecm_sub_ff}, @code{ecm_chsgn_ff}
                   1210: @findex ecm_add_ff
                   1211: @findex ecm_sub_ff
                   1212: @findex ecm_chsgn_ff
                   1213:
                   1214: @table @t
                   1215: @item ecm_add_ff(@var{p1},@var{p2},@var{ec})
                   1216: @itemx ecm_sub_ff(@var{p1},@var{p2},@var{ec})
1.3       noro     1217: @itemx ecm_chsgn_ff(@var{p1})
1.2       noro     1218: \JP :: $BBJ1_6J@~>e$NE@$N2C;;(B, $B8:;;(B, $B5U85(B
                   1219: \EG :: Addition, Subtraction and additive inverse for points on an elliptic curve.
1.1       noro     1220: @end table
                   1221:
                   1222: @table @var
                   1223: @item return
1.2       noro     1224: \JP $B%Y%/%H%k$^$?$O(B 0
                   1225: \EG vector or 0
1.1       noro     1226: @item p1,p2
1.2       noro     1227: \JP $BD9$5(B 3 $B$N%Y%/%H%k$^$?$O(B 0
                   1228: \EG vector of length 3 or 0
1.1       noro     1229: @item ec
1.2       noro     1230: \JP $BD9$5(B 2 $B$N%Y%/%H%k(B
                   1231: \EG vector of length 2
1.1       noro     1232: @end table
                   1233:
                   1234: @itemize @bullet
1.2       noro     1235: \BJP
1.1       noro     1236: @item
                   1237: $B8=:_@_Dj$5$l$F$$$kM-8BBN>e$G(B,  @var{ec} $B$GDj5A$5$l$kBJ1_6J@~>e$N(B
                   1238: $BE@(B @var{p1}, @var{p2} $B$NOB(B @var{p1+p2}, $B:9(B @var{p1-p2}, $B5U85(B @var{-p1} $B$rJV$9(B.
                   1239: @item
                   1240: @var{ec} $B$O(B, $B@_Dj$5$l$F$$$kM-8BBN$,4qI8?tAGBN$N>l9g(B,
                   1241: @var{y^2=x^3+ec[0]x+ec[1]}, $BI8?t(B 2 $B$N>l9g(B @var{y^2+xy=x^3+ec[0]x^2+ec[1]}
                   1242: $B$rI=$9(B.
                   1243: @item
                   1244: $B0z?t(B, $B7k2L$H$b$K(B, $BL58B1sE@$O(B 0 $B$GI=$5$l$k(B.
                   1245: @item
                   1246: @var{p1}, @var{p2} $B$,D9$5(B 3 $B$N%Y%/%H%k$N>l9g(B, $B@F<!:BI8$K$h$k6J@~>e$N(B
                   1247: $BE@$rI=$9(B. $B$3$N>l9g(B, $BBh(B 3 $B:BI8$O(B 0 $B$G$"$C$F$O$$$1$J$$(B.
                   1248: @item
                   1249: $B7k2L$,D9$5(B 3 $B$N%Y%/%H%k$N>l9g(B, $BBh(B 3 $B:BI8$O(B 0 $B$G$J$$$,(B, 1 $B$H$O8B$i$J$$(B.
                   1250: $B%"%U%#%s:BI8$K$h$k7k2L$rF@$k$?$a$K$O(B, $BBh(B 1 $B:BI8(B, $BBh(B 2 $B:BI8$rBh(B 3 $B:BI8(B
                   1251: $B$G3d$kI,MW$,$"$k(B.
                   1252: @item
                   1253: @var{p1}, @var{p2} $B$,BJ1_6J@~>e$NE@$+$I$&$+$N%A%'%C%/$O$7$J$$(B.
1.2       noro     1254: \E
                   1255: \BEG
                   1256: @item
                   1257: Let @var{p1}, @var{p2} be points on the elliptic curve represented by
                   1258: @var{ec} over the current base field.
                   1259: ecm_add_ff(@var{p1},@var{p2},@var{ec}), ecm_sub_ff(@var{p1},@var{p2},@var{ec})
1.3       noro     1260: and ecm_chsgn_ff(@var{p1}) returns
1.2       noro     1261: @var{p1+p2}, @var{p1-p2} and @var{-p1} respectively.
                   1262: @item
                   1263: If the current base field is a prime field of odd order, then
                   1264: @var{ec} represents @var{y^2=x^3+ec[0]x+ec[1]}.
                   1265: If the characteristic of the current base field is 2,
                   1266: then @var{ec} represents @var{y^2+xy=x^3+ec[0]x^2+ec[1]}.
                   1267: @item
                   1268: The point at infinity is represented by 0.
                   1269: @item
                   1270: If an argument denoting a point is a vector of length 3,
                   1271: then it is the projective coordinate. In such a case
                   1272: the third coordinate must not be 0.
                   1273: @item
                   1274: If the result is a vector of length 3, then the third coordinate
                   1275: is not equal to 0 but not necessarily 1. To get the result by
                   1276: the affine coordinate, the first and the second coordinates should
                   1277: be divided by the third coordinate.
                   1278: @item
                   1279: The check whether the arguments are on the curve is omitted.
                   1280: \E
1.1       noro     1281: @end itemize
                   1282:
                   1283: @example
                   1284: [0] setmod_ff(1125899906842679)$
                   1285: [1] EC=newvect(2,[ptolmp(1),ptolmp(1)])$
                   1286: [2] Pt1=newvect(3,[1,-412127497938252,1])$
                   1287: [3] Pt2=newvect(3,[6,-252647084363045,1])$
                   1288: [4] Pt3=ecm_add_ff(Pt1,Pt2,EC);
                   1289: [ 560137044461222 184453736165476 125 ]
                   1290: [5] F=y^2-(x^3+EC[0]*x+EC[1])$
                   1291: [6] subst(F,x,Pt3[0]/Pt3[2],y,Pt3[1]/Pt3[2]);
                   1292: 0
                   1293: [7] ecm_add_ff(Pt3,ecm_chsgn_ff(Pt3),EC);
                   1294: 0
                   1295: [8] D=ecm_sub_ff(Pt3,Pt2,EC);
                   1296: [ 886545905133065 119584559149586 886545905133065 ]
                   1297: [9] D[0]/D[2]==Pt1[0]/Pt1[2];
                   1298: 1
                   1299: [10] D[1]/D[2]==Pt1[1]/Pt1[2];
                   1300: 1
                   1301: @end example
                   1302:
                   1303: @table @t
1.2       noro     1304: \JP @item $B;2>H(B
                   1305: \EG @item References
1.1       noro     1306: @fref{setmod_ff}
                   1307: @end table
                   1308:

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