File Coverage

blib/lib/Math/Polynomial/Cyclotomic.pm
Criterion Covered Total %
statement 218 218 100.0
branch 82 82 100.0
condition 48 53 90.5
subroutine 29 29 100.0
pod 8 16 50.0
total 385 398 96.7


line stmt bran cond sub pod time code
1             # Copyright (c) 2019-2021 by Martin Becker. This package is free software,
2             # licensed under The Artistic License 2.0 (GPL compatible).
3              
4             package Math::Polynomial::Cyclotomic;
5              
6 3     3   24970 use 5.006;
  3         23  
7 3     3   16 use strict;
  3         6  
  3         66  
8 3     3   14 use warnings;
  3         7  
  3         109  
9 3     3   18 use Carp qw(croak);
  3         7  
  3         218  
10 3     3   4014 use Math::BigInt try => 'GMP';
  3         100816  
  3         16  
11 3     3   84213 use Math::Polynomial 1.014;
  3         7662  
  3         114  
12 3         17 use Math::Prime::Util qw(
13             divisors factor factor_exp euler_phi gcd is_square_free is_power
14             moebius kronecker vecprod
15 3     3   3926 );
  3         34576  
16             require Exporter;
17              
18             our @ISA = qw(Exporter);
19             our @EXPORT_OK = qw(
20             cyclo_poly cyclo_factors cyclo_plusfactors cyclo_poly_iterate
21             cyclo_lucas_cd cyclo_schinzel_cd cyclo_int_factors cyclo_int_plusfactors
22             );
23             our %EXPORT_TAGS = (all => \@EXPORT_OK);
24             our $VERSION = '0.003';
25              
26             # some polynomial with coefficient type Math::BigInt
27             my $default = Math::Polynomial->new(Math::BigInt->new('1'));
28             $default->string_config({fold_sign => 1, times => '*'});
29              
30             # ----- private subroutines -----
31              
32             sub _cyclo_poly {
33 118     118   286 my ($poly, $table, $n, $divisors) = @_;
34 118 100       425 return $table->{$n} if exists $table->{$n};
35 62         360 my $m = vecprod(map { $_->[0] } factor_exp($n)); # $m = radix($n)
  81         276  
36 62         174 my $o = $m & 1;
37 62 100       160 $m >>= 1 if !$o;
38 62         101 my $p;
39 62 100       158 if (exists $table->{$m}) {
40 26         52 $p = $table->{$m};
41             }
42             else {
43 36         120 my $one = $poly->coeff_one;
44 36 100       309 my @d = $divisors? (grep { not $m % $_ } @{$divisors}): divisors($m);
  116         237  
  23         49  
45 36         123 $p = $poly->monomial(pop @d)->sub_const($one);
46 36 100       10299 if (@d) {
47 26         62 my $b = $d[-1];
48 26         74 $p /= $poly->monomial($b)->sub_const($one);
49 26         346737 for (my $i = 1; $i < $#d; ++$i) {
50 11         78277 my $r = $d[$i];
51 11 100       52 if ($b % $r) {
52 9   66     68 $p /= $table->{$r} || _cyclo_poly($poly, $table, $r, \@d);
53             }
54             }
55             }
56 36         94588 $table->{$m} = $p;
57             }
58 62 100       167 if (!$o) {
59 29 100       90 $p = -$p if $m == 1;
60 29         1403 $m <<= 1;
61 29         92 $p = $p->mirror;
62 29         2952 $table->{$m} = $p;
63             }
64 62 100       153 if ($m != $n) {
65 21         89 $p = $p->inflate($n/$m);
66 21         1694 $table->{$n} = $p;
67             }
68 62         261 return $p;
69             }
70              
71             # for a positive integer n, return r,s so that r is square-free and n=rs^2
72             sub _square_free_square {
73 16     16   31 my ($n) = @_;
74 16         34 my ($r, $s) = (1, 1);
75 16         105 foreach my $be (factor_exp($n)) {
76 27         48 my ($b, $e) = @{$be};
  27         51  
77 27 100       62 $r *= $b if $e & 1;
78 27         40 $e >>= 1;
79 27         61 while ($e) {
80 7 100       18 $s *= $b if $e & 1;
81 7 100       23 $e >>= 1 and $b *= $b;
82             }
83             }
84 16         41 return ($r, $s);
85             }
86              
87             # generate polynomials C, D, satisfying the identity of Aurifeuille,
88             # Le Lasseur and Lucas: for n > 1, square-free,
89             # n === 1 (mod 4): Phi_n(x) = C^2 - n*x*D^2
90             # else: Phi_2n(x) = C^2 - n*x*D^2
91             sub _lucas_cd {
92 10     10   24 my ($poly, $table, $n) = @_;
93 10         25 my $c1 = 1 == ($n & 3);
94 10 100       26 my $n1 = $c1? $n: $n + $n;
95 10 100       33 if (exists $table->{"$n1 $n"}) {
96 3         7 return (@{$table->{"$n1 $n"}})
  3         14  
97             }
98 7         23 my $c2 = !($n & 1);
99 7         26 my $ee = euler_phi($n1);
100 7         15 my $e = $ee >> 1;
101 7         24 my $one = $poly->coeff_one;
102 7         69 my $nul = $poly->coeff_zero;
103              
104 7         24 my $E = $e | 1;
105 7         17 my @q = ($one);
106 7         13 my $cos = $one;
107 7         15 my %MP = ();
108 7         16 for (my $k = 2; $k <= $E; ++$k) {
109 30 100       2419 if ($k & 1) {
110 15         64 push @q, $nul + kronecker($n, $k);
111 15         2940 next;
112             }
113 15 100 100     50 if ($c2 && $k & 2) {
114 2         4 push @q, $nul;
115 2         5 next;
116             }
117 13 100       38 $cos = -$cos if !$c1; # $cos is cos((n-1)*k*pi/4)
118 13         420 my $gk = gcd($n1, $k);
119 13   66     98 my $mp = $MP{$gk} ||= moebius($n1 / $gk) * euler_phi($gk);
120 13         88 push @q, $cos * $mp;
121             }
122              
123 7         16 my @cs = ($one);
124 7         12 my @ds = ($one);
125 7         18 $cs[$e] = $ds[$e-1] = $one;
126 7         22 for(my $k = 1, my $kk = $e - 1; $k <= $kk; ++$k, --$kk) {
127 15         3283 my ($c, $d) = ($nul, $nul);
128 15         38 for (my $i = 0, my $j = $k-1; $j >= 0; $i += 2, --$j) {
129 37         6701 my $cc = $cs[$j];
130 37         58 my $dd = $ds[$j];
131 37         80 my ($q1, $q2) = @q[$i, $i+1];
132 37         91 $c += $q1 * $n * $dd - $q2 * $cc;
133 37         17510 $d += $q[$i+2] * $cc - $q2 * $dd;
134             }
135 15         4376 $c /= ($k + $k);
136 15         3667 $cs[$k] = $cs[$kk] = $c;
137 15 100       58 $ds[$k] = $ds[$kk-1] = ($d + $c) / ($k + $k + 1) if $k < $kk;
138             }
139              
140 7         27 my $cp = $poly->new(@cs);
141 7         363 my $dp = $poly->new(@ds);
142 7         284 $table->{"$n1 $n"} = [$cp, $dp];
143 7         50 return ($cp, $dp);
144             }
145              
146             # generate polynomials C, D, satisfying the identity of Beeger and Schinzel:
147             # for k > 1, square-free, k1 = k (if k === 1 (mod 4)), k1 = 2*k (else),
148             # n = odd multiple of k1: Phi_n(x) = C^2 - k*x*D^2
149             sub _schinzel_cd {
150 25     25   60 my ($poly, $table, $n, $k) = @_;
151 25 100       73 my $K = ($k & 3) == 1? $k: $k << 1;
152 25         51 my $f = $n / $K;
153 25 100       63 return () if not $f & 1;
154 23         113 my $r = vecprod(map { $_->[0] } factor_exp($f));
  10         40  
155 23         85 my $m = $f / $r * gcd($f, $k);
156 23 100       58 if ($m > 1) {
157 3         8 $n /= $m;
158 3         6 $f /= $m;
159             }
160 23         45 my ($C, $D) = ();
161 23 100       99 if (exists $table->{"$n $k"}) {
162 17         25 ($C, $D) = @{$table->{"$n $k"}};
  17         57  
163             }
164             else {
165 6         22 ($C, $D) = _lucas_cd($poly, $table, $k);
166 6         15 my ($L, $M, $Q) = ();
167 6         29 foreach my $p (factor($f)) {
168 6         10284 my $p2 = $p >> 1;
169 6         21 my $kp2 = Math::BigInt->new($k)->bpow($p2);
170 6 100       2216 if (!defined $M) {
171 5         19 $Q = $poly->monomial(2, $k);
172 5         812 my $CC = $C->nest($Q);
173 5         20527 my $DD = $D->nest($Q)->shift_up(1)->mul_const($k);
174 5         16658 $L = $CC - $DD;
175 5         2615 $M = $CC + $DD;
176             }
177 6 100       2215 if (kronecker($k, $p) < 0) {
178 5         17 ($L, $M) = (
179             $L->nest($poly->monomial($p, $kp2)) / $M,
180             $M->nest($poly->monomial($p, $kp2)) / $L,
181             );
182             }
183             else {
184 1         6 ($L, $M) = (
185             $M->nest($poly->monomial($p, $kp2)) / $M,
186             $L->nest($poly->monomial($p, $kp2)) / $L,
187             );
188             }
189             }
190 6 100       459108 if (defined $M) {
191 5         23 $C = ($M + $L)->div_const(2)->unnest($Q);
192 5         152033 $D = (($M - $L) / $poly->monomial(1, $k << 1))->unnest($Q);
193 5         131699 $table->{"$n $k"} = [$C, $D];
194             }
195             }
196 23 100       68 if ($m > 1) {
197 3         15 $C = $C->inflate($m);
198 3         274 $D = $D->inflate($m)->shift_up($m >> 1);
199             }
200 23         401 return ($C, $D);
201             }
202              
203             # for r > 1, integer, square-free, s > 0, integer, x = r*s^2,
204             # r1 = r (if r === 1 (mod 4)), r1 = 2*r (else), n = odd multiple of r1,
205             # generate integer factors l < m such that l * m = Phi_n(x).
206             # if l = 1, return (m) else (l, m).
207             sub _schinzel_lm {
208 16     16   42 my ($poly, $table, $n, $r, $s, $x) = @_;
209 16         41 my ($c, $d) = _schinzel_cd($poly, $table, $n, $r);
210 16         49 my $cx = $c->evaluate($x);
211 16         18213 my $dx = $d->evaluate($x) * $r * $s;
212 16         19341 my ($l, $m) = ($cx - $dx, $cx + $dx);
213 16 100       3131 return $m if $l == $poly->coeff_one;
214 14         587 return ($l, $m);
215             }
216              
217             # ----- Math::Polynomial extension -----
218              
219             sub Math::Polynomial::cyclotomic {
220 12     12 0 6491 my ($this, $n, $table) = @_;
221 12   100     78 return _cyclo_poly($this, $table || {}, $n);
222             }
223              
224             sub Math::Polynomial::cyclo_factors {
225 6     6 0 6931 my ($this, $n, $table) = @_;
226 6         42 my @d = divisors($n);
227 6   100     31 $table ||= {};
228 6         14 return map { _cyclo_poly($this, $table, $_, \@d) } @d;
  28         63  
229             }
230              
231             sub Math::Polynomial::cyclo_int_factors {
232 13     13 0 65 my ($this, $x, $n, $table) = @_;
233 13 100 100     70 return ($this->coeff_zero) if !$n || $x == $this->coeff_one;
234 11 100 100     1709 return ($x - $this->coeff_one) if $n == 1 || !$x;
235 9   50     27 $table ||= {};
236 9 100       65 if (my $exp = is_power($x, 0, \my $root)) {
237 2         4 $x = $root;
238 2         5 $n *= $exp;
239             }
240 9         26 my ($r, $s) = _square_free_square($x);
241 9 100       28 my $r1 = (1 == ($r & 3))? $r: $r+$r;
242 9         51 my @d = divisors($n);
243 9   100     36 my $i = $x == 2 || 0;
244             return
245             map {
246 9 100 100     31 !($_ % $r1) && ($_ / $r1) & 1?
  45         22791  
247             _schinzel_lm($this, $table, $_, $r, $s, $x):
248             (_cyclo_poly($this, $table, $_, \@d))->evaluate($x)
249             } @d[$i .. $#d];
250             }
251              
252             sub Math::Polynomial::cyclo_plusfactors {
253 4     4 0 668 my ($this, $n, $table) = @_;
254 4         30 my @d = divisors($n << 1);
255 4         13 my $m = $n ^ ($n - 1);
256 4   100     22 $table ||= {};
257             return
258 8         21 map { _cyclo_poly($this, $table, $_, \@d) }
259 4         11 grep { !($_ & $m) } @d;
  20         45  
260             }
261              
262             sub Math::Polynomial::cyclo_int_plusfactors {
263 11     11 0 26 my ($this, $x, $n, $table) = @_;
264 11         35 my $u = $this->coeff_one;
265 11 100       54 return ($u + $u) if !$n;
266 10 100 100     63 return ($x + $u) if $n == 1 || !$x || $x == $u;
      100        
267 7 100       974 if (my $exp = is_power($x, 0, \my $root)) {
268 2         5 $x = $root;
269 2         5 $n *= $exp;
270             }
271 7         18 my ($r, $s) = _square_free_square($x);
272 7 100       21 my $r1 = (1 == ($r & 3))? $r: $r+$r;
273 7         39 my @d = divisors($n << 1);
274 7         16 my $m = $n ^ ($n - 1);
275 7   50     17 $table ||= {};
276             return
277             map {
278 23 100 100     12565 !($_ % $r1) && ($_ / $r1) & 1?
279             _schinzel_lm($this, $table, $_, $r, $s, $x):
280             (_cyclo_poly($this, $table, $_, \@d))->evaluate($x)
281 7         15 } grep { !($_ & $m) } @d;
  58         107  
282             }
283              
284             sub Math::Polynomial::cyclo_lucas_cd {
285 6     6 0 16 my ($this, $n, $table) = @_;
286 6 100 100     51 if ($n <= 1 || !is_square_free($n)) {
287 2         331 croak "$n: not a square-free integer greater than one";
288             }
289 4   50     15 return _lucas_cd($this, $table || {}, $n);
290             }
291              
292             sub Math::Polynomial::cyclo_schinzel_cd {
293 11     11 0 32 my ($this, $n, $k, $table) = @_;
294 11 100 100     82 if ($k <= 1 || !is_square_free($k)) {
295 2         205 croak "$k: not a square-free integer greater than one";
296             }
297 9   100     39 my @cd = _schinzel_cd($this, $table || {}, $n, $k);
298 9 100       27 if (!@cd) {
299 2 100       8 my $k1 = ($k & 3) == 1? 'k': '2*k';
300 2         205 croak "$n: n is not an odd multiple of $k1";
301             }
302 7         33 return @cd;
303             }
304              
305             sub Math::Polynomial::cyclo_poly_iterate {
306 4     4 0 2062 my ($this, $n, $table) = @_;
307 4   100     21 $n ||= 1;
308 4         9 --$n;
309 4   100     41 $table ||= {};
310             return
311             sub {
312 14     14   8670 ++$n;
313 14         40 _cyclo_poly($this, $table, $n);
314 4         42 };
315             }
316              
317             # ----- public subroutines -----
318              
319 9     9 1 8442 sub cyclo_poly { $default->cyclotomic(@_) }
320 2     2 1 2150 sub cyclo_factors { $default->cyclo_factors(@_) }
321 3     3 1 2571 sub cyclo_plusfactors { $default->cyclo_plusfactors(@_) }
322 2     2 1 1354 sub cyclo_poly_iterate { $default->cyclo_poly_iterate(@_) }
323 6     6 1 9994 sub cyclo_lucas_cd { $default->cyclo_lucas_cd(@_) }
324 11     11 1 13090 sub cyclo_schinzel_cd { $default->cyclo_schinzel_cd(@_) }
325 13     13 1 10128 sub cyclo_int_factors { $default->cyclo_int_factors(@_) }
326 11     11 1 16143 sub cyclo_int_plusfactors { $default->cyclo_int_plusfactors(@_) }
327              
328             1;
329              
330             __END__