File Coverage

blib/lib/Math/BigNum.pm
Criterion Covered Total %
statement 12 14 85.7
branch n/a
condition n/a
subroutine 5 5 100.0
pod n/a
total 17 19 89.4


line stmt bran cond sub pod time code
1             package Math::BigNum;
2              
3 1     1   13608 use 5.014;
  1         2  
4 1     1   3 use strict;
  1         1  
  1         15  
5 1     1   2 use warnings;
  1         3  
  1         25  
6              
7 1     1   3 no warnings 'numeric';
  1         1  
  1         22  
8              
9 1     1   222 use Math::GMPq qw();
  0            
  0            
10             use Math::GMPz qw();
11             use Math::MPFR qw();
12              
13             use Class::Multimethods qw();
14              
15             #<<<
16             use constant {
17             #MAX_UI => unpack('I', pack 'I', -1), # UP: ~0
18             #MIN_SI => 0.5 * (-1 - unpack('I', pack 'I', -1)), # UP: -(~0 >> 1) - 1
19              
20             MAX_UI => Math::GMPq::_ulong_max(),
21             MIN_SI => Math::GMPq::_long_min(),
22             };
23             #>>>
24              
25             our $VERSION = '0.18';
26              
27             =encoding utf8
28              
29             =head1 NAME
30              
31             Math::BigNum - Arbitrary size precision for integers, rationals and floating-point numbers.
32              
33             =head1 VERSION
34              
35             Version 0.18
36              
37             =head1 SYNOPSIS
38              
39             use 5.014;
40             use Math::BigNum qw(:constant);
41              
42             # Big numbers
43             say ((100->fac + 1) / 2);
44             # => 466631077219720763408496194281333502453579841321908107 \
45             # 342964819476087999966149578044707319880782591431268489 \
46             # 60413611879125592605458432000000000000000000000000.5
47              
48             # Small numbers
49             say sqrt(1 / 100->fac); # => 1.03513781117562647132049[...]e-79
50              
51             # Rational numbers
52             my $x = 2/3;
53             say $x*3; # => 2
54             say 2/$x; # => 3
55             say $x->as_frac; # => "2/3"
56              
57             # Floating-point numbers
58             say "equal" if (1.1 + 2.2 == 3.3); # => "equal"
59              
60             =head1 DESCRIPTION
61              
62             Math::BigNum provides a transparent interface to Math::GMPz, Math::GMPq and Math::MPFR, focusing
63             on performance and easy-to-use. In most cases, it can be used as a drop-in replacement for the
64             L and L pragmas.
65              
66             =head1 MOTIVATION
67              
68             This module came into existence as a response to Dana Jacobsen's request for a transparent
69             interface to L and L, which he talked about at the YAPC NA, in 2015.
70              
71             See his great presentation at: L.
72              
73             The main aim of this module is to provide a fast and correct alternative to L,
74             L and L, as well as to L, L and L pragmas.
75              
76             =head1 HOW IT WORKS
77              
78             Math::BigNum tries really hard to do the right thing and as efficiently as possible.
79             For example, when computing C, it first checks to see if C and C are integers,
80             so it can optimize the operation to integer exponentiation, by calling the corresponding
81             I function. When only C is an integer, it does rational exponentiation based on the
82             identity: I<(a/b)^n = a^n / b^n>. Otherwise, it will fallback to floating-point exponentiation,
83             using the corresponding I function.
84              
85             All numbers in Math::BigNum are stored as rational L objects. Each operation,
86             outside the functions provided by L, is done by converting the internal objects to
87             L or L objects and calling the corresponding functions, converting
88             the results back to L objects, without loosing any precision in the process.
89              
90             =head1 IMPORT / EXPORT
91              
92             Math::BigNum does not export anything by default, but it recognizes the followings:
93              
94             :constant # will make any number a Math::BigNum object
95             # it will also export the "Inf" and "NaN" constants,
96             # which represent +Infinity and NaN special values
97              
98             :all # export everything that is exportable
99             PREC n # set the global precision to the value of `n`
100              
101             B
102              
103             e # "e" constant (2.7182...)
104             pi # "pi" constant (3.1415...)
105             tau # "tau" constant (which is: 2*pi)
106             phi # Golden ratio constant (1.618...)
107             G # Catalan's constant (0.91596...)
108             Y # Euler-Mascheroni constant (0.57721...)
109             Inf # +Infinity constant
110             NaN # Not-a-Number constant
111              
112             B
113              
114             factorial(n) # product of first n integers: n!
115             primorial(n) # product of primes <= n
116             binomial(n,k) # binomial coefficient
117             fibonacci(n) # nth-Fibonacci number
118             lucas(n) # nth-Lucas number
119             ipow(a,k) # integer exponentiation: a^k
120              
121             B this functions are designed and optimized for native Perl integers as input.
122              
123             The syntax for importing something, is:
124              
125             use Math::BigNum qw(:constant pi factorial);
126             say cos(2*pi); # => 1
127             say factorial(5); # => 120
128              
129             B C<:constant> is lexical to the current scope only.
130              
131             The syntax for disabling the C<:constant> behavior in the current scope, is:
132              
133             no Math::BigNum; # :constant will be disabled in the current scope
134              
135             =head1 PRECISION
136              
137             The default precision for floating-point numbers is 200 bits, which is equivalent with about
138             50 digits of precision in base 10.
139              
140             The precision can be changed by modifying the C<$Math::BigNum::PREC> variable, such as:
141              
142             local $Math::BigNum::PREC = 1024;
143              
144             or by specifying the precision at import (this sets the precision globally):
145              
146             use Math::BigNum PREC => 1024;
147              
148             However, an important thing to take into account, unlike the L objects, Math::BigNum
149             objects do not have a fixed precision stored inside. Rather, they can grow or shrink dynamically,
150             regardless of the global precision.
151              
152             The global precision controls only the precision of the floating-point functions and the
153             stringification of floating-point numbers.
154              
155             For example, if we change the precision to 3 decimal digits (where C<4> is the conversion factor),
156             we get the following results:
157              
158             local $Math::BigNum::PREC = 3*4;
159             say sqrt(2); # => 1.414
160             say 98**7; # => 86812553324672
161             say 1 / 98**7 # => 1.15e-14
162              
163             As shown above, integers do not obey the global precision, because they can grow or shrink
164             dynamically, without a specific limit. This is true for rational numbers as well.
165              
166             A rational number never losses precision in rational operations, therefore if we say:
167              
168             my $x = 1 / 3;
169             say $x * 3; # => 1
170             say 1 / $x; # => 3
171             say 3 / $x; # => 9
172              
173             ...the results are 100% exact.
174              
175             =head1 NOTATIONS
176              
177             Methods that begin with a B followed by the actual name (e.g.: C), are mutable
178             methods that change the self object in-place, while their counter-parts (e.g.: C)
179             do not. Instead, they will create and return a new object.
180              
181             In addition, Math::BigNum features another kind of methods that begin with an B followed by
182             the actual name (e.g.: C). This methods do integer operations, by first
183             truncating their arguments to integers, whenever needed.
184              
185             Lastly, Math::BigNum implements another kind of methods that begin with an B followed by the actual name (e.g.: C).
186             This methods do floating-point operations and are usually faster than their rational counterparts when invoked on very large or very small real-numbers.
187              
188             The returned types are noted as follows:
189              
190             BigNum # a "Math::BigNum" object
191             Inf # a "Math::BigNum::Inf" object
192             Nan # a "Math::BigNum::Nan" object
193             Scalar # a Perl number or string
194             Bool # true or false (actually: 1 or 0)
195              
196             When two or more types are separated with pipe characters (B<|>), it means that the
197             corresponding function can return any of the specified types.
198              
199             =head1 PERFORMANCE
200              
201             The performance varies greatly, but, in most cases, Math::BigNum is between 2x up to 10x
202             faster than L with the B backend, and about 100x faster than L
203             without the B backend (to be modest).
204              
205             Math::BigNum is fast because of the following facts:
206              
207             =over 4
208              
209             =item *
210              
211             minimal overhead in object creation.
212              
213             =item *
214              
215             minimal Perl code is executed per operation.
216              
217             =item *
218              
219             the B and B libraries are extremely efficient.
220              
221             =back
222              
223             To achieve the best performance, try to follow this rules:
224              
225             =over 4
226              
227             =item *
228              
229             use the B methods whenever you can.
230              
231             =item *
232              
233             use the B methods wherever applicable.
234              
235             =item *
236              
237             use the B methods when accuracy is not important.
238              
239             =item *
240              
241             pass Perl numbers as arguments to methods, if you can.
242              
243             =item *
244              
245             avoid the stringification of non-integer Math::BigNum objects.
246              
247             =item *
248              
249             don't use B followed by a B method! Just leave out the B.
250              
251             =back
252              
253             =cut
254              
255             our ($ROUND, $PREC);
256              
257             BEGIN {
258             $ROUND = Math::MPFR::MPFR_RNDN();
259             $PREC = 200; # too little?
260             }
261              
262             use Math::BigNum::Inf qw();
263             use Math::BigNum::Nan qw();
264              
265             state $MONE = do {
266             my $r = Math::GMPq::Rmpq_init_nobless();
267             Math::GMPq::Rmpq_set_si($r, -1, 1);
268             $r;
269             };
270              
271             state $ZERO = do {
272             my $r = Math::GMPq::Rmpq_init_nobless();
273             Math::GMPq::Rmpq_set_ui($r, 0, 1);
274             $r;
275             };
276              
277             state $ONE = do {
278             my $r = Math::GMPq::Rmpq_init_nobless();
279             Math::GMPq::Rmpq_set_ui($r, 1, 1);
280             $r;
281             };
282              
283             state $ONE_Z = Math::GMPz::Rmpz_init_set_ui_nobless(1);
284              
285             use overload
286             '""' => \&stringify,
287             '0+' => \&numify,
288             bool => \&boolify,
289              
290             '=' => \©,
291              
292             # Some shortcuts for speed
293             '+=' => sub { $_[0]->badd($_[1]) },
294             '-=' => sub { $_[0]->bsub($_[1]) },
295             '*=' => sub { $_[0]->bmul($_[1]) },
296             '/=' => sub { $_[0]->bdiv($_[1]) },
297             '%=' => sub { $_[0]->bmod($_[1]) },
298             '**=' => sub { $_[0]->bpow($_[1]) },
299              
300             '^=' => sub { $_[0]->bxor($_[1]) },
301             '&=' => sub { $_[0]->band($_[1]) },
302             '|=' => sub { $_[0]->bior($_[1]) },
303             '<<=' => sub { $_[0]->blsft($_[1]) },
304             '>>=' => sub { $_[0]->brsft($_[1]) },
305              
306             '+' => sub { $_[0]->add($_[1]) },
307             '*' => sub { $_[0]->mul($_[1]) },
308              
309             '==' => sub { $_[0]->eq($_[1]) },
310             '!=' => sub { $_[0]->ne($_[1]) },
311             '&' => sub { $_[0]->and($_[1]) },
312             '|' => sub { $_[0]->ior($_[1]) },
313             '^' => sub { $_[0]->xor($_[1]) },
314             '~' => \¬,
315              
316             '++' => \&binc,
317             '--' => \&bdec,
318              
319             '>' => sub { Math::BigNum::gt($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
320             '>=' => sub { Math::BigNum::ge($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
321             '<' => sub { Math::BigNum::lt($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
322             '<=' => sub { Math::BigNum::le($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
323             '<=>' => sub { Math::BigNum::cmp($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
324              
325             '>>' => sub { Math::BigNum::rsft($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
326             '<<' => sub { Math::BigNum::lsft($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
327              
328             '**' => sub { Math::BigNum::pow($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
329             '-' => sub { Math::BigNum::sub($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
330             '/' => sub { Math::BigNum::div($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
331             '%' => sub { Math::BigNum::mod($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
332              
333             atan2 => sub { Math::BigNum::atan2($_[2] ? ($_[1], $_[0]) : ($_[0], $_[1])) },
334              
335             eq => sub { "$_[0]" eq "$_[1]" },
336             ne => sub { "$_[0]" ne "$_[1]" },
337              
338             cmp => sub { $_[2] ? "$_[1]" cmp $_[0]->stringify : $_[0]->stringify cmp "$_[1]" },
339              
340             neg => \&neg,
341             sin => \&sin,
342             cos => \&cos,
343             exp => \&exp,
344             log => \&ln,
345             int => \&int,
346             abs => \&abs,
347             sqrt => \&sqrt;
348              
349             {
350             my $binomial = sub {
351             my ($n, $k) = @_;
352              
353             (defined($n) and defined($k)) or return nan();
354             ref($n) eq __PACKAGE__ and return $n->binomial($k);
355              
356             (CORE::int($k) eq $k and $k >= MIN_SI and $k <= MAX_UI)
357             || return Math::BigNum->new($n)->binomial(Math::BigNum->new($k));
358              
359             my $n_ui = (CORE::int($n) eq $n and $n >= 0 and $n <= MAX_UI);
360             my $k_ui = $k >= 0;
361              
362             my $z = Math::GMPz::Rmpz_init();
363              
364             if ($n_ui and $k_ui) {
365             Math::GMPz::Rmpz_bin_uiui($z, $n, $k);
366             }
367             else {
368             eval { Math::GMPz::Rmpz_set_str($z, "$n", 10); 1 } // return Math::BigNum->new($n)->binomial($k);
369             $k_ui
370             ? Math::GMPz::Rmpz_bin_ui($z, $z, $k)
371             : Math::GMPz::Rmpz_bin_si($z, $z, $k);
372             }
373              
374             _mpz2big($z);
375             };
376              
377             my $factorial = sub {
378             my ($n) = @_;
379             $n // return nan();
380             ref($n) eq __PACKAGE__ and return $n->fac;
381             if (CORE::int($n) eq $n and $n >= 0 and $n <= MAX_UI) {
382             my $z = Math::GMPz::Rmpz_init();
383             Math::GMPz::Rmpz_fac_ui($z, $n);
384             _mpz2big($z);
385             }
386             else {
387             Math::BigNum->new($n)->fac;
388             }
389             };
390              
391             my $primorial = sub {
392             my ($n) = @_;
393             $n // return nan();
394             ref($n) eq __PACKAGE__ and return $n->primorial;
395             if (CORE::int($n) eq $n and $n >= 0 and $n <= MAX_UI) {
396             my $z = Math::GMPz::Rmpz_init();
397             Math::GMPz::Rmpz_primorial_ui($z, $n);
398             _mpz2big($z);
399             }
400             else {
401             Math::BigNum->new($n)->primorial;
402             }
403             };
404              
405             my $fibonacci = sub {
406             my ($n) = @_;
407             $n // return nan();
408             ref($n) eq __PACKAGE__ and return $n->fib;
409             if (CORE::int($n) eq $n and $n >= 0 and $n <= MAX_UI) {
410             my $z = Math::GMPz::Rmpz_init();
411             Math::GMPz::Rmpz_fib_ui($z, $n);
412             _mpz2big($z);
413             }
414             else {
415             Math::BigNum->new($n)->fib;
416             }
417             };
418              
419             my $lucas = sub {
420             my ($n) = @_;
421             $n // return nan();
422             ref($n) eq __PACKAGE__ and return $n->lucas;
423             if (CORE::int($n) eq $n and $n >= 0 and $n <= MAX_UI) {
424             my $z = Math::GMPz::Rmpz_init();
425             Math::GMPz::Rmpz_lucnum_ui($z, $n);
426             _mpz2big($z);
427             }
428             else {
429             Math::BigNum->new($n)->lucas;
430             }
431             };
432              
433             my $ipow = sub {
434             my ($n, $k) = @_;
435              
436             (defined($n) and defined($k)) or return nan();
437             ref($n) eq __PACKAGE__ and return $n->ipow($k);
438              
439             (CORE::int($n) eq $n and CORE::int($k) eq $k and $n <= MAX_UI and $k <= MAX_UI and $n >= MIN_SI and $k >= 0)
440             || return Math::BigNum->new($n)->ipow($k);
441              
442             my $z = Math::GMPz::Rmpz_init();
443             Math::GMPz::Rmpz_ui_pow_ui($z, CORE::abs($n), $k);
444             Math::GMPz::Rmpz_neg($z, $z) if ($n < 0 and $k % 2);
445             _mpz2big($z);
446             };
447              
448             my %constants = (
449             e => \&e,
450             phi => \&phi,
451             tau => \&tau,
452             pi => \&pi,
453             Y => \&Y,
454             G => \&G,
455             Inf => \&inf,
456             NaN => \&nan,
457             );
458              
459             my %functions = (
460             binomial => $binomial,
461             factorial => $factorial,
462             primorial => $primorial,
463             fibonacci => $fibonacci,
464             lucas => $lucas,
465             ipow => $ipow,
466             );
467              
468             sub import {
469             shift;
470              
471             my $caller = caller(0);
472              
473             while (@_) {
474             my $name = shift(@_);
475              
476             if ($name eq ':constant') {
477             overload::constant
478             integer => sub { Math::BigNum->new_uint($_[0]) },
479             float => sub { Math::BigNum->new($_[0], 10) },
480             binary => sub {
481             my ($const) = @_;
482             my $prefix = substr($const, 0, 2);
483             $prefix eq '0x' ? Math::BigNum->new(substr($const, 2), 16)
484             : $prefix eq '0b' ? Math::BigNum->new(substr($const, 2), 2)
485             : Math::BigNum->new(substr($const, 1), 8);
486             },
487             ;
488              
489             # Export 'Inf' and 'NaN' as constants
490             no strict 'refs';
491              
492             my $inf_sub = $caller . '::' . 'Inf';
493             if (!defined &$inf_sub) {
494             my $inf = inf();
495             *$inf_sub = sub () { $inf };
496             }
497              
498             my $nan_sub = $caller . '::' . 'NaN';
499             if (!defined &$nan_sub) {
500             my $nan = nan();
501             *$nan_sub = sub () { $nan };
502             }
503             }
504             elsif (exists $constants{$name}) {
505             no strict 'refs';
506             my $caller_sub = $caller . '::' . $name;
507             if (!defined &$caller_sub) {
508             my $sub = $constants{$name};
509             my $value = Math::BigNum->$sub;
510             *$caller_sub = sub() { $value }
511             }
512             }
513             elsif (exists $functions{$name}) {
514             no strict 'refs';
515             my $caller_sub = $caller . '::' . $name;
516             if (!defined &$caller_sub) {
517             *$caller_sub = $functions{$name};
518             }
519             }
520             elsif ($name eq ':all') {
521             push @_, keys(%constants), keys(%functions);
522             }
523             elsif ($name eq 'PREC') {
524             my $prec = CORE::int(shift(@_));
525             if ($prec < 2 or $prec > MAX_UI) {
526             die "invalid value for <>: must be between 2 and ", MAX_UI;
527             }
528             $Math::BigNum::PREC = $prec;
529             }
530             else {
531             die "unknown import: <<$name>>";
532             }
533             }
534             return;
535             }
536              
537             sub unimport {
538             overload::remove_constant('binary', '', 'float', '', 'integer');
539             }
540             }
541              
542             # Converts a string representing a floating-point number into a rational representation
543             # Example: "1.234" is converted into "1234/1000"
544             # TODO: find a better solution (maybe)
545             # This solution is very slow for literals with absolute big exponents, such as: "1e-10000000"
546             sub _str2rat {
547             my $str = lc($_[0] || "0");
548              
549             my $sign = substr($str, 0, 1);
550             if ($sign eq '-') {
551             substr($str, 0, 1, '');
552             $sign = '-';
553             }
554             else {
555             substr($str, 0, 1, '') if ($sign eq '+');
556             $sign = '';
557             }
558              
559             my $i;
560             if (($i = index($str, 'e')) != -1) {
561              
562             my $exp = substr($str, $i + 1);
563              
564             # Handle specially numbers with very big exponents
565             # (it's not a very good solution, but I hope it's only temporarily)
566             if (CORE::abs($exp) >= 1000000) {
567             my $mpfr = Math::MPFR::Rmpfr_init2($PREC);
568             Math::MPFR::Rmpfr_set_str($mpfr, "$sign$str", 10, $ROUND);
569             my $mpq = Math::GMPq::Rmpq_init();
570             Math::MPFR::Rmpfr_get_q($mpq, $mpfr);
571             return Math::GMPq::Rmpq_get_str($mpq, 10);
572             }
573              
574             my ($before, $after) = split(/\./, substr($str, 0, $i));
575              
576             if (!defined($after)) { # return faster for numbers like "13e2"
577             if ($exp >= 0) {
578             return ("$sign$before" . ('0' x $exp));
579             }
580             else {
581             $after = '';
582             }
583             }
584              
585             my $numerator = "$before$after";
586             my $denominator = "1";
587              
588             if ($exp < 1) {
589             $denominator .= '0' x (CORE::abs($exp) + CORE::length($after));
590             }
591             else {
592             my $diff = ($exp - CORE::length($after));
593             if ($diff >= 0) {
594             $numerator .= '0' x $diff;
595             }
596             else {
597             my $s = "$before$after";
598             substr($s, $exp + CORE::length($before), 0, '.');
599             return _str2rat("$sign$s");
600             }
601             }
602              
603             "$sign$numerator/$denominator";
604             }
605             elsif (($i = index($str, '.')) != -1) {
606             my ($before, $after) = (substr($str, 0, $i), substr($str, $i + 1));
607             if ($after =~ tr/0// == CORE::length($after)) {
608             return "$sign$before";
609             }
610             $sign . ("$before$after/1" =~ s/^0+//r) . ('0' x CORE::length($after));
611             }
612             else {
613             "$sign$str";
614             }
615             }
616              
617             # Converts a string into an mpfr object
618             sub _str2mpfr {
619             my $r = Math::MPFR::Rmpfr_init2($PREC);
620              
621             if (CORE::int($_[0]) eq $_[0] and $_[0] >= MIN_SI and $_[0] <= MAX_UI) {
622             $_[0] >= 0
623             ? Math::MPFR::Rmpfr_set_ui($r, $_[0], $ROUND)
624             : Math::MPFR::Rmpfr_set_si($r, $_[0], $ROUND);
625             }
626             else {
627             Math::MPFR::Rmpfr_set_str($r, $_[0], 10, $ROUND) && return;
628             }
629              
630             $r;
631             }
632              
633             # Converts a string into an mpq object
634             sub _str2mpq {
635             my $r = Math::GMPq::Rmpq_init();
636              
637             $_[0] || do {
638             Math::GMPq::Rmpq_set($r, $ZERO);
639             return $r;
640             };
641              
642             # Performance improvement for Perl integers
643             if (CORE::int($_[0]) eq $_[0] and $_[0] >= MIN_SI and $_[0] <= MAX_UI) {
644             if ($_[0] >= 0) {
645             Math::GMPq::Rmpq_set_ui($r, $_[0], 1);
646             }
647             else {
648             Math::GMPq::Rmpq_set_si($r, $_[0], 1);
649             }
650             }
651              
652             # Otherwise, it's a string or a float (this is slightly slower)
653             else {
654             my $rat = $_[0] =~ tr/.Ee// ? _str2rat($_[0] =~ tr/_//dr) : ($_[0] =~ tr/_+//dr);
655             if ($rat !~ m{^\s*[-+]?[0-9]+(?>\s*/\s*[-+]?[1-9]+[0-9]*)?\s*\z}) {
656             return;
657             }
658             Math::GMPq::Rmpq_set_str($r, $rat, 10);
659             Math::GMPq::Rmpq_canonicalize($r) if (index($rat, '/') != -1);
660             }
661              
662             $r;
663             }
664              
665             # Converts a string into an mpz object
666             sub _str2mpz {
667             (CORE::int($_[0]) eq $_[0] and $_[0] <= MAX_UI and $_[0] >= MIN_SI)
668             ? (
669             ($_[0] >= 0)
670             ? Math::GMPz::Rmpz_init_set_ui($_[0])
671             : Math::GMPz::Rmpz_init_set_si($_[0])
672             )
673             : eval { Math::GMPz::Rmpz_init_set_str($_[0], 10) };
674             }
675              
676             # Converts a BigNum object to mpfr
677             sub _big2mpfr {
678              
679             $PREC = CORE::int($PREC) if ref($PREC);
680              
681             my $r = Math::MPFR::Rmpfr_init2($PREC);
682             Math::MPFR::Rmpfr_set_q($r, ${$_[0]}, $ROUND);
683             $r;
684             }
685              
686             # Converts a BigNum object to mpz
687             sub _big2mpz {
688             my $z = Math::GMPz::Rmpz_init();
689             Math::GMPz::Rmpz_set_q($z, ${$_[0]});
690             $z;
691             }
692              
693             # Converts an integer BigNum object to mpz
694             sub _int2mpz {
695             my $z = Math::GMPz::Rmpz_init();
696             Math::GMPq::Rmpq_numref($z, ${$_[0]});
697             $z;
698             }
699              
700             # Converts an mpfr object to BigNum
701             sub _mpfr2big {
702              
703             if (!Math::MPFR::Rmpfr_number_p($_[0])) {
704              
705             if (Math::MPFR::Rmpfr_inf_p($_[0])) {
706             if (Math::MPFR::Rmpfr_sgn($_[0]) > 0) {
707             return inf();
708             }
709             else {
710             return ninf();
711             }
712             }
713              
714             if (Math::MPFR::Rmpfr_nan_p($_[0])) {
715             return nan();
716             }
717             }
718              
719             my $r = Math::GMPq::Rmpq_init();
720             Math::MPFR::Rmpfr_get_q($r, $_[0]);
721             bless \$r, __PACKAGE__;
722             }
723              
724             # Converts an mpfr object to mpq and puts it in $x
725             sub _mpfr2x {
726              
727             if (!Math::MPFR::Rmpfr_number_p($_[1])) {
728              
729             if (Math::MPFR::Rmpfr_inf_p($_[1])) {
730             if (Math::MPFR::Rmpfr_sgn($_[1]) > 0) {
731             return $_[0]->binf;
732             }
733             else {
734             return $_[0]->bninf;
735             }
736             }
737              
738             if (Math::MPFR::Rmpfr_nan_p($_[1])) {
739             return $_[0]->bnan;
740             }
741             }
742              
743             Math::MPFR::Rmpfr_get_q(${$_[0]}, $_[1]);
744             $_[0];
745             }
746              
747             # Converts an mpz object to BigNum
748             sub _mpz2big {
749             my $r = Math::GMPq::Rmpq_init();
750             Math::GMPq::Rmpq_set_z($r, $_[0]);
751             bless \$r, __PACKAGE__;
752             }
753              
754             *_big2inf = \&Math::BigNum::Inf::_big2inf;
755             *_big2ninf = \&Math::BigNum::Inf::_big2ninf;
756              
757             #*_big2cplx = \&Math::BigNum::Complex::_big2cplx;
758              
759             =head1 INITIALIZATION / CONSTANTS
760              
761             This section includes methods for creating new B objects
762             and some useful mathematical constants.
763              
764             =cut
765              
766             =head2 new
767              
768             BigNum->new(Scalar) # => BigNum
769             BigNum->new(Scalar, Scalar) # => BigNum
770              
771             Returns a new BigNum object with the value specified in the first argument,
772             which can be a Perl numerical value, a string representing a number in a
773             rational form, such as C<"1/2">, a string holding a floating-point number,
774             such as C<"0.5">, or a string holding an integer, such as C<"255">.
775              
776             The second argument specifies the base of the number, which can range from 2
777             to 36 inclusive and defaults to 10.
778              
779             For setting an hexadecimal number, we can say:
780              
781             my $x = Math::BigNum->new("deadbeef", 16);
782              
783             B no prefix, such as C<"0x"> or C<"0b">, is allowed as part of the number.
784              
785             =cut
786              
787             sub new {
788             my ($class, $num, $base) = @_;
789              
790             my $ref = ref($num);
791              
792             # Be forgetful about undefined values or empty strings
793             if ($ref eq '' and !$num) {
794             return zero();
795             }
796              
797             # Special string values
798             elsif (!defined($base) and $ref eq '') {
799             my $lc = lc($num);
800             if ($lc eq 'inf' or $lc eq '+inf') {
801             return inf();
802             }
803             elsif ($lc eq '-inf') {
804             return ninf();
805             }
806             elsif ($lc eq 'nan') {
807             return nan();
808             }
809             }
810              
811             # Special objects
812             elsif ( $ref eq 'Math::BigNum'
813             or $ref eq 'Math::BigNum::Inf'
814             or $ref eq 'Math::BigNum::Nan') {
815             return $num->copy;
816             }
817              
818             # Special values as Big{Int,Float,Rat}
819             elsif ( $ref eq 'Math::BigInt'
820             or $ref eq 'Math::BigFloat'
821             or $ref eq 'Math::BigRat') {
822             if ($num->is_nan) {
823             return nan();
824             }
825             elsif ($num->is_inf('-')) {
826             return ninf();
827             }
828             elsif ($num->is_inf('+')) {
829             return inf();
830             }
831             }
832              
833             # GMPz
834             elsif ($ref eq 'Math::GMPz') {
835             return _mpz2big($num);
836             }
837              
838             # MPFR
839             elsif ($ref eq 'Math::MPFR') {
840             return _mpfr2big($num);
841             }
842              
843             # Plain scalar
844             if ($ref eq '' and (!defined($base) or $base == 10)) { # it's a base 10 scalar
845             return bless \(_str2mpq($num) // return nan()), $class; # so we can return faster
846             }
847              
848             # Create a new GMPq object
849             my $r = Math::GMPq::Rmpq_init();
850              
851             # BigInt
852             if ($ref eq 'Math::BigInt') {
853             Math::GMPq::Rmpq_set_str($r, $num->bstr, 10);
854             }
855              
856             # BigFloat
857             elsif ($ref eq 'Math::BigFloat') {
858             my $rat = _str2rat($num->bstr);
859             Math::GMPq::Rmpq_set_str($r, $rat, 10);
860             Math::GMPq::Rmpq_canonicalize($r) if (index($rat, '/') != -1);
861             }
862              
863             # BigRat
864             elsif ($ref eq 'Math::BigRat') {
865             Math::GMPq::Rmpq_set_str($r, $num->bstr, 10);
866             }
867              
868             # GMPq
869             elsif ($ref eq 'Math::GMPq') {
870             Math::GMPq::Rmpq_set($r, $num);
871             }
872              
873             # Number with base
874             elsif (defined($base) and $ref eq '') {
875              
876             if ($base < 2 or $base > 36) {
877             require Carp;
878             Carp::croak("base must be between 2 and 36, got $base");
879             }
880              
881             Math::GMPq::Rmpq_set_str($r, $num, $base);
882             Math::GMPq::Rmpq_canonicalize($r) if (index($num, '/') != -1);
883             }
884              
885             # Other reference (which may support stringification)
886             else {
887             Math::GMPq::Rmpq_set($r, _str2mpq("$num") // return nan());
888             }
889              
890             # Return a blessed BigNum object
891             bless \$r, $class;
892             }
893              
894             =head2 new_int
895              
896             BigNum->new_int(Scalar) # => BigNum
897              
898             A faster version of the method C for setting a I native integer.
899              
900             Example:
901              
902             my $x = Math::BigNum->new_int(-42);
903              
904             =cut
905              
906             sub new_int {
907             my $r = Math::GMPq::Rmpq_init();
908             Math::GMPq::Rmpq_set_si($r, $_[1], 1);
909             bless \$r, __PACKAGE__;
910             }
911              
912             =head2 new_uint
913              
914             BigNum->new_uint(Scalar) # => BigNum
915              
916             A faster version of the method C for setting an I native integer.
917              
918             Example:
919              
920             my $x = Math::BigNum->new_uint(42);
921              
922             =cut
923              
924             sub new_uint {
925             my $r = Math::GMPq::Rmpq_init();
926             Math::GMPq::Rmpq_set_ui($r, $_[1], 1);
927             bless \$r, __PACKAGE__;
928             }
929              
930             #
931             ## Constants
932             #
933              
934             =head2 nan
935              
936             BigNum->nan # => Nan
937              
938             Returns a new Nan object.
939              
940             =cut
941              
942             BEGIN { *nan = \&Math::BigNum::Nan::nan }
943              
944             =head2 inf
945              
946             BigNum->inf # => Inf
947              
948             Returns a new Inf object to represent positive Infinity.
949              
950             =cut
951              
952             BEGIN { *inf = \&Math::BigNum::Inf::inf }
953              
954             =head2 ninf
955              
956             BigNum->ninf # => -Inf
957              
958             Returns an Inf object to represent negative Infinity.
959              
960             =cut
961              
962             BEGIN { *ninf = \&Math::BigNum::Inf::ninf }
963              
964             =head2 one
965              
966             BigNum->one # => BigNum
967              
968             Returns a BigNum object containing the value C<1>.
969              
970             =cut
971              
972             sub one {
973             my $r = Math::GMPq::Rmpq_init();
974             Math::GMPq::Rmpq_set($r, $ONE);
975             bless \$r, __PACKAGE__;
976             }
977              
978             =head2 zero
979              
980             BigNum->zero # => BigNum
981              
982             Returns a BigNum object containing the value C<0>.
983              
984             =cut
985              
986             sub zero {
987             my $r = Math::GMPq::Rmpq_init();
988             Math::GMPq::Rmpq_set($r, $ZERO);
989             bless \$r, __PACKAGE__;
990             }
991              
992             =head2 mone
993              
994             BigNum->mone # => BigNum
995              
996             Returns a BigNum object containing the value C<-1>.
997              
998             =cut
999              
1000             sub mone {
1001             my $r = Math::GMPq::Rmpq_init();
1002             Math::GMPq::Rmpq_set($r, $MONE);
1003             bless \$r, __PACKAGE__;
1004             }
1005              
1006             =head2 bzero
1007              
1008             $x->bzero # => BigNum
1009              
1010             Changes C in-place to hold the value 0.
1011              
1012             =cut
1013              
1014             sub bzero {
1015             my ($x) = @_;
1016             Math::GMPq::Rmpq_set($$x, $ZERO);
1017             if (ref($x) ne __PACKAGE__) {
1018             bless $x, __PACKAGE__;
1019             }
1020             $x;
1021             }
1022              
1023             =head2 bone
1024              
1025             $x->bone # => BigNum
1026              
1027             Changes C in-place to hold the value +1.
1028              
1029             =cut
1030              
1031             sub bone {
1032             my ($x) = @_;
1033             Math::GMPq::Rmpq_set($$x, $ONE);
1034             if (ref($x) ne __PACKAGE__) {
1035             bless $x, __PACKAGE__;
1036             }
1037             $x;
1038             }
1039              
1040             =head2 bmone
1041              
1042             $x->bmone # => BigNum
1043              
1044             Changes C in-place to hold the value -1.
1045              
1046             =cut
1047              
1048             sub bmone {
1049             my ($x) = @_;
1050             Math::GMPq::Rmpq_set($$x, $MONE);
1051             if (ref($x) ne __PACKAGE__) {
1052             bless $x, __PACKAGE__;
1053             }
1054             $x;
1055             }
1056              
1057             =head2 binf
1058              
1059             $x->binf # => Inf
1060              
1061             Changes C in-place to positive Infinity.
1062              
1063             =cut
1064              
1065             *binf = \&Math::BigNum::Inf::binf;
1066              
1067             =head2 bninf
1068              
1069             $x->bninf # => -Inf
1070              
1071             Changes C in-place to negative Infinity.
1072              
1073             =cut
1074              
1075             *bninf = \&Math::BigNum::Inf::bninf;
1076              
1077             =head2 bnan
1078              
1079             $x->bnan # => Nan
1080              
1081             Changes C in-place to the special Not-a-Number value.
1082              
1083             =cut
1084              
1085             *bnan = \&Math::BigNum::Nan::bnan;
1086              
1087             =head2 pi
1088              
1089             BigNum->pi # => BigNum
1090              
1091             Returns the number PI, which is C<3.1415...>.
1092              
1093             =cut
1094              
1095             sub pi {
1096             my $pi = Math::MPFR::Rmpfr_init2($PREC);
1097             Math::MPFR::Rmpfr_const_pi($pi, $ROUND);
1098             _mpfr2big($pi);
1099             }
1100              
1101             =head2 tau
1102              
1103             BigNum->tau # => BigNum
1104              
1105             Returns the number TAU, which is C<2*PI>.
1106              
1107             =cut
1108              
1109             sub tau {
1110             my $tau = Math::MPFR::Rmpfr_init2($PREC);
1111             Math::MPFR::Rmpfr_const_pi($tau, $ROUND);
1112             Math::MPFR::Rmpfr_mul_ui($tau, $tau, 2, $ROUND);
1113             _mpfr2big($tau);
1114             }
1115              
1116             =head2 ln2
1117              
1118             BigNum->ln2 # => BigNum
1119              
1120             Returns the natural logarithm of C<2>.
1121              
1122             =cut
1123              
1124             sub ln2 {
1125             my $ln2 = Math::MPFR::Rmpfr_init2($PREC);
1126             Math::MPFR::Rmpfr_const_log2($ln2, $ROUND);
1127             _mpfr2big($ln2);
1128             }
1129              
1130             =head2 Y
1131              
1132             BigNum->Y # => BigNum
1133              
1134             Returns the Euler-Mascheroni constant, which is C<0.57721...>.
1135              
1136             =cut
1137              
1138             sub Y {
1139             my $euler = Math::MPFR::Rmpfr_init2($PREC);
1140             Math::MPFR::Rmpfr_const_euler($euler, $ROUND);
1141             _mpfr2big($euler);
1142             }
1143              
1144             =head2 G
1145              
1146             BigNum->G # => BigNum
1147              
1148             Returns the value of Catalan's constant, also known
1149             as Beta(2) or G, and starts as: C<0.91596...>.
1150              
1151             =cut
1152              
1153             sub G {
1154             my $catalan = Math::MPFR::Rmpfr_init2($PREC);
1155             Math::MPFR::Rmpfr_const_catalan($catalan, $ROUND);
1156             _mpfr2big($catalan);
1157             }
1158              
1159             =head2 e
1160              
1161             BigNum->e # => BigNum
1162              
1163             Returns the e mathematical constant, which is C<2.718...>.
1164              
1165             =cut
1166              
1167             sub e {
1168             state $one_f = (Math::MPFR::Rmpfr_init_set_ui_nobless(1, $ROUND))[0];
1169             my $e = Math::MPFR::Rmpfr_init2($PREC);
1170             Math::MPFR::Rmpfr_exp($e, $one_f, $ROUND);
1171             _mpfr2big($e);
1172             }
1173              
1174             =head2 phi
1175              
1176             BigNum->phi # => BigNum
1177              
1178             Returns the value of the golden ratio, which is C<1.61803...>.
1179              
1180             =cut
1181              
1182             sub phi {
1183             state $five4_f = (Math::MPFR::Rmpfr_init_set_str_nobless("1.25", 10, $ROUND))[0];
1184             state $half_f = (Math::MPFR::Rmpfr_init_set_str_nobless("0.5", 10, $ROUND))[0];
1185              
1186             my $phi = Math::MPFR::Rmpfr_init2($PREC);
1187             Math::MPFR::Rmpfr_sqrt($phi, $five4_f, $ROUND);
1188             Math::MPFR::Rmpfr_add($phi, $phi, $half_f, $ROUND);
1189              
1190             _mpfr2big($phi);
1191             }
1192              
1193             ############################ RATIONAL OPERATIONS ############################
1194              
1195             =head1 RATIONAL OPERATIONS
1196              
1197             All operations in this section are done rationally, which means that the
1198             returned results are 100% exact (unless otherwise stated in some special cases).
1199              
1200             =cut
1201              
1202             =head2 add
1203              
1204             $x->add(BigNum) # => BigNum
1205             $x->add(Scalar) # => BigNum
1206              
1207             BigNum + BigNum # => BigNum
1208             BigNum + Scalar # => BigNum
1209             Scalar + BigNum # => BigNum
1210              
1211             Adds C to C and returns the result.
1212              
1213             =cut
1214              
1215             Class::Multimethods::multimethod add => qw(Math::BigNum Math::BigNum) => sub {
1216             my ($x, $y) = @_;
1217             my $r = Math::GMPq::Rmpq_init();
1218             Math::GMPq::Rmpq_add($r, $$x, $$y);
1219             bless \$r, __PACKAGE__;
1220             };
1221              
1222             Class::Multimethods::multimethod add => qw(Math::BigNum $) => sub {
1223             my ($x, $y) = @_;
1224             my $r = _str2mpq($y) // return Math::BigNum->new($y)->badd($x);
1225             Math::GMPq::Rmpq_add($r, $r, $$x);
1226             bless \$r, __PACKAGE__;
1227             };
1228              
1229             =for comment
1230             Class::Multimethods::multimethod add => qw(Math::BigNum Math::BigNum::Complex) => sub {
1231             Math::BigNum::Complex->new($_[0])->add($_[1]);
1232             };
1233             =cut
1234              
1235             Class::Multimethods::multimethod add => qw(Math::BigNum *) => sub {
1236             Math::BigNum->new($_[1])->badd($_[0]);
1237             };
1238              
1239             Class::Multimethods::multimethod add => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->copy };
1240             Class::Multimethods::multimethod add => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
1241              
1242             =head2 badd
1243              
1244             $x->badd(BigNum) # => BigNum
1245             $x->badd(Scalar) # => BigNum
1246              
1247             BigNum += BigNum # => BigNum
1248             BigNum += Scalar # => BigNum
1249              
1250             Adds C to C, changing C in-place.
1251              
1252             =cut
1253              
1254             Class::Multimethods::multimethod badd => qw(Math::BigNum Math::BigNum) => sub {
1255             my ($x, $y) = @_;
1256             Math::GMPq::Rmpq_add($$x, $$x, $$y);
1257             $x;
1258             };
1259              
1260             Class::Multimethods::multimethod badd => qw(Math::BigNum $) => sub {
1261             my ($x, $y) = @_;
1262             Math::GMPq::Rmpq_add($$x, $$x, _str2mpq($y) // return $x->badd(Math::BigNum->new($y)));
1263             $x;
1264             };
1265              
1266             Class::Multimethods::multimethod badd => qw(Math::BigNum *) => sub {
1267             $_[0]->badd(Math::BigNum->new($_[1]));
1268             };
1269              
1270             Class::Multimethods::multimethod badd => qw(Math::BigNum Math::BigNum::Inf) => \&_big2inf;
1271             Class::Multimethods::multimethod badd => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
1272              
1273             =head2 sub
1274              
1275             $x->sub(BigNum) # => BigNum
1276             $x->sub(Scalar) # => BigNum
1277              
1278             BigNum - BigNum # => BigNum
1279             BigNum - Scalar # => BigNum
1280             Scalar - BigNum # => BigNum
1281              
1282             Subtracts C from C and returns the result.
1283              
1284             =cut
1285              
1286             Class::Multimethods::multimethod sub => qw(Math::BigNum Math::BigNum) => sub {
1287             my ($x, $y) = @_;
1288             my $r = Math::GMPq::Rmpq_init();
1289             Math::GMPq::Rmpq_sub($r, $$x, $$y);
1290             bless \$r, __PACKAGE__;
1291             };
1292              
1293             Class::Multimethods::multimethod sub => qw(Math::BigNum $) => sub {
1294             my ($x, $y) = @_;
1295             my $r = _str2mpq($y) // return Math::BigNum->new($y)->bneg->badd($x);
1296             Math::GMPq::Rmpq_sub($r, $$x, $r);
1297             bless \$r, __PACKAGE__;
1298             };
1299              
1300             Class::Multimethods::multimethod sub => qw($ Math::BigNum) => sub {
1301             my ($x, $y) = @_;
1302             my $r = _str2mpq($x) // return Math::BigNum->new($x)->bsub($y);
1303             Math::GMPq::Rmpq_sub($r, $r, $$y);
1304             bless \$r, __PACKAGE__;
1305             };
1306              
1307             =for comment
1308             Class::Multimethods::multimethod sub => qw(Math::BigNum Math::BigNum::Complex) => sub {
1309             Math::BigNum::Complex->new($_[0])->sub($_[1]);
1310             };
1311             =cut
1312              
1313             Class::Multimethods::multimethod sub => qw(* Math::BigNum) => sub {
1314             Math::BigNum->new($_[0])->bsub($_[1]);
1315             };
1316              
1317             Class::Multimethods::multimethod sub => qw(Math::BigNum *) => sub {
1318             Math::BigNum->new($_[1])->bneg->badd($_[0]);
1319             };
1320              
1321             Class::Multimethods::multimethod sub => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->neg };
1322             Class::Multimethods::multimethod sub => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
1323              
1324             =head2 bsub
1325              
1326             $x->bsub(BigNum) # => BigNum
1327             $x->bsub(Scalar) # => BigNum
1328              
1329             BigNum -= BigNum # => BigNum
1330             BigNum -= Scalar # => BigNum
1331              
1332             Subtracts C from C by changing C in-place.
1333              
1334             =cut
1335              
1336             Class::Multimethods::multimethod bsub => qw(Math::BigNum Math::BigNum) => sub {
1337             my ($x, $y) = @_;
1338             Math::GMPq::Rmpq_sub($$x, $$x, $$y);
1339             $x;
1340             };
1341              
1342             Class::Multimethods::multimethod bsub => qw(Math::BigNum $) => sub {
1343             my ($x, $y) = @_;
1344             Math::GMPq::Rmpq_sub($$x, $$x, _str2mpq($y) // return $x->bsub(Math::BigNum->new($y)));
1345             $x;
1346             };
1347              
1348             Class::Multimethods::multimethod bsub => qw(Math::BigNum *) => sub {
1349             $_[0]->bsub(Math::BigNum->new($_[1]));
1350             };
1351              
1352             Class::Multimethods::multimethod bsub => qw(Math::BigNum Math::BigNum::Inf) => \&_big2ninf;
1353             Class::Multimethods::multimethod bsub => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
1354              
1355             =head2 mul
1356              
1357             $x->mul(BigNum) # => BigNum
1358             $x->mul(Scalar) # => BigNum
1359              
1360             BigNum * BigNum # => BigNum
1361             BigNum * Scalar # => BigNum
1362             Scalar * BigNum # => BigNum
1363              
1364             Multiplies C by C and returns the result.
1365              
1366             =cut
1367              
1368             Class::Multimethods::multimethod mul => qw(Math::BigNum Math::BigNum) => sub {
1369             my ($x, $y) = @_;
1370             my $r = Math::GMPq::Rmpq_init();
1371             Math::GMPq::Rmpq_mul($r, $$x, $$y);
1372             bless \$r, __PACKAGE__;
1373             };
1374              
1375             Class::Multimethods::multimethod mul => qw(Math::BigNum $) => sub {
1376             my ($x, $y) = @_;
1377             my $r = _str2mpq($y) // return Math::BigNum->new($y)->bmul($x);
1378             Math::GMPq::Rmpq_mul($r, $$x, $r);
1379             bless \$r, __PACKAGE__;
1380             };
1381              
1382             =for comment
1383             Class::Multimethods::multimethod mul => qw(Math::BigNum Math::BigNum::Complex) => sub {
1384             $_[1]->mul($_[0]);
1385             };
1386             =cut
1387              
1388             Class::Multimethods::multimethod mul => qw(Math::BigNum *) => sub {
1389             Math::BigNum->new($_[1])->bmul($_[0]);
1390             };
1391              
1392             Class::Multimethods::multimethod mul => qw(Math::BigNum Math::BigNum::Inf) => sub {
1393             my $sign = Math::GMPq::Rmpq_sgn(${$_[0]});
1394             $sign < 0 ? $_[1]->neg : $sign > 0 ? $_[1]->copy : nan;
1395             };
1396              
1397             Class::Multimethods::multimethod mul => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
1398              
1399             =head2 bmul
1400              
1401             $x->bmul(BigNum) # => BigNum
1402             $x->bmul(Scalar) # => BigNum
1403              
1404             BigNum *= BigNum # => BigNum
1405             BigNum *= Scalar # => BigNum
1406              
1407             Multiply C by C, changing C in-place.
1408              
1409             =cut
1410              
1411             Class::Multimethods::multimethod bmul => qw(Math::BigNum Math::BigNum) => sub {
1412             my ($x, $y) = @_;
1413             Math::GMPq::Rmpq_mul($$x, $$x, $$y);
1414             $x;
1415             };
1416              
1417             Class::Multimethods::multimethod bmul => qw(Math::BigNum $) => sub {
1418             my ($x, $y) = @_;
1419             Math::GMPq::Rmpq_mul($$x, $$x, _str2mpq($y) // return $x->bmul(Math::BigNum->new($y)));
1420             $x;
1421             };
1422              
1423             Class::Multimethods::multimethod bmul => qw(Math::BigNum *) => sub {
1424             $_[0]->bmul(Math::BigNum->new($_[1]));
1425             };
1426              
1427             Class::Multimethods::multimethod bmul => qw(Math::BigNum Math::BigNum::Inf) => sub {
1428             my ($x) = @_;
1429             my $sign = Math::GMPq::Rmpq_sgn($$x);
1430              
1431             $sign < 0 ? _big2ninf(@_)
1432             : $sign > 0 ? _big2inf(@_)
1433             : $x->bnan;
1434             };
1435              
1436             Class::Multimethods::multimethod bmul => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
1437              
1438             =head2 div
1439              
1440             $x->div(BigNum) # => BigNum | Inf | Nan
1441             $x->div(Scalar) # => BigNum | Inf | Nan
1442              
1443             BigNum / BigNum # => BigNum | Inf | Nan
1444             BigNum / Scalar # => BigNum | Inf | Nan
1445             Scalar / BigNum # => BigNum | Inf | Nan
1446              
1447             Divides C by C and returns the result. Returns Nan when C and C are 0,
1448             Inf when C is 0 and C is positive, -Inf when C is zero and C is negative.
1449              
1450             =cut
1451              
1452             Class::Multimethods::multimethod div => qw(Math::BigNum Math::BigNum) => sub {
1453             my ($x, $y) = @_;
1454              
1455             Math::GMPq::Rmpq_sgn($$y) || do {
1456             my $sign = Math::GMPq::Rmpq_sgn($$x);
1457             return (!$sign ? nan : $sign > 0 ? inf : ninf);
1458             };
1459              
1460             my $r = Math::GMPq::Rmpq_init();
1461             Math::GMPq::Rmpq_div($r, $$x, $$y);
1462             bless \$r, __PACKAGE__;
1463             };
1464              
1465             Class::Multimethods::multimethod div => qw(Math::BigNum $) => sub {
1466             my ($x, $y) = @_;
1467              
1468             $y || do {
1469             my $sign = Math::GMPq::Rmpq_sgn($$x);
1470             return (!$sign ? nan : $sign > 0 ? inf : ninf);
1471             };
1472              
1473             my $r = _str2mpq($y) // return $x->div(Math::BigNum->new($y));
1474             Math::GMPq::Rmpq_div($r, $$x, $r);
1475             bless \$r, __PACKAGE__;
1476             };
1477              
1478             Class::Multimethods::multimethod div => qw($ Math::BigNum) => sub {
1479             my ($x, $y) = @_;
1480              
1481             Math::GMPq::Rmpq_sgn($$y)
1482             || return (!$x ? nan : $x > 0 ? inf : ninf);
1483              
1484             my $r = _str2mpq($x) // return Math::BigNum->new($x)->bdiv($y);
1485             Math::GMPq::Rmpq_div($r, $r, $$y);
1486             bless \$r, __PACKAGE__;
1487             };
1488              
1489             =for comment
1490             Class::Multimethods::multimethod div => qw(Math::BigNum Math::BigNum::Complex) => sub {
1491             Math::BigNum::Complex->new($_[0])->div($_[1]);
1492             };
1493             =cut
1494              
1495             Class::Multimethods::multimethod div => qw(* Math::BigNum) => sub {
1496             Math::BigNum->new($_[0])->bdiv($_[1]);
1497             };
1498              
1499             Class::Multimethods::multimethod div => qw(Math::BigNum *) => sub {
1500             Math::BigNum->new($_[1])->binv->bmul($_[0]);
1501             };
1502              
1503             Class::Multimethods::multimethod div => qw(Math::BigNum Math::BigNum::Inf) => \&zero;
1504             Class::Multimethods::multimethod div => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
1505              
1506             =head2 bdiv
1507              
1508             $x->bdiv(BigNum) # => BigNum | Nan | Inf
1509             $x->bdiv(Scalar) # => BigNum | Nan | Inf
1510              
1511             BigNum /= BigNum # => BigNum | Nan | Inf
1512             BigNum /= Scalar # => BigNum | Nan | Inf
1513              
1514             Divide C by C, changing C in-place. The return values are the same as for C.
1515              
1516             =cut
1517              
1518             Class::Multimethods::multimethod bdiv => qw(Math::BigNum Math::BigNum) => sub {
1519             my ($x, $y) = @_;
1520              
1521             Math::GMPq::Rmpq_sgn($$y) || do {
1522             my $sign = Math::GMPq::Rmpq_sgn($$x);
1523             return
1524             $sign > 0 ? $x->binf
1525             : $sign < 0 ? $x->bninf
1526             : $x->bnan;
1527             };
1528              
1529             Math::GMPq::Rmpq_div($$x, $$x, $$y);
1530             $x;
1531             };
1532              
1533             Class::Multimethods::multimethod bdiv => qw(Math::BigNum $) => sub {
1534             my ($x, $y) = @_;
1535              
1536             $y || do {
1537             my $sign = Math::GMPq::Rmpq_sgn($$x);
1538             return
1539             $sign > 0 ? $x->binf
1540             : $sign < 0 ? $x->bninf
1541             : $x->bnan;
1542             };
1543              
1544             Math::GMPq::Rmpq_div($$x, $$x, _str2mpq($y) // return $x->bdiv(Math::BigNum->new($y)));
1545             $x;
1546             };
1547              
1548             Class::Multimethods::multimethod bdiv => qw(Math::BigNum *) => sub {
1549             $_[0]->bdiv(Math::BigNum->new($_[1]));
1550             };
1551              
1552             Class::Multimethods::multimethod bdiv => qw(Math::BigNum Math::BigNum::Inf) => \&bzero;
1553             Class::Multimethods::multimethod bdiv => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
1554              
1555             =head2 mod
1556              
1557             $x->mod(BigNum) # => BigNum | Nan
1558             $x->mod(Scalar) # => BigNum | Nan
1559              
1560             BigNum % BigNum # => BigNum | Nan
1561             BigNum % Scalar # => BigNum | Nan
1562             Scalar % BigNum # => BigNum | Nan
1563              
1564             Remainder of C when is divided by C. Returns Nan when C is zero.
1565              
1566             When C and C are both integers, the returned result is exact.
1567             Otherwise, the result is a floating-point approximation.
1568              
1569             =cut
1570              
1571             Class::Multimethods::multimethod mod => qw(Math::BigNum Math::BigNum) => sub {
1572             my ($x, $y) = @_;
1573              
1574             if (Math::GMPq::Rmpq_integer_p($$x) and Math::GMPq::Rmpq_integer_p($$y)) {
1575              
1576             my $yz = _int2mpz($y);
1577             my $sign_y = Math::GMPz::Rmpz_sgn($yz);
1578             return nan if !$sign_y;
1579              
1580             my $r = _int2mpz($x);
1581             Math::GMPz::Rmpz_mod($r, $r, $yz);
1582             if (!Math::GMPz::Rmpz_sgn($r)) {
1583             return (zero); # return faster
1584             }
1585             elsif ($sign_y < 0) {
1586             Math::GMPz::Rmpz_add($r, $r, $yz);
1587             }
1588             _mpz2big($r);
1589             }
1590             else {
1591             my $r = _big2mpfr($x);
1592             my $yf = _big2mpfr($y);
1593             Math::MPFR::Rmpfr_fmod($r, $r, $yf, $ROUND);
1594             my $sign_r = Math::MPFR::Rmpfr_sgn($r);
1595             if (!$sign_r) {
1596             return (zero); # return faster
1597             }
1598             elsif ($sign_r > 0 xor Math::MPFR::Rmpfr_sgn($yf) > 0) {
1599             Math::MPFR::Rmpfr_add($r, $r, $yf, $ROUND);
1600             }
1601             _mpfr2big($r);
1602             }
1603             };
1604              
1605             Class::Multimethods::multimethod mod => qw(Math::BigNum $) => sub {
1606             my ($x, $y) = @_;
1607              
1608             return nan if ($y == 0);
1609              
1610             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI and Math::GMPq::Rmpq_integer_p($$x)) {
1611             my $r = _int2mpz($x);
1612             my $neg_y = $y < 0;
1613             $y = CORE::abs($y) if $neg_y;
1614             Math::GMPz::Rmpz_mod_ui($r, $r, $y);
1615             if (!Math::GMPz::Rmpz_sgn($r)) {
1616             return (zero); # return faster
1617             }
1618             elsif ($neg_y) {
1619             Math::GMPz::Rmpz_sub_ui($r, $r, $y);
1620             }
1621             _mpz2big($r);
1622             }
1623             else {
1624             my $yf = _str2mpfr($y) // return $x->mod(Math::BigNum->new($y));
1625             my $r = _big2mpfr($x);
1626             Math::MPFR::Rmpfr_fmod($r, $r, $yf, $ROUND);
1627             my $sign = Math::MPFR::Rmpfr_sgn($r);
1628             if (!$sign) {
1629             return (zero); # return faster
1630             }
1631             elsif ($sign > 0 xor Math::MPFR::Rmpfr_sgn($yf) > 0) {
1632             Math::MPFR::Rmpfr_add($r, $r, $yf, $ROUND);
1633             }
1634             _mpfr2big($r);
1635             }
1636             };
1637              
1638             Class::Multimethods::multimethod mod => qw(* Math::BigNum) => sub {
1639             Math::BigNum->new($_[0])->bmod($_[1]);
1640             };
1641              
1642             Class::Multimethods::multimethod mod => qw(Math::BigNum *) => sub {
1643             $_[0]->mod(Math::BigNum->new($_[1]));
1644             };
1645              
1646             Class::Multimethods::multimethod mod => qw(Math::BigNum Math::BigNum::Inf) => sub {
1647             $_[0]->copy->bmod($_[1]);
1648             };
1649              
1650             Class::Multimethods::multimethod mod => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
1651              
1652             =head2 bmod
1653              
1654             $x->bmod(BigNum) # => BigNum | Nan
1655             $x->bmod(Scalar) # => BigNum | Nan
1656              
1657             BigNum %= BigNum # => BigNum | Nan
1658             BigNum %= Scalar # => BigNum | Nan
1659              
1660             Sets C to the remainder of C when is divided by C. Sets C to Nan when C is zero.
1661              
1662             =cut
1663              
1664             Class::Multimethods::multimethod bmod => qw(Math::BigNum Math::BigNum) => sub {
1665             my ($x, $y) = @_;
1666              
1667             if (Math::GMPq::Rmpq_integer_p($$x) and Math::GMPq::Rmpq_integer_p($$y)) {
1668              
1669             my $yz = _int2mpz($y);
1670             my $sign_y = Math::GMPz::Rmpz_sgn($yz);
1671             return $x->bnan if !$sign_y;
1672              
1673             my $r = _int2mpz($x);
1674             Math::GMPz::Rmpz_mod($r, $r, $yz);
1675             if ($sign_y < 0 and Math::GMPz::Rmpz_sgn($r)) {
1676             Math::GMPz::Rmpz_add($r, $r, $yz);
1677             }
1678             Math::GMPq::Rmpq_set_z($$x, $r);
1679             }
1680             else {
1681             my $r = _big2mpfr($x);
1682             my $yf = _big2mpfr($y);
1683             Math::MPFR::Rmpfr_fmod($r, $r, $yf, $ROUND);
1684             my $sign = Math::MPFR::Rmpfr_sgn($r);
1685             if (!$sign) {
1686             ## ok
1687             }
1688             elsif ($sign > 0 xor Math::MPFR::Rmpfr_sgn($yf) > 0) {
1689             Math::MPFR::Rmpfr_add($r, $r, $yf, $ROUND);
1690             }
1691             _mpfr2x($x, $r);
1692             }
1693              
1694             $x;
1695             };
1696              
1697             Class::Multimethods::multimethod bmod => qw(Math::BigNum $) => sub {
1698             my ($x, $y) = @_;
1699              
1700             return $x->bnan if ($y == 0);
1701              
1702             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI and Math::GMPq::Rmpq_integer_p($$x)) {
1703             my $r = _int2mpz($x);
1704             my $neg_y = $y < 0;
1705             $y = CORE::abs($y) if $neg_y;
1706             Math::GMPz::Rmpz_mod_ui($r, $r, $y);
1707             if ($neg_y and Math::GMPz::Rmpz_sgn($r)) {
1708             Math::GMPz::Rmpz_sub_ui($r, $r, $y);
1709             }
1710             Math::GMPq::Rmpq_set_z($$x, $r);
1711             }
1712             else {
1713             my $yf = _str2mpfr($y) // return $x->bmod(Math::BigNum->new($y));
1714             my $r = _big2mpfr($x);
1715             Math::MPFR::Rmpfr_fmod($r, $r, $yf, $ROUND);
1716             my $sign_r = Math::MPFR::Rmpfr_sgn($r);
1717             if (!$sign_r) {
1718             ## ok
1719             }
1720             elsif ($sign_r > 0 xor Math::MPFR::Rmpfr_sgn($yf) > 0) {
1721             Math::MPFR::Rmpfr_add($r, $r, $yf, $ROUND);
1722             }
1723             _mpfr2x($x, $r);
1724             }
1725              
1726             $x;
1727             };
1728              
1729             Class::Multimethods::multimethod bmod => qw(Math::BigNum *) => sub {
1730             $_[0]->bmod(Math::BigNum->new($_[1]));
1731             };
1732              
1733             # +x mod +Inf = x
1734             # +x mod -Inf = -Inf
1735             # -x mod +Inf = +Inf
1736             # -x mod -Inf = x
1737             Class::Multimethods::multimethod bmod => qw(Math::BigNum Math::BigNum::Inf) => sub {
1738             my ($x, $y) = @_;
1739             Math::GMPq::Rmpq_sgn($$x) == Math::GMPq::Rmpq_sgn($$y) ? $x : _big2inf($x, $y);
1740             };
1741              
1742             Class::Multimethods::multimethod bmod => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
1743              
1744             =head2 pow
1745              
1746             $x->pow(BigNum) # => BigNum | Nan
1747             $x->pow(Scalar) # => BigNum | Nan
1748              
1749             BigNum ** BigNum # => BigNum | Nan
1750             BigNum ** Scalar # => BigNum | Nan
1751             Scalar ** BigNum # => BigNum | Nan
1752              
1753             Raises C to power C. Returns Nan when C is negative
1754             and C is not an integer.
1755              
1756             When both C and C are integers, it does integer exponentiation and returns the exact result.
1757              
1758             When only C is an integer, it does rational exponentiation based on the identity: C<(a/b)^n = a^n / b^n>,
1759             which computes the exact result.
1760              
1761             When C and C are rationals, it does floating-point exponentiation, which is, in most cases, equivalent
1762             with: C, in which the returned result may not be exact.
1763              
1764             =cut
1765              
1766             Class::Multimethods::multimethod pow => qw(Math::BigNum Math::BigNum) => sub {
1767             my ($x, $y) = @_;
1768              
1769             # Integer power
1770             if (Math::GMPq::Rmpq_integer_p($$y)) {
1771              
1772             my $q = Math::GMPq::Rmpq_init();
1773             my $pow = Math::GMPq::Rmpq_get_d($$y);
1774              
1775             if (Math::GMPq::Rmpq_integer_p($$x)) {
1776              
1777             my $z = _int2mpz($x);
1778             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1779             Math::GMPq::Rmpq_set_z($q, $z);
1780              
1781             if ($pow < 0) {
1782             if (!Math::GMPq::Rmpq_sgn($q)) {
1783             return inf();
1784             }
1785             Math::GMPq::Rmpq_inv($q, $q);
1786             }
1787             }
1788             else {
1789             my $z = Math::GMPz::Rmpz_init();
1790             Math::GMPq::Rmpq_numref($z, $$x);
1791             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1792              
1793             Math::GMPq::Rmpq_set_num($q, $z);
1794              
1795             Math::GMPq::Rmpq_denref($z, $$x);
1796             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1797              
1798             Math::GMPq::Rmpq_set_den($q, $z);
1799              
1800             Math::GMPq::Rmpq_inv($q, $q) if $pow < 0;
1801             }
1802              
1803             return bless \$q, __PACKAGE__;
1804             }
1805              
1806             # Floating-point exponentiation otherwise
1807             my $r = _big2mpfr($x);
1808             Math::MPFR::Rmpfr_pow($r, $r, _big2mpfr($y), $ROUND);
1809             _mpfr2big($r);
1810             };
1811              
1812             =for comment
1813             Class::Multimethods::multimethod pow => qw(Math::BigNum Math::BigNum::Complex) => sub {
1814             Math::BigNum::Complex->new($_[0])->pow($_[1]);
1815             };
1816             =cut
1817              
1818             Class::Multimethods::multimethod pow => qw(Math::BigNum $) => sub {
1819             my ($x, $pow) = @_;
1820              
1821             # Integer power
1822             if (CORE::int($pow) eq $pow and $pow >= MIN_SI and $pow <= MAX_UI) {
1823              
1824             my $q = Math::GMPq::Rmpq_init();
1825              
1826             if (Math::GMPq::Rmpq_integer_p($$x)) {
1827              
1828             my $z = _int2mpz($x);
1829             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1830             Math::GMPq::Rmpq_set_z($q, $z);
1831              
1832             if ($pow < 0) {
1833             if (!Math::GMPq::Rmpq_sgn($q)) {
1834             return inf();
1835             }
1836             Math::GMPq::Rmpq_inv($q, $q);
1837             }
1838             }
1839             else {
1840             my $z = Math::GMPz::Rmpz_init();
1841             Math::GMPq::Rmpq_numref($z, $$x);
1842             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1843              
1844             Math::GMPq::Rmpq_set_num($q, $z);
1845              
1846             Math::GMPq::Rmpq_denref($z, $$x);
1847             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1848              
1849             Math::GMPq::Rmpq_set_den($q, $z);
1850              
1851             Math::GMPq::Rmpq_inv($q, $q) if $pow < 0;
1852             }
1853              
1854             return bless \$q, __PACKAGE__;
1855             }
1856              
1857             $x->pow(Math::BigNum->new($pow));
1858             };
1859              
1860             Class::Multimethods::multimethod pow => qw(* Math::BigNum) => sub {
1861             Math::BigNum->new($_[0])->bpow($_[1]);
1862             };
1863              
1864             Class::Multimethods::multimethod pow => qw(Math::BigNum *) => sub {
1865             $_[0]->pow(Math::BigNum->new($_[1]));
1866             };
1867              
1868             # 0 ** Inf = 0
1869             # 0 ** -Inf = Inf
1870             # (+/-1) ** (+/-Inf) = 1
1871             # x ** (-Inf) = 0
1872             # x ** Inf = Inf
1873              
1874             Class::Multimethods::multimethod pow => qw(Math::BigNum Math::BigNum::Inf) => sub {
1875             $_[0]->is_zero
1876             ? $_[1]->is_neg
1877             ? inf
1878             : zero
1879             : $_[0]->is_one || $_[0]->is_mone ? one
1880             : $_[1]->is_neg ? zero
1881             : inf;
1882             };
1883              
1884             Class::Multimethods::multimethod pow => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
1885              
1886             =head2 bpow
1887              
1888             $x->bpow(BigNum) # => BigNum | Nan
1889             $x->bpow(Scalar) # => BigNum | Nan
1890              
1891             BigNum **= BigNum # => BigNum | Nan
1892             BigNum **= Scalar # => BigNum | Nan
1893             Scalar **= BigNum # => BigNum | Nan
1894              
1895             Raises C to power C, changing C in-place.
1896              
1897             =cut
1898              
1899             Class::Multimethods::multimethod bpow => qw(Math::BigNum Math::BigNum) => sub {
1900             my ($x, $y) = @_;
1901              
1902             # Integer power
1903             if (Math::GMPq::Rmpq_integer_p($$y)) {
1904              
1905             my $q = $$x;
1906             my $pow = Math::GMPq::Rmpq_get_d($$y);
1907              
1908             if (Math::GMPq::Rmpq_integer_p($q)) {
1909             my $z = Math::GMPz::Rmpz_init();
1910             Math::GMPz::Rmpz_set_q($z, $q);
1911             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1912             Math::GMPq::Rmpq_set_z($q, $z);
1913              
1914             if ($pow < 0) {
1915             if (!Math::GMPq::Rmpq_sgn($q)) {
1916             return $x->binf;
1917             }
1918             Math::GMPq::Rmpq_inv($q, $q);
1919             }
1920             }
1921             else {
1922             my $z = Math::GMPz::Rmpz_init();
1923             Math::GMPq::Rmpq_numref($z, $q);
1924             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1925              
1926             Math::GMPq::Rmpq_set_num($q, $z);
1927              
1928             Math::GMPq::Rmpq_denref($z, $q);
1929             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1930              
1931             Math::GMPq::Rmpq_set_den($q, $z);
1932              
1933             Math::GMPq::Rmpq_inv($q, $q) if $pow < 0;
1934             }
1935              
1936             return $x;
1937             }
1938              
1939             # A floating-point otherwise
1940             my $r = _big2mpfr($x);
1941             Math::MPFR::Rmpfr_pow($r, $r, _big2mpfr($y), $ROUND);
1942             _mpfr2x($x, $r);
1943             };
1944              
1945             Class::Multimethods::multimethod bpow => qw(Math::BigNum $) => sub {
1946             my ($x, $pow) = @_;
1947              
1948             my $pow_is_int = (CORE::int($pow) eq $pow and $pow >= MIN_SI and $pow <= MAX_UI);
1949              
1950             # Integer power
1951             if ($pow_is_int) {
1952              
1953             my $q = $$x;
1954              
1955             if (Math::GMPq::Rmpq_integer_p($q)) {
1956             my $z = Math::GMPz::Rmpz_init();
1957             Math::GMPz::Rmpz_set_q($z, $q);
1958             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1959             Math::GMPq::Rmpq_set_z($q, $z);
1960              
1961             if ($pow < 0) {
1962             if (!Math::GMPq::Rmpq_sgn($q)) {
1963             return $x->binf;
1964             }
1965             Math::GMPq::Rmpq_inv($q, $q);
1966             }
1967             }
1968             else {
1969             my $z = Math::GMPz::Rmpz_init();
1970             Math::GMPq::Rmpq_numref($z, $$x);
1971             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1972              
1973             Math::GMPq::Rmpq_set_num($q, $z);
1974              
1975             Math::GMPq::Rmpq_denref($z, $$x);
1976             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
1977              
1978             Math::GMPq::Rmpq_set_den($q, $z);
1979              
1980             Math::GMPq::Rmpq_inv($q, $q) if $pow < 0;
1981             }
1982              
1983             return $x;
1984             }
1985              
1986             # A floating-point otherwise
1987             my $r = _big2mpfr($x);
1988             if ($pow_is_int) {
1989             if ($pow >= 0) {
1990             Math::MPFR::Rmpfr_pow_ui($r, $r, $pow, $ROUND);
1991             }
1992             else {
1993             Math::MPFR::Rmpfr_pow_si($r, $r, $pow, $ROUND);
1994             }
1995             }
1996             else {
1997             Math::MPFR::Rmpfr_pow($r, $r, _str2mpfr($pow) // (return $x->bpow(Math::BigNum->new($pow))), $ROUND);
1998             }
1999              
2000             _mpfr2x($x, $r);
2001             };
2002              
2003             Class::Multimethods::multimethod bpow => qw(Math::BigNum *) => sub {
2004             $_[0]->bpow(Math::BigNum->new($_[1]));
2005             };
2006              
2007             # 0 ** Inf = 0
2008             # 0 ** -Inf = Inf
2009             # (+/-1) ** (+/-Inf) = 1
2010             # x ** (-Inf) = 0
2011             # x ** Inf = Inf
2012              
2013             Class::Multimethods::multimethod bpow => qw(Math::BigNum Math::BigNum::Inf) => sub {
2014             $_[0]->is_zero
2015             ? $_[1]->is_neg
2016             ? $_[0]->binf
2017             : $_[0]->bzero
2018             : $_[0]->is_one || $_[0]->is_mone ? $_[0]->bone
2019             : $_[1]->is_neg ? $_[0]->bzero
2020             : $_[0]->binf;
2021             };
2022              
2023             Class::Multimethods::multimethod bpow => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
2024              
2025             =head2 inv
2026              
2027             $x->inv # => BigNum | Inf
2028              
2029             Inverse value of C. Return Inf when C is zero. (C<1/x>)
2030              
2031             =cut
2032              
2033             sub inv {
2034             my ($x) = @_;
2035              
2036             # Return Inf when $x is zero.
2037             Math::GMPq::Rmpq_sgn($$x)
2038             || return inf();
2039              
2040             my $r = Math::GMPq::Rmpq_init();
2041             Math::GMPq::Rmpq_inv($r, $$x);
2042             bless \$r, __PACKAGE__;
2043             }
2044              
2045             =head2 binv
2046              
2047             $x->binv # => BigNum | Inf
2048              
2049             Set C to its inverse value. (C<1/x>)
2050              
2051             =cut
2052              
2053             sub binv {
2054             my ($x) = @_;
2055              
2056             # Return Inf when $x is zero.
2057             Math::GMPq::Rmpq_sgn($$x)
2058             || return $x->binf;
2059              
2060             Math::GMPq::Rmpq_inv($$x, $$x);
2061             $x;
2062             }
2063              
2064             =head2 sqr
2065              
2066             $x->sqr # => BigNum
2067              
2068             Raise C to the power of 2 and return the result. (C)
2069              
2070             =cut
2071              
2072             sub sqr {
2073             my ($x) = @_;
2074             my $r = Math::GMPq::Rmpq_init();
2075             Math::GMPq::Rmpq_mul($r, $$x, $$x);
2076             bless \$r, __PACKAGE__;
2077             }
2078              
2079             =head2 bsqr
2080              
2081             $x->bsqr # => BigNum
2082              
2083             Set C to its multiplicative double. (C)
2084              
2085             =cut
2086              
2087             sub bsqr {
2088             my ($x) = @_;
2089             Math::GMPq::Rmpq_mul($$x, $$x, $$x);
2090             $x;
2091             }
2092              
2093             =head2 bernfrac
2094              
2095             $n->bernfrac # => BigNum | Nan
2096              
2097             Returns the nth-Bernoulli number C as an exact fraction, computed with an
2098             improved version of Seidel's algorithm, starting with C.
2099              
2100             For n >= 50, a more efficient algorithm is used, based on Zeta(n).
2101              
2102             For negative values of C, Nan is returned.
2103              
2104             =cut
2105              
2106             sub bernfrac {
2107             my ($n) = @_;
2108              
2109             $n = CORE::int(Math::GMPq::Rmpq_get_d($$n));
2110              
2111             $n == 0 and return one();
2112             $n > 1 and $n % 2 and return zero(); # Bn=0 for odd n>1
2113             $n < 0 and return nan();
2114              
2115             # Use a faster algorithm based on values of the Zeta function.
2116             # B(n) = (-1)^(n/2 + 1) * zeta(n)*2*n! / (2*pi)^n
2117             if ($n >= 50) {
2118              
2119             my $prec = (
2120             $n <= 156
2121             ? CORE::int($n * CORE::log($n) + 1)
2122             : CORE::int($n * CORE::log($n) / CORE::log(2) - 3 * $n) # TODO: optimize for large n (>50_000)
2123             );
2124              
2125             my $f = Math::MPFR::Rmpfr_init2($prec);
2126             Math::MPFR::Rmpfr_zeta_ui($f, $n, $ROUND); # f = zeta(n)
2127              
2128             my $z = Math::GMPz::Rmpz_init();
2129             Math::GMPz::Rmpz_fac_ui($z, $n); # z = n!
2130             Math::GMPz::Rmpz_div_2exp($z, $z, $n - 1); # z = z / 2^(n-1)
2131             Math::MPFR::Rmpfr_mul_z($f, $f, $z, $ROUND); # f = f*z
2132              
2133             my $p = Math::MPFR::Rmpfr_init2($prec);
2134             Math::MPFR::Rmpfr_const_pi($p, $ROUND); # p = PI
2135             Math::MPFR::Rmpfr_pow_ui($p, $p, $n, $ROUND); # p = p^n
2136             Math::MPFR::Rmpfr_div($f, $f, $p, $ROUND); # f = f/p
2137              
2138             Math::GMPz::Rmpz_set_ui($z, 1); # z = 1
2139             Math::GMPz::Rmpz_mul_2exp($z, $z, $n + 1); # z = 2^(n+1)
2140             Math::GMPz::Rmpz_sub_ui($z, $z, 2); # z = z-2
2141              
2142             Math::MPFR::Rmpfr_mul_z($f, $f, $z, $ROUND); # f = f*z
2143             Math::MPFR::Rmpfr_round($f, $f); # f = [f]
2144              
2145             my $q = Math::GMPq::Rmpq_init();
2146             Math::MPFR::Rmpfr_get_q($q, $f); # q = f
2147             Math::GMPq::Rmpq_set_den($q, $z); # q = q/z
2148             Math::GMPq::Rmpq_canonicalize($q); # remove common factors
2149              
2150             Math::GMPq::Rmpq_neg($q, $q) if $n % 4 == 0; # q = -q (iff 4|n)
2151             return bless \$q, __PACKAGE__;
2152             }
2153              
2154             #<<<
2155             my @D = (
2156             Math::GMPz::Rmpz_init_set_ui(0),
2157             Math::GMPz::Rmpz_init_set_ui(1),
2158             map { Math::GMPz::Rmpz_init_set_ui(0) } (1 .. $n/2 - 1)
2159             );
2160             #>>>
2161              
2162             my ($h, $w) = (1, 1);
2163             foreach my $i (0 .. $n - 1) {
2164             if ($w ^= 1) {
2165             Math::GMPz::Rmpz_add($D[$_], $D[$_], $D[$_ - 1]) for (1 .. $h - 1);
2166             }
2167             else {
2168             $w = $h++;
2169             Math::GMPz::Rmpz_add($D[$w], $D[$w], $D[$w + 1]) while --$w;
2170             }
2171             }
2172              
2173             my $den = Math::GMPz::Rmpz_init_set($ONE_Z);
2174             Math::GMPz::Rmpz_mul_2exp($den, $den, $n + 1);
2175             Math::GMPz::Rmpz_sub_ui($den, $den, 2);
2176             Math::GMPz::Rmpz_neg($den, $den) if $n % 4 == 0;
2177              
2178             my $r = Math::GMPq::Rmpq_init();
2179             Math::GMPq::Rmpq_set_num($r, $D[$h - 1]);
2180             Math::GMPq::Rmpq_set_den($r, $den);
2181             Math::GMPq::Rmpq_canonicalize($r);
2182              
2183             bless \$r, __PACKAGE__;
2184             }
2185              
2186             =head2 harmfrac
2187              
2188             $n->harmfrac # => BigNum | Nan
2189              
2190             Returns the nth-Harmonic number C. The harmonic numbers are the sum of
2191             reciprocals of the first C natural numbers: C<1 + 1/2 + 1/3 + ... + 1/n>.
2192              
2193             For values greater than 7000, binary splitting (Fredrik Johansson's elegant formulation) is used.
2194              
2195             =cut
2196              
2197             sub harmfrac {
2198             my ($n) = @_;
2199              
2200             my $ui = CORE::int(Math::GMPq::Rmpq_get_d($$n));
2201              
2202             $ui || return zero();
2203             $ui < 0 and return nan();
2204              
2205             # Use binary splitting for large values of n. (by Fredrik Johansson)
2206             # http://fredrik-j.blogspot.ro/2009/02/how-not-to-compute-harmonic-numbers.html
2207             if ($ui > 7000) {
2208              
2209             my $num = Math::GMPz::Rmpz_init_set_ui(1);
2210              
2211             my $den = Math::GMPz::Rmpz_init();
2212             Math::GMPz::Rmpz_set_q($den, $$n);
2213             Math::GMPz::Rmpz_add_ui($den, $den, 1);
2214              
2215             my $temp = Math::GMPz::Rmpz_init();
2216              
2217             # Inspired by Dana Jacobsen's code from Math::Prime::Util::{PP,GMP}.
2218             # https://metacpan.org/pod/Math::Prime::Util::PP
2219             # https://metacpan.org/pod/Math::Prime::Util::GMP
2220             my $sub;
2221             $sub = sub {
2222             my ($num, $den) = @_;
2223             Math::GMPz::Rmpz_sub($temp, $den, $num);
2224              
2225             if (Math::GMPz::Rmpz_cmp_ui($temp, 1) == 0) {
2226             Math::GMPz::Rmpz_set($den, $num);
2227             Math::GMPz::Rmpz_set_ui($num, 1);
2228             }
2229             elsif (Math::GMPz::Rmpz_cmp_ui($temp, 2) == 0) {
2230             Math::GMPz::Rmpz_set($den, $num);
2231             Math::GMPz::Rmpz_mul_2exp($num, $num, 1);
2232             Math::GMPz::Rmpz_add_ui($num, $num, 1);
2233             Math::GMPz::Rmpz_addmul($den, $den, $den);
2234             }
2235             else {
2236             Math::GMPz::Rmpz_add($temp, $num, $den);
2237             Math::GMPz::Rmpz_tdiv_q_2exp($temp, $temp, 1);
2238             my $q = Math::GMPz::Rmpz_init_set($temp);
2239             my $r = Math::GMPz::Rmpz_init_set($temp);
2240             $sub->($num, $q);
2241             $sub->($r, $den);
2242             Math::GMPz::Rmpz_mul($num, $num, $den);
2243             Math::GMPz::Rmpz_mul($temp, $q, $r);
2244             Math::GMPz::Rmpz_add($num, $num, $temp);
2245             Math::GMPz::Rmpz_mul($den, $den, $q);
2246             }
2247             };
2248              
2249             $sub->($num, $den);
2250              
2251             my $q = Math::GMPq::Rmpq_init();
2252             Math::GMPq::Rmpq_set_num($q, $num);
2253             Math::GMPq::Rmpq_set_den($q, $den);
2254             Math::GMPq::Rmpq_canonicalize($q);
2255              
2256             return bless \$q, __PACKAGE__;
2257             }
2258              
2259             my $num = Math::GMPz::Rmpz_init_set_ui(1);
2260             my $den = Math::GMPz::Rmpz_init_set_ui(1);
2261              
2262             for (my $k = 2 ; $k <= $ui ; ++$k) {
2263             Math::GMPz::Rmpz_mul_ui($num, $num, $k); # num = num * k
2264             Math::GMPz::Rmpz_add($num, $num, $den); # num = num + den
2265             Math::GMPz::Rmpz_mul_ui($den, $den, $k); # den = den * k
2266             }
2267              
2268             my $r = Math::GMPq::Rmpq_init();
2269             Math::GMPq::Rmpq_set_num($r, $num);
2270             Math::GMPq::Rmpq_set_den($r, $den);
2271             Math::GMPq::Rmpq_canonicalize($r);
2272              
2273             bless \$r, __PACKAGE__;
2274             }
2275              
2276             ############################ FLOATING-POINT OPERATIONS ############################
2277              
2278             =head1 FLOATING-POINT OPERATIONS
2279              
2280             All the operations in this section are done with floating-point approximations,
2281             which are, in the end, converted to fraction-approximations.
2282             In some cases, the results are 100% exact, but this is not guaranteed.
2283              
2284             =cut
2285              
2286             =head2 fadd
2287              
2288             $x->fadd(BigNum) # => BigNum
2289             $x->fadd(Scalar) # => BigNum
2290              
2291             Floating-point addition of C and C.
2292              
2293             =cut
2294              
2295             Class::Multimethods::multimethod fadd => qw(Math::BigNum Math::BigNum) => sub {
2296             my ($x, $y) = @_;
2297             $x = _big2mpfr($x);
2298             Math::MPFR::Rmpfr_add($x, $x, _big2mpfr($y), $ROUND);
2299             _mpfr2big($x);
2300             };
2301              
2302             Class::Multimethods::multimethod fadd => qw(Math::BigNum $) => sub {
2303             my ($x, $y) = @_;
2304              
2305             my $r = _big2mpfr($x);
2306             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
2307             $y >= 0
2308             ? Math::MPFR::Rmpfr_add_ui($r, $r, $y, $ROUND)
2309             : Math::MPFR::Rmpfr_add_si($r, $r, $y, $ROUND);
2310             }
2311             else {
2312             Math::MPFR::Rmpfr_add($r, $r, _str2mpfr($y) // (return Math::BigNum->new($y)->bfadd($x)), $ROUND);
2313             }
2314             _mpfr2big($r);
2315             };
2316              
2317             Class::Multimethods::multimethod fadd => qw(Math::BigNum *) => sub {
2318             Math::BigNum->new($_[1])->bfadd($_[0]);
2319             };
2320              
2321             Class::Multimethods::multimethod fadd => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1] };
2322             Class::Multimethods::multimethod fadd => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
2323              
2324             =head2 bfadd
2325              
2326             $x->bfadd(BigNum) # => BigNum
2327             $x->bfadd(Scalar) # => BigNum
2328              
2329             Floating-point addition of C and C, changing C in-place.
2330              
2331             =cut
2332              
2333             Class::Multimethods::multimethod bfadd => qw(Math::BigNum Math::BigNum) => sub {
2334             my ($x, $y) = @_;
2335             my $r = _big2mpfr($x);
2336             Math::MPFR::Rmpfr_add($r, $r, _big2mpfr($y), $ROUND);
2337             _mpfr2x($x, $r);
2338             };
2339              
2340             Class::Multimethods::multimethod bfadd => qw(Math::BigNum $) => sub {
2341             my ($x, $y) = @_;
2342              
2343             my $r = _big2mpfr($x);
2344             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
2345             $y >= 0
2346             ? Math::MPFR::Rmpfr_add_ui($r, $r, $y, $ROUND)
2347             : Math::MPFR::Rmpfr_add_si($r, $r, $y, $ROUND);
2348             }
2349             else {
2350             Math::MPFR::Rmpfr_add($r, $r, _str2mpfr($y) // (return $x->bfadd(Math::BigNum->new($y))), $ROUND);
2351             }
2352             _mpfr2x($x, $r);
2353             };
2354              
2355             Class::Multimethods::multimethod bfadd => qw(Math::BigNum *) => sub {
2356             $_[0]->bfadd(Math::BigNum->new($_[1]));
2357             };
2358              
2359             Class::Multimethods::multimethod bfadd => qw(Math::BigNum Math::BigNum::Inf) => \&_big2inf;
2360             Class::Multimethods::multimethod bfadd => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
2361              
2362             =head2 fsub
2363              
2364             $x->fsub(BigNum) # => BigNum
2365             $x->fsub(Scalar) # => BigNum
2366              
2367             Floating-point subtraction of C and C.
2368              
2369             =cut
2370              
2371             Class::Multimethods::multimethod fsub => qw(Math::BigNum Math::BigNum) => sub {
2372             my ($x, $y) = @_;
2373             $x = _big2mpfr($x);
2374             Math::MPFR::Rmpfr_sub($x, $x, _big2mpfr($y), $ROUND);
2375             _mpfr2big($x);
2376             };
2377              
2378             Class::Multimethods::multimethod fsub => qw(Math::BigNum $) => sub {
2379             my ($x, $y) = @_;
2380              
2381             my $r = _big2mpfr($x);
2382             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
2383             $y >= 0
2384             ? Math::MPFR::Rmpfr_sub_ui($r, $r, $y, $ROUND)
2385             : Math::MPFR::Rmpfr_sub_si($r, $r, $y, $ROUND);
2386             }
2387             else {
2388             Math::MPFR::Rmpfr_sub($r, $r, _str2mpfr($y) // (return Math::BigNum->new($y)->bneg->bfadd($x)), $ROUND);
2389             }
2390             _mpfr2big($r);
2391             };
2392              
2393             Class::Multimethods::multimethod fsub => qw(Math::BigNum *) => sub {
2394             Math::BigNum->new($_[1])->bneg->bfadd($_[0]);
2395             };
2396              
2397             Class::Multimethods::multimethod fsub => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->neg };
2398             Class::Multimethods::multimethod fsub => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
2399              
2400             =head2 bfsub
2401              
2402             $x->bfsub(BigNum) # => BigNum
2403             $x->bfsub(Scalar) # => BigNum
2404              
2405             Floating-point subtraction of C and C, changing C in-place.
2406              
2407             =cut
2408              
2409             Class::Multimethods::multimethod bfsub => qw(Math::BigNum Math::BigNum) => sub {
2410             my ($x, $y) = @_;
2411             my $r = _big2mpfr($x);
2412             Math::MPFR::Rmpfr_sub($r, $r, _big2mpfr($y), $ROUND);
2413             _mpfr2x($x, $r);
2414             };
2415              
2416             Class::Multimethods::multimethod bfsub => qw(Math::BigNum $) => sub {
2417             my ($x, $y) = @_;
2418              
2419             my $r = _big2mpfr($x);
2420             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
2421             $y >= 0
2422             ? Math::MPFR::Rmpfr_sub_ui($r, $r, $y, $ROUND)
2423             : Math::MPFR::Rmpfr_sub_si($r, $r, $y, $ROUND);
2424             }
2425             else {
2426             Math::MPFR::Rmpfr_sub($r, $r, _str2mpfr($y) // (return $x->bfsub(Math::BigNum->new($y))), $ROUND);
2427             }
2428             _mpfr2x($x, $r);
2429             };
2430              
2431             Class::Multimethods::multimethod bfsub => qw(Math::BigNum *) => sub {
2432             $_[0]->bfsub(Math::BigNum->new($_[1]));
2433             };
2434              
2435             Class::Multimethods::multimethod bfsub => qw(Math::BigNum Math::BigNum::Inf) => \&_big2ninf;
2436             Class::Multimethods::multimethod bfsub => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
2437              
2438             =head2 fmul
2439              
2440             $x->fmul(BigNum) # => BigNum
2441             $x->fmul(Scalar) # => BigNum
2442              
2443             Floating-point multiplication of C by C.
2444              
2445             =cut
2446              
2447             Class::Multimethods::multimethod fmul => qw(Math::BigNum Math::BigNum) => sub {
2448             my ($x, $y) = @_;
2449             $x = _big2mpfr($x);
2450             Math::MPFR::Rmpfr_mul($x, $x, _big2mpfr($y), $ROUND);
2451             _mpfr2big($x);
2452             };
2453              
2454             Class::Multimethods::multimethod fmul => qw(Math::BigNum $) => sub {
2455             my ($x, $y) = @_;
2456              
2457             my $r = _big2mpfr($x);
2458             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
2459             $y >= 0
2460             ? Math::MPFR::Rmpfr_mul_ui($r, $r, $y, $ROUND)
2461             : Math::MPFR::Rmpfr_mul_si($r, $r, $y, $ROUND);
2462             }
2463             else {
2464             Math::MPFR::Rmpfr_mul($r, $r, _str2mpfr($y) // (return Math::BigNum->new($y)->bfmul($x)), $ROUND);
2465             }
2466             _mpfr2big($r);
2467             };
2468              
2469             Class::Multimethods::multimethod fmul => qw(Math::BigNum *) => sub {
2470             Math::BigNum->new($_[1])->bfmul($_[0]);
2471             };
2472              
2473             Class::Multimethods::multimethod fmul => qw(Math::BigNum Math::BigNum::Inf) => sub {
2474             my $sign = Math::GMPq::Rmpq_sgn(${$_[0]});
2475             $sign < 0 ? $_[1]->neg : $sign > 0 ? $_[1]->copy : nan;
2476             };
2477              
2478             Class::Multimethods::multimethod fmul => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
2479              
2480             =head2 bfmul
2481              
2482             $x->bfmul(BigNum) # => BigNum
2483             $x->bfmul(Scalar) # => BigNum
2484              
2485             Floating-point multiplication of C by C, changing C in-place.
2486              
2487             =cut
2488              
2489             Class::Multimethods::multimethod bfmul => qw(Math::BigNum Math::BigNum) => sub {
2490             my ($x, $y) = @_;
2491             my $r = _big2mpfr($x);
2492             Math::MPFR::Rmpfr_mul($r, $r, _big2mpfr($y), $ROUND);
2493             _mpfr2x($x, $r);
2494             };
2495              
2496             Class::Multimethods::multimethod bfmul => qw(Math::BigNum $) => sub {
2497             my ($x, $y) = @_;
2498              
2499             my $r = _big2mpfr($x);
2500             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
2501             $y >= 0
2502             ? Math::MPFR::Rmpfr_mul_ui($r, $r, $y, $ROUND)
2503             : Math::MPFR::Rmpfr_mul_si($r, $r, $y, $ROUND);
2504             }
2505             else {
2506             Math::MPFR::Rmpfr_mul($r, $r, _str2mpfr($y) // (return $x->bfmul(Math::BigNum->new($y))), $ROUND);
2507             }
2508             _mpfr2x($x, $r);
2509             };
2510              
2511             Class::Multimethods::multimethod bfmul => qw(Math::BigNum *) => sub {
2512             $_[0]->bfmul(Math::BigNum->new($_[1]));
2513             };
2514              
2515             Class::Multimethods::multimethod bfmul => qw(Math::BigNum Math::BigNum::Inf) => sub {
2516             my ($x) = @_;
2517             my $sign = Math::GMPq::Rmpq_sgn($$x);
2518             $sign < 0 ? _big2ninf(@_) : $sign > 0 ? _big2inf(@_) : $x->bnan;
2519             };
2520              
2521             Class::Multimethods::multimethod bfmul => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
2522              
2523             =head2 fdiv
2524              
2525             $x->fdiv(BigNum) # => BigNum | Nan | Inf
2526             $x->fdiv(Scalar) # => BigNum | Nan | Inf
2527              
2528             Floating-point division of C by C.
2529              
2530             =cut
2531              
2532             Class::Multimethods::multimethod fdiv => qw(Math::BigNum Math::BigNum) => sub {
2533             my ($x, $y) = @_;
2534             $x = _big2mpfr($x);
2535             Math::MPFR::Rmpfr_div($x, $x, _big2mpfr($y), $ROUND);
2536             _mpfr2big($x);
2537             };
2538              
2539             Class::Multimethods::multimethod fdiv => qw(Math::BigNum $) => sub {
2540             my ($x, $y) = @_;
2541              
2542             my $r = _big2mpfr($x);
2543             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
2544             $y >= 0
2545             ? Math::MPFR::Rmpfr_div_ui($r, $r, $y, $ROUND)
2546             : Math::MPFR::Rmpfr_div_si($r, $r, $y, $ROUND);
2547             }
2548             else {
2549             Math::MPFR::Rmpfr_div($r, $r, _str2mpfr($y) // (return Math::BigNum->new($y)->bfdiv($x)->binv), $ROUND);
2550             }
2551             _mpfr2big($r);
2552             };
2553              
2554             Class::Multimethods::multimethod fdiv => qw(Math::BigNum *) => sub {
2555             Math::BigNum->new($_[1])->bfdiv($_[0])->binv;
2556             };
2557              
2558             Class::Multimethods::multimethod fdiv => qw(Math::BigNum Math::BigNum::Inf) => \&zero;
2559             Class::Multimethods::multimethod fdiv => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
2560              
2561             =head2 bfdiv
2562              
2563             $x->bfdiv(BigNum) # => BigNum | Nan | Inf
2564             $x->bfdiv(Scalar) # => BigNum | Nan | Inf
2565              
2566             Floating-point division of C by C, changing C in-place.
2567              
2568             =cut
2569              
2570             Class::Multimethods::multimethod bfdiv => qw(Math::BigNum Math::BigNum) => sub {
2571             my ($x, $y) = @_;
2572             my $r = _big2mpfr($x);
2573             Math::MPFR::Rmpfr_div($r, $r, _big2mpfr($y), $ROUND);
2574             _mpfr2x($x, $r);
2575             };
2576              
2577             Class::Multimethods::multimethod bfdiv => qw(Math::BigNum $) => sub {
2578             my ($x, $y) = @_;
2579              
2580             my $r = _big2mpfr($x);
2581             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
2582             $y >= 0
2583             ? Math::MPFR::Rmpfr_div_ui($r, $r, $y, $ROUND)
2584             : Math::MPFR::Rmpfr_div_si($r, $r, $y, $ROUND);
2585             }
2586             else {
2587             Math::MPFR::Rmpfr_div($r, $r, _str2mpfr($y) // (return $x->bfdiv(Math::BigNum->new($y))), $ROUND);
2588             }
2589             _mpfr2x($x, $r);
2590             };
2591              
2592             Class::Multimethods::multimethod bfdiv => qw(Math::BigNum *) => sub {
2593             $_[0]->bfdiv(Math::BigNum->new($_[1]));
2594             };
2595              
2596             Class::Multimethods::multimethod bfdiv => qw(Math::BigNum Math::BigNum::Inf) => \&bzero;
2597             Class::Multimethods::multimethod bfdiv => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
2598              
2599             =head2 fpow
2600              
2601             $x->fpow(BigNum) # => BigNum | Inf | Nan
2602             $x->fpow(Scalar) # => BigNum | Inf | Nan
2603              
2604             Raises C to power C. Returns Nan when C is negative
2605             and C is not an integer.
2606              
2607             =cut
2608              
2609             Class::Multimethods::multimethod fpow => qw(Math::BigNum Math::BigNum) => sub {
2610             my ($x, $y) = @_;
2611             my $r = _big2mpfr($x);
2612             Math::MPFR::Rmpfr_pow($r, $r, _big2mpfr($y), $ROUND);
2613             _mpfr2big($r);
2614             };
2615              
2616             Class::Multimethods::multimethod fpow => qw(Math::BigNum $) => sub {
2617             my ($x, $y) = @_;
2618             my $r = _big2mpfr($x);
2619             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
2620             $y >= 0
2621             ? Math::MPFR::Rmpfr_pow_ui($r, $r, $y, $ROUND)
2622             : Math::MPFR::Rmpfr_pow_si($r, $r, $y, $ROUND);
2623             }
2624             else {
2625             Math::MPFR::Rmpfr_pow($r, $r, _str2mpfr($y) // (return $x->fpow(Math::BigNum->new($y))), $ROUND);
2626             }
2627             _mpfr2big($r);
2628             };
2629              
2630             Class::Multimethods::multimethod fpow => qw(Math::BigNum *) => sub {
2631             $_[0]->fpow(Math::BigNum->new($_[1]));
2632             };
2633              
2634             Class::Multimethods::multimethod fpow => qw(Math::BigNum Math::BigNum::Inf) => sub {
2635             $_[0]->pow($_[1]);
2636             };
2637              
2638             Class::Multimethods::multimethod fpow => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
2639              
2640             =head2 bfpow
2641              
2642             $x->bfpow(BigNum) # => BigNum | Inf | Nan
2643             $x->bfpow(Scalar) # => BigNum | Inf | Nan
2644              
2645             Raises C to power C, changing C in-place. Promotes C to Nan when C is negative
2646             and C is not an integer.
2647              
2648             =cut
2649              
2650             Class::Multimethods::multimethod bfpow => qw(Math::BigNum Math::BigNum) => sub {
2651             my ($x, $y) = @_;
2652             my $r = _big2mpfr($x);
2653             Math::MPFR::Rmpfr_pow($r, $r, _big2mpfr($y), $ROUND);
2654             _mpfr2x($x, $r);
2655             };
2656              
2657             Class::Multimethods::multimethod bfpow => qw(Math::BigNum $) => sub {
2658             my ($x, $y) = @_;
2659             my $r = _big2mpfr($x);
2660             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
2661             $y >= 0
2662             ? Math::MPFR::Rmpfr_pow_ui($r, $r, $y, $ROUND)
2663             : Math::MPFR::Rmpfr_pow_si($r, $r, $y, $ROUND);
2664             }
2665             else {
2666             Math::MPFR::Rmpfr_pow($r, $r, _str2mpfr($y) // (return $x->fpow(Math::BigNum->new($y))), $ROUND);
2667             }
2668             _mpfr2x($x, $r);
2669             };
2670              
2671             Class::Multimethods::multimethod bfpow => qw(Math::BigNum *) => sub {
2672             $_[0]->bfpow(Math::BigNum->new($_[1]));
2673             };
2674              
2675             Class::Multimethods::multimethod bfpow => qw(Math::BigNum Math::BigNum::Inf) => sub {
2676             $_[0]->bpow($_[1]);
2677             };
2678              
2679             Class::Multimethods::multimethod bfpow => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
2680              
2681             =head2 fmod
2682              
2683             $x->fmod(BigNum) # => BigNum | Nan
2684             $x->fmod(Scalar) # => BigNum | Nan
2685              
2686             The remainder of C when is divided by C. Nan is returned when C is zero.
2687              
2688             =cut
2689              
2690             Class::Multimethods::multimethod fmod => qw(Math::BigNum Math::BigNum) => sub {
2691             my ($x, $y) = @_;
2692              
2693             $x = _big2mpfr($x);
2694             $y = _big2mpfr($y);
2695              
2696             Math::MPFR::Rmpfr_fmod($x, $x, $y, $ROUND);
2697              
2698             my $sign_r = Math::MPFR::Rmpfr_sgn($x);
2699             if (!$sign_r) {
2700             return (zero); # return faster
2701             }
2702             elsif ($sign_r > 0 xor Math::MPFR::Rmpfr_sgn($y) > 0) {
2703             Math::MPFR::Rmpfr_add($x, $x, $y, $ROUND);
2704             }
2705              
2706             _mpfr2big($x);
2707             };
2708              
2709             Class::Multimethods::multimethod fmod => qw(Math::BigNum $) => sub {
2710             my ($x, $y) = @_;
2711              
2712             my $m = _str2mpfr($y) // return $x->fmod(Math::BigNum->new($y));
2713             my $r = _big2mpfr($x);
2714              
2715             Math::MPFR::Rmpfr_fmod($r, $r, $m, $ROUND);
2716              
2717             my $sign_r = Math::MPFR::Rmpfr_sgn($r);
2718             if (!$sign_r) {
2719             return (zero); # return faster
2720             }
2721             elsif ($sign_r > 0 xor Math::MPFR::Rmpfr_sgn($m) > 0) {
2722             Math::MPFR::Rmpfr_add($r, $r, $m, $ROUND);
2723             }
2724              
2725             _mpfr2big($r);
2726             };
2727              
2728             Class::Multimethods::multimethod fmod => qw(Math::BigNum *) => sub {
2729             $_[0]->fmod(Math::BigNum->new($_[1]));
2730             };
2731              
2732             Class::Multimethods::multimethod fmod => qw(Math::BigNum Math::BigNum::Inf) => sub {
2733             $_[0]->copy->bmod($_[1]);
2734             };
2735              
2736             Class::Multimethods::multimethod fmod => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
2737              
2738             =head2 bfmod
2739              
2740             $x->bfmod(BigNum) # => BigNum | Nan
2741             $x->bfmod(Scalar) # => BigNum | Nan
2742              
2743             The remainder of C when is divided by C, changing C in-place.
2744             Promotes C to Nan when C is zero.
2745              
2746             =cut
2747              
2748             Class::Multimethods::multimethod bfmod => qw(Math::BigNum Math::BigNum) => sub {
2749             my ($x, $y) = @_;
2750              
2751             my $r = _big2mpfr($x);
2752             my $m = _big2mpfr($y);
2753              
2754             Math::MPFR::Rmpfr_fmod($r, $r, $m, $ROUND);
2755              
2756             my $sign_r = Math::MPFR::Rmpfr_sgn($r);
2757             if (!$sign_r) {
2758             return $x->bzero; # return faster
2759             }
2760             elsif ($sign_r > 0 xor Math::MPFR::Rmpfr_sgn($m) > 0) {
2761             Math::MPFR::Rmpfr_add($r, $r, $m, $ROUND);
2762             }
2763              
2764             _mpfr2x($x, $r);
2765             };
2766              
2767             Class::Multimethods::multimethod bfmod => qw(Math::BigNum $) => sub {
2768             my ($x, $y) = @_;
2769              
2770             my $m = _str2mpfr($y) // return $x->bfmod(Math::BigNum->new($y));
2771             my $r = _big2mpfr($x);
2772              
2773             Math::MPFR::Rmpfr_fmod($r, $r, $m, $ROUND);
2774              
2775             my $sign_r = Math::MPFR::Rmpfr_sgn($r);
2776             if (!$sign_r) {
2777             return $x->bzero; # return faster
2778             }
2779             elsif ($sign_r > 0 xor Math::MPFR::Rmpfr_sgn($m) > 0) {
2780             Math::MPFR::Rmpfr_add($r, $r, $m, $ROUND);
2781             }
2782              
2783             _mpfr2x($x, $r);
2784             };
2785              
2786             Class::Multimethods::multimethod bfmod => qw(Math::BigNum *) => sub {
2787             $_[0]->bfmod(Math::BigNum->new($_[1]));
2788             };
2789              
2790             Class::Multimethods::multimethod bfmod => qw(Math::BigNum Math::BigNum::Inf) => sub {
2791             $_[0]->bmod($_[1]);
2792             };
2793              
2794             Class::Multimethods::multimethod bfmod => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
2795              
2796             =head2 sqrt
2797              
2798             $x->sqrt # => BigNum | Nan
2799             sqrt($x) # => BigNum | Nan
2800              
2801             Square root of C. Returns Nan when C is negative.
2802              
2803             =cut
2804              
2805             sub sqrt {
2806             my ($x) = @_;
2807             my $r = _big2mpfr($x);
2808             Math::MPFR::Rmpfr_sqrt($r, $r, $ROUND);
2809             _mpfr2big($r);
2810             }
2811              
2812             =head2 bsqrt
2813              
2814             $x->bsqrt # => BigNum | Nan
2815              
2816             Square root of C, changing C in-place. Promotes C to Nan when C is negative.
2817              
2818             =cut
2819              
2820             sub bsqrt {
2821             my ($x) = @_;
2822             my $r = _big2mpfr($x);
2823             Math::MPFR::Rmpfr_sqrt($r, $r, $ROUND);
2824             _mpfr2x($x, $r);
2825             }
2826              
2827             =head2 cbrt
2828              
2829             $x->cbrt # => BigNum | Nan
2830              
2831             Cube root of C. Returns Nan when C is negative.
2832              
2833             =cut
2834              
2835             sub cbrt {
2836             my ($x) = @_;
2837             my $r = _big2mpfr($x);
2838             Math::MPFR::Rmpfr_cbrt($r, $r, $ROUND);
2839             _mpfr2big($r);
2840             }
2841              
2842             =head2 root
2843              
2844             $x->root(BigNum) # => BigNum | Nan
2845             $x->root(Scalar) # => BigNum | Nan
2846              
2847             Nth root of C. Returns Nan when C is negative.
2848              
2849             =cut
2850              
2851             Class::Multimethods::multimethod root => qw(Math::BigNum Math::BigNum) => sub {
2852             my ($x, $y) = @_;
2853              
2854             if (Math::GMPq::Rmpq_sgn($$y) > 0 and Math::GMPq::Rmpq_integer_p($$y)) {
2855             $x = _big2mpfr($x);
2856             Math::MPFR::Rmpfr_root($x, $x, Math::GMPq::Rmpq_get_d($$y), $ROUND);
2857             _mpfr2big($x);
2858             }
2859             else {
2860             $x->pow($y->inv);
2861             }
2862             };
2863              
2864             =for comment
2865             Class::Multimethods::multimethod root => qw(Math::BigNum Math::BigNum::Complex) => sub {
2866             Math::BigNum::Complex->new($_[0])->pow($_[1]->inv);
2867             };
2868             =cut
2869              
2870             Class::Multimethods::multimethod root => qw(Math::BigNum $) => sub {
2871             my ($x, $y) = @_;
2872              
2873             if (CORE::int($y) eq $y and $y > 0 and $y <= MAX_UI) {
2874             $x = _big2mpfr($x);
2875             Math::MPFR::Rmpfr_root($x, $x, $y, $ROUND);
2876             _mpfr2big($x);
2877             }
2878             else {
2879             $x->pow(Math::BigNum->new($y)->binv);
2880             }
2881             };
2882              
2883             Class::Multimethods::multimethod root => qw(Math::BigNum *) => sub {
2884             $_[0]->root(Math::BigNum->new($_[1]));
2885             };
2886              
2887             Class::Multimethods::multimethod root => qw(Math::BigNum Math::BigNum::Inf) => \&one;
2888             Class::Multimethods::multimethod root => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
2889              
2890             =head2 broot
2891              
2892             $x->broot(BigNum) # => BigNum | Nan
2893             $x->broot(Scalar) # => BigNum(1)
2894              
2895             Nth root of C, changing C in-place. Promotes
2896             C to Nan when C is negative.
2897              
2898             =cut
2899              
2900             Class::Multimethods::multimethod broot => qw(Math::BigNum Math::BigNum) => sub {
2901             my ($x, $y) = @_;
2902              
2903             if (Math::GMPq::Rmpq_sgn($$y) > 0 and Math::GMPq::Rmpq_integer_p($$y)) {
2904             my $f = _big2mpfr($x);
2905             Math::MPFR::Rmpfr_root($f, $f, Math::GMPq::Rmpq_get_d($$y), $ROUND);
2906             _mpfr2x($x, $f);
2907             }
2908             else {
2909             $x->pow($y->inv);
2910             }
2911             };
2912              
2913             Class::Multimethods::multimethod broot => qw(Math::BigNum $) => sub {
2914             my ($x, $y) = @_;
2915              
2916             if (CORE::int($y) eq $y and $y > 0 and $y <= MAX_UI) {
2917             my $f = _big2mpfr($x);
2918             Math::MPFR::Rmpfr_root($f, $f, $y, $ROUND);
2919             _mpfr2x($x, $f);
2920             }
2921             else {
2922             $x->bpow(Math::BigNum->new($y)->binv);
2923             }
2924             };
2925              
2926             Class::Multimethods::multimethod broot => qw(Math::BigNum *) => sub {
2927             $_[0]->broot(Math::BigNum->new($_[1]));
2928             };
2929              
2930             =for comment
2931             Class::Multimethods::multimethod broot => qw(Math::BigNum Math::BigNum::Complex) => sub {
2932             my $complex = Math::BigNum::Complex->new($_[0])->bpow($_[1]->inv);
2933             _big2cplx($_[0], $complex);
2934             };
2935             =cut
2936              
2937             Class::Multimethods::multimethod broot => qw(Math::BigNum Math::BigNum::Inf) => \&bone;
2938             Class::Multimethods::multimethod broot => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
2939              
2940             =head2 ln
2941              
2942             $x->ln # => BigNum | Nan
2943              
2944             Logarithm of C in base I. Returns Nan when C is negative.
2945              
2946             =cut
2947              
2948             sub ln {
2949             my ($x) = @_;
2950             my $r = _big2mpfr($x);
2951             Math::MPFR::Rmpfr_log($r, $r, $ROUND);
2952             _mpfr2big($r);
2953             }
2954              
2955             =head2 bln
2956              
2957             $x->bln # => BigNum | Nan
2958              
2959             Logarithm of C in base I, changing the C in-place.
2960             Promotes C to Nan when C is negative.
2961              
2962             =cut
2963              
2964             sub bln {
2965             my ($x) = @_;
2966             my $r = _big2mpfr($x);
2967             Math::MPFR::Rmpfr_log($r, $r, $ROUND);
2968             _mpfr2x($x, $r);
2969             }
2970              
2971             =head2 log
2972              
2973             $x->log # => BigNum | Nan
2974             $x->log(BigNum) # => BigNum | Nan
2975             $x->log(Scalar) # => BigNum | Nan
2976             log(BigNum) # => BigNum | Nan
2977              
2978             Logarithm of C in base C. When C is not specified, it defaults to base e.
2979             Returns Nan when C is negative and -Inf when C is zero.
2980              
2981             =cut
2982              
2983             # Probably we should add cases when the base equals zero.
2984              
2985             # Example:
2986             # log(+42) / log(0) = 0
2987             # log(-42) / log(0) = 0
2988             # log( 0 ) / log(0) = undefined
2989              
2990             Class::Multimethods::multimethod log => qw(Math::BigNum Math::BigNum) => sub {
2991             my ($x, $y) = @_;
2992              
2993             # log(x,base) = log(x)/log(base)
2994             my $r = _big2mpfr($x);
2995             Math::MPFR::Rmpfr_log($r, $r, $ROUND);
2996             my $baseln = _big2mpfr($y);
2997             Math::MPFR::Rmpfr_log($baseln, $baseln, $ROUND);
2998             Math::MPFR::Rmpfr_div($r, $r, $baseln, $ROUND);
2999              
3000             _mpfr2big($r);
3001             };
3002              
3003             Class::Multimethods::multimethod log => qw(Math::BigNum $) => sub {
3004             my ($x, $y) = @_;
3005              
3006             if (CORE::int($y) eq $y and $y == 2) {
3007             my $r = _big2mpfr($x);
3008             Math::MPFR::Rmpfr_log2($r, $r, $ROUND);
3009             _mpfr2big($r);
3010             }
3011             elsif (CORE::int($y) eq $y and $y == 10) {
3012             my $r = _big2mpfr($x);
3013             Math::MPFR::Rmpfr_log10($r, $r, $ROUND);
3014             _mpfr2big($r);
3015             }
3016             else {
3017             my $baseln = _str2mpfr($y) // return $x->log(Math::BigNum->new($y));
3018             my $r = _big2mpfr($x);
3019             Math::MPFR::Rmpfr_log($r, $r, $ROUND);
3020             Math::MPFR::Rmpfr_log($baseln, $baseln, $ROUND);
3021             Math::MPFR::Rmpfr_div($r, $r, $baseln, $ROUND);
3022             _mpfr2big($r);
3023             }
3024             };
3025              
3026             Class::Multimethods::multimethod log => qw(Math::BigNum) => \&ln;
3027              
3028             Class::Multimethods::multimethod log => qw(Math::BigNum *) => sub {
3029             $_[0]->log(Math::BigNum->new($_[1]));
3030             };
3031              
3032             Class::Multimethods::multimethod log => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
3033              
3034             # log(+/-Inf) = +Inf
3035             # log(-42) / log(+/-Inf) = 0
3036             # log(+42) / log(+/-Inf) = 0
3037             # log(0) / log(+/-Inf) = NaN
3038              
3039             Class::Multimethods::multimethod log => qw(Math::BigNum Math::BigNum::Inf) => sub {
3040             Math::GMPq::Rmpq_sgn(${$_[0]}) == 0 ? nan() : zero();
3041             };
3042              
3043             =head2 blog
3044              
3045             $x->blog # => BigNum | Nan
3046             $x->blog(BigNum) # => BigNum | Nan
3047             $x->log(Scalar) # => BigNum | Nan
3048              
3049             Logarithm of C in base C, changing the C in-place.
3050             When C is not specified, it defaults to base I.
3051              
3052             =cut
3053              
3054             Class::Multimethods::multimethod blog => qw(Math::BigNum $) => sub {
3055             my ($x, $y) = @_;
3056              
3057             if (CORE::int($y) eq $y and $y == 2) {
3058             my $r = _big2mpfr($x);
3059             Math::MPFR::Rmpfr_log2($r, $r, $ROUND);
3060             _mpfr2x($x, $r);
3061              
3062             }
3063             elsif (CORE::int($y) eq $y and $y == 10) {
3064             my $r = _big2mpfr($x);
3065             Math::MPFR::Rmpfr_log10($r, $r, $ROUND);
3066             _mpfr2x($x, $r);
3067             }
3068             else {
3069             my $baseln = _str2mpfr($y) // return $x->blog(Math::BigNum->new($y));
3070             my $r = _big2mpfr($x);
3071             Math::MPFR::Rmpfr_log($r, $r, $ROUND);
3072             Math::MPFR::Rmpfr_log($baseln, $baseln, $ROUND);
3073             Math::MPFR::Rmpfr_div($r, $r, $baseln, $ROUND);
3074             _mpfr2x($x, $r);
3075             }
3076             };
3077              
3078             Class::Multimethods::multimethod blog => qw(Math::BigNum Math::BigNum) => sub {
3079             $_[0]->blog(Math::GMPq::Rmpq_get_d(${$_[1]}));
3080             };
3081              
3082             Class::Multimethods::multimethod blog => qw(Math::BigNum) => \&bln;
3083              
3084             Class::Multimethods::multimethod blog => qw(Math::BigNum *) => sub {
3085             $_[0]->blog(Math::BigNum->new($_[1]));
3086             };
3087              
3088             Class::Multimethods::multimethod blog => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
3089              
3090             Class::Multimethods::multimethod blog => qw(Math::BigNum Math::BigNum::Inf) => sub {
3091             Math::GMPq::Rmpq_sgn(${$_[0]}) == 0 ? $_[0]->bnan : $_[0]->bzero;
3092             };
3093              
3094             =head2 log2
3095              
3096             $x->log2 # => BigNum | Nan
3097              
3098             Logarithm of C in base 2. Returns Nan when C is negative.
3099              
3100             =cut
3101              
3102             sub log2 {
3103             my ($x) = @_;
3104             my $r = _big2mpfr($x);
3105             Math::MPFR::Rmpfr_log2($r, $r, $ROUND);
3106             _mpfr2big($r);
3107             }
3108              
3109             =head2 log10
3110              
3111             $x->log10 # => BigNum | Nan
3112              
3113             Logarithm of C in base 10. Returns Nan when C is negative.
3114              
3115             =cut
3116              
3117             sub log10 {
3118             my ($x) = @_;
3119             my $r = _big2mpfr($x);
3120             Math::MPFR::Rmpfr_log10($r, $r, $ROUND);
3121             _mpfr2big($r);
3122             }
3123              
3124             =head2 lgrt
3125              
3126             $x->lgrt # => BigNum | Nan
3127              
3128             Logarithmic-root of C, which is the largest solution to C, where C is known.
3129             It is defined in real numbers for values of x greater than or equal to C<0.7>.
3130              
3131             Example:
3132              
3133             100->lgrt # solves for x in `x^x = 100` and returns: `3.59728...`
3134              
3135             =cut
3136              
3137             sub lgrt {
3138             my ($x) = @_;
3139              
3140             my $d = _big2mpfr($x);
3141             Math::MPFR::Rmpfr_log($d, $d, $ROUND);
3142              
3143             my $p = Math::MPFR::Rmpfr_init2($PREC);
3144             Math::MPFR::Rmpfr_ui_pow_ui($p, 10, CORE::int($PREC / 4), $ROUND);
3145             Math::MPFR::Rmpfr_ui_div($p, 1, $p, $ROUND);
3146              
3147             $x = Math::MPFR::Rmpfr_init2($PREC);
3148             Math::MPFR::Rmpfr_set_ui($x, 1, $ROUND);
3149              
3150             my $y = Math::MPFR::Rmpfr_init2($PREC);
3151             Math::MPFR::Rmpfr_set_ui($y, 0, $ROUND);
3152              
3153             my $count = 0;
3154             my $tmp = Math::MPFR::Rmpfr_init2($PREC);
3155              
3156             while (1) {
3157             Math::MPFR::Rmpfr_sub($tmp, $x, $y, $ROUND);
3158             Math::MPFR::Rmpfr_cmpabs($tmp, $p) <= 0 and last;
3159              
3160             Math::MPFR::Rmpfr_set($y, $x, $ROUND);
3161              
3162             Math::MPFR::Rmpfr_log($tmp, $x, $ROUND);
3163             Math::MPFR::Rmpfr_add_ui($tmp, $tmp, 1, $ROUND);
3164              
3165             Math::MPFR::Rmpfr_add($x, $x, $d, $ROUND);
3166             Math::MPFR::Rmpfr_div($x, $x, $tmp, $ROUND);
3167             last if ++$count > $PREC;
3168             }
3169              
3170             _mpfr2big($x);
3171             }
3172              
3173             =head2 lambert_w
3174              
3175             $x->lambert_w # => BigNum | Nan
3176              
3177             The Lambert-W function, defined in real numbers. The value of C should not be less than C<-1/e>.
3178              
3179             Example:
3180              
3181             100->log->lambert_w->exp # solves for x in `x^x = 100` and returns: `3.59728...`
3182              
3183             =cut
3184              
3185             sub lambert_w {
3186             my ($x) = @_;
3187              
3188             my $sgn = Math::GMPq::Rmpq_sgn($$x);
3189              
3190             $sgn == 0 and return zero();
3191             Math::GMPq::Rmpq_equal($$x, $MONE) && return nan();
3192              
3193             my $d = _big2mpfr($x);
3194              
3195             $PREC = CORE::int($PREC);
3196             Math::MPFR::Rmpfr_ui_pow_ui((my $p = Math::MPFR::Rmpfr_init2($PREC)), 10, CORE::int($PREC / 4), $ROUND);
3197             Math::MPFR::Rmpfr_ui_div($p, 1, $p, $ROUND);
3198              
3199             Math::MPFR::Rmpfr_set_ui(($x = Math::MPFR::Rmpfr_init2($PREC)), 1, $ROUND);
3200             Math::MPFR::Rmpfr_set_ui((my $y = Math::MPFR::Rmpfr_init2($PREC)), 0, $ROUND);
3201              
3202             my $count = 0;
3203             my $tmp = Math::MPFR::Rmpfr_init2($PREC);
3204              
3205             while (1) {
3206             Math::MPFR::Rmpfr_sub($tmp, $x, $y, $ROUND);
3207             Math::MPFR::Rmpfr_cmpabs($tmp, $p) <= 0 and last;
3208              
3209             Math::MPFR::Rmpfr_set($y, $x, $ROUND);
3210              
3211             Math::MPFR::Rmpfr_log($tmp, $x, $ROUND);
3212             Math::MPFR::Rmpfr_add_ui($tmp, $tmp, 1, $ROUND);
3213              
3214             Math::MPFR::Rmpfr_add($x, $x, $d, $ROUND);
3215             Math::MPFR::Rmpfr_div($x, $x, $tmp, $ROUND);
3216             last if ++$count > $PREC;
3217             }
3218              
3219             Math::MPFR::Rmpfr_log($x, $x, $ROUND);
3220             _mpfr2big($x);
3221             }
3222              
3223             =head2 exp
3224              
3225             $x->exp # => BigNum
3226              
3227             Exponential of C in base e. (C)
3228              
3229             =cut
3230              
3231             sub exp {
3232             my $r = _big2mpfr($_[0]);
3233             Math::MPFR::Rmpfr_exp($r, $r, $ROUND);
3234             _mpfr2big($r);
3235             }
3236              
3237             =head2 bexp
3238              
3239             $x->bexp # => BigNum
3240              
3241             Exponential of C in base e, changing C in-place.
3242              
3243             =cut
3244              
3245             sub bexp {
3246             my ($x) = @_;
3247             my $r = _big2mpfr($x);
3248             Math::MPFR::Rmpfr_exp($r, $r, $ROUND);
3249             _mpfr2x($x, $r);
3250             }
3251              
3252             =head2 exp2
3253              
3254             $x->exp2 # => BigNum
3255              
3256             Exponential of C in base 2. (C<2^x>)
3257              
3258             =cut
3259              
3260             sub exp2 {
3261             my $r = _big2mpfr($_[0]);
3262             Math::MPFR::Rmpfr_exp2($r, $r, $ROUND);
3263             _mpfr2big($r);
3264             }
3265              
3266             =head2 exp10
3267              
3268             $x->exp10 # => BigNum
3269              
3270             Exponential of C in base 10. (C<10^x>)
3271              
3272             =cut
3273              
3274             sub exp10 {
3275             my $r = _big2mpfr($_[0]);
3276             Math::MPFR::Rmpfr_exp10($r, $r, $ROUND);
3277             _mpfr2big($r);
3278             }
3279              
3280             =head1 * Trigonometry
3281              
3282             =cut
3283              
3284             =head2 sin
3285              
3286             $x->sin # => BigNum
3287              
3288             Returns the sine of C.
3289              
3290             =cut
3291              
3292             sub sin {
3293             my $r = _big2mpfr($_[0]);
3294             Math::MPFR::Rmpfr_sin($r, $r, $ROUND);
3295             _mpfr2big($r);
3296             }
3297              
3298             =head2 asin
3299              
3300             $x->asin # => BigNum | Nan
3301              
3302             Returns the inverse sine of C.
3303             Returns Nan for x < -1 or x > 1.
3304              
3305             =cut
3306              
3307             sub asin {
3308             my ($x) = @_;
3309             my $r = _big2mpfr($x);
3310             Math::MPFR::Rmpfr_asin($r, $r, $ROUND);
3311             _mpfr2big($r);
3312             }
3313              
3314             =head2 sinh
3315              
3316             $x->sinh # => BigNum
3317              
3318             Returns the hyperbolic sine of C.
3319              
3320             =cut
3321              
3322             sub sinh {
3323             my $r = _big2mpfr($_[0]);
3324             Math::MPFR::Rmpfr_sinh($r, $r, $ROUND);
3325             _mpfr2big($r);
3326             }
3327              
3328             =head2 asinh
3329              
3330             $x->asinh # => BigNum
3331              
3332             Returns the inverse hyperbolic sine of C.
3333              
3334             =cut
3335              
3336             sub asinh {
3337             my $r = _big2mpfr($_[0]);
3338             Math::MPFR::Rmpfr_asinh($r, $r, $ROUND);
3339             _mpfr2big($r);
3340             }
3341              
3342             =head2 cos
3343              
3344             $x->cos # => BigNum
3345              
3346             Returns the cosine of C.
3347              
3348             =cut
3349              
3350             sub cos {
3351             my $r = _big2mpfr($_[0]);
3352             Math::MPFR::Rmpfr_cos($r, $r, $ROUND);
3353             _mpfr2big($r);
3354             }
3355              
3356             =head2 acos
3357              
3358             $x->acos # => BigNum | Nan
3359              
3360             Returns the inverse cosine of C.
3361             Returns Nan for x < -1 or x > 1.
3362              
3363             =cut
3364              
3365             sub acos {
3366             my ($x) = @_;
3367             my $r = _big2mpfr($x);
3368             Math::MPFR::Rmpfr_acos($r, $r, $ROUND);
3369             _mpfr2big($r);
3370             }
3371              
3372             =head2 cosh
3373              
3374             $x->cosh # => BigNum
3375              
3376             Returns the hyperbolic cosine of C.
3377              
3378             =cut
3379              
3380             sub cosh {
3381             my $r = _big2mpfr($_[0]);
3382             Math::MPFR::Rmpfr_cosh($r, $r, $ROUND);
3383             _mpfr2big($r);
3384             }
3385              
3386             =head2 acosh
3387              
3388             $x->acosh # => BigNum | Nan
3389              
3390             Returns the inverse hyperbolic cosine of C.
3391             Returns Nan for x < 1.
3392              
3393             =cut
3394              
3395             sub acosh {
3396             my ($x) = @_;
3397             my $r = _big2mpfr($x);
3398             Math::MPFR::Rmpfr_acosh($r, $r, $ROUND);
3399             _mpfr2big($r);
3400             }
3401              
3402             =head2 tan
3403              
3404             $x->tan # => BigNum
3405              
3406             Returns the tangent of C.
3407              
3408             =cut
3409              
3410             sub tan {
3411             my $r = _big2mpfr($_[0]);
3412             Math::MPFR::Rmpfr_tan($r, $r, $ROUND);
3413             _mpfr2big($r);
3414             }
3415              
3416             =head2 atan
3417              
3418             $x->atan # => BigNum
3419              
3420             Returns the inverse tangent of C.
3421              
3422             =cut
3423              
3424             sub atan {
3425             my $r = _big2mpfr($_[0]);
3426             Math::MPFR::Rmpfr_atan($r, $r, $ROUND);
3427             _mpfr2big($r);
3428             }
3429              
3430             =head2 tanh
3431              
3432             $x->tanh # => BigNum
3433              
3434             Returns the hyperbolic tangent of C.
3435              
3436             =cut
3437              
3438             sub tanh {
3439             my $r = _big2mpfr($_[0]);
3440             Math::MPFR::Rmpfr_tanh($r, $r, $ROUND);
3441             _mpfr2big($r);
3442             }
3443              
3444             =head2 atanh
3445              
3446             $x->atanh # => BigNum | Nan
3447              
3448             Returns the inverse hyperbolic tangent of C.
3449             Returns Nan for x <= -1 or x >= 1.
3450              
3451             =cut
3452              
3453             sub atanh {
3454             my ($x) = @_;
3455             my $r = _big2mpfr($x);
3456             Math::MPFR::Rmpfr_atanh($r, $r, $ROUND);
3457             _mpfr2big($r);
3458             }
3459              
3460             =head2 sec
3461              
3462             $x->sec # => BigNum
3463              
3464             Returns the secant of C.
3465              
3466             =cut
3467              
3468             sub sec {
3469             my $r = _big2mpfr($_[0]);
3470             Math::MPFR::Rmpfr_sec($r, $r, $ROUND);
3471             _mpfr2big($r);
3472             }
3473              
3474             =head2 asec
3475              
3476             $x->asec # => BigNum | Nan
3477              
3478             Returns the inverse secant of C.
3479             Returns Nan for x > -1 and x < 1.
3480              
3481             Defined as:
3482              
3483             asec(x) = acos(1/x)
3484              
3485             =cut
3486              
3487             #
3488             ## asec(x) = acos(1/x)
3489             #
3490             sub asec {
3491             my ($x) = @_;
3492             my $r = _big2mpfr($x);
3493             Math::MPFR::Rmpfr_ui_div($r, 1, $r, $ROUND);
3494             Math::MPFR::Rmpfr_acos($r, $r, $ROUND);
3495             _mpfr2big($r);
3496             }
3497              
3498             =head2 sech
3499              
3500             $x->sech # => BigNum
3501              
3502             Returns the hyperbolic secant of C.
3503              
3504             =cut
3505              
3506             sub sech {
3507             my $r = _big2mpfr($_[0]);
3508             Math::MPFR::Rmpfr_sech($r, $r, $ROUND);
3509             _mpfr2big($r);
3510             }
3511              
3512             =head2 asech
3513              
3514             $x->asech # => BigNum | Nan
3515              
3516             Returns the inverse hyperbolic secant of C.
3517             Returns a Nan for x < 0 or x > 1.
3518              
3519             Defined as:
3520              
3521             asech(x) = acosh(1/x)
3522              
3523             =cut
3524              
3525             #
3526             ## asech(x) = acosh(1/x)
3527             #
3528             sub asech {
3529             my ($x) = @_;
3530             my $r = _big2mpfr($x);
3531             Math::MPFR::Rmpfr_ui_div($r, 1, $r, $ROUND);
3532             Math::MPFR::Rmpfr_acosh($r, $r, $ROUND);
3533             _mpfr2big($r);
3534             }
3535              
3536             =head2 csc
3537              
3538             $x->csc # => BigNum
3539              
3540             Returns the cosecant of C.
3541              
3542             =cut
3543              
3544             sub csc {
3545             my $r = _big2mpfr($_[0]);
3546             Math::MPFR::Rmpfr_csc($r, $r, $ROUND);
3547             _mpfr2big($r);
3548             }
3549              
3550             =head2 acsc
3551              
3552             $x->acsc # => BigNum | Nan
3553              
3554             Returns the inverse cosecant of C.
3555             Returns Nan for x > -1 and x < 1.
3556              
3557             Defined as:
3558              
3559             acsc(x) = asin(1/x)
3560              
3561             =cut
3562              
3563             #
3564             ## acsc(x) = asin(1/x)
3565             #
3566             sub acsc {
3567             my ($x) = @_;
3568             my $r = _big2mpfr($x);
3569             Math::MPFR::Rmpfr_ui_div($r, 1, $r, $ROUND);
3570             Math::MPFR::Rmpfr_asin($r, $r, $ROUND);
3571             _mpfr2big($r);
3572             }
3573              
3574             =head2 csch
3575              
3576             $x->csch # => BigNum
3577              
3578             Returns the hyperbolic cosecant of C.
3579              
3580             =cut
3581              
3582             sub csch {
3583             my $r = _big2mpfr($_[0]);
3584             Math::MPFR::Rmpfr_csch($r, $r, $ROUND);
3585             _mpfr2big($r);
3586             }
3587              
3588             =head2 acsch
3589              
3590             $x->acsch # => BigNum
3591              
3592             Returns the inverse hyperbolic cosecant of C.
3593              
3594             Defined as:
3595              
3596             acsch(x) = asinh(1/x)
3597              
3598             =cut
3599              
3600             #
3601             ## acsch(x) = asinh(1/x)
3602             #
3603             sub acsch {
3604             my ($x) = @_;
3605             my $r = _big2mpfr($x);
3606             Math::MPFR::Rmpfr_ui_div($r, 1, $r, $ROUND);
3607             Math::MPFR::Rmpfr_asinh($r, $r, $ROUND);
3608             _mpfr2big($r);
3609             }
3610              
3611             =head2 cot
3612              
3613             $x->cot # => BigNum
3614              
3615             Returns the cotangent of C.
3616              
3617             =cut
3618              
3619             sub cot {
3620             my $r = _big2mpfr($_[0]);
3621             Math::MPFR::Rmpfr_cot($r, $r, $ROUND);
3622             _mpfr2big($r);
3623             }
3624              
3625             =head2 acot
3626              
3627             $x->acot # => BigNum
3628              
3629             Returns the inverse cotangent of C.
3630              
3631             Defined as:
3632              
3633             acot(x) = atan(1/x)
3634              
3635             =cut
3636              
3637             #
3638             ## acot(x) = atan(1/x)
3639             #
3640             sub acot {
3641             my ($x) = @_;
3642             my $r = _big2mpfr($x);
3643             Math::MPFR::Rmpfr_ui_div($r, 1, $r, $ROUND);
3644             Math::MPFR::Rmpfr_atan($r, $r, $ROUND);
3645             _mpfr2big($r);
3646             }
3647              
3648             =head2 coth
3649              
3650             $x->coth # => BigNum
3651              
3652             Returns the hyperbolic cotangent of C.
3653              
3654             =cut
3655              
3656             sub coth {
3657             my $r = _big2mpfr($_[0]);
3658             Math::MPFR::Rmpfr_coth($r, $r, $ROUND);
3659             _mpfr2big($r);
3660             }
3661              
3662             =head2 acoth
3663              
3664             $x->acoth # => BigNum
3665              
3666             Returns the inverse hyperbolic cotangent of C.
3667              
3668             Defined as:
3669              
3670             acoth(x) = atanh(1/x)
3671              
3672             =cut
3673              
3674             #
3675             ## acoth(x) = atanh(1/x)
3676             #
3677             sub acoth {
3678             my $r = _big2mpfr($_[0]);
3679             Math::MPFR::Rmpfr_ui_div($r, 1, $r, $ROUND);
3680             Math::MPFR::Rmpfr_atanh($r, $r, $ROUND);
3681             _mpfr2big($r);
3682             }
3683              
3684             =head2 atan2
3685              
3686             $x->atan2(BigNum) # => BigNum
3687             $x->atan2(Scalar) # => BigNum
3688              
3689             atan2(BigNum, BigNum) # => BigNum
3690             atan2(BigNum, Scalar) # => BigNum
3691             atan2(Scalar, BigNum) # => BigNum
3692              
3693             Arctangent of C and C. When C is -Inf returns PI when x >= 0, or C<-PI> when x < 0.
3694              
3695             =cut
3696              
3697             Class::Multimethods::multimethod atan2 => qw(Math::BigNum Math::BigNum) => sub {
3698             my $r = _big2mpfr($_[0]);
3699             Math::MPFR::Rmpfr_atan2($r, $r, _big2mpfr($_[1]), $ROUND);
3700             _mpfr2big($r);
3701             };
3702              
3703             Class::Multimethods::multimethod atan2 => qw(Math::BigNum $) => sub {
3704             my $f = _str2mpfr($_[1]) // return $_[0]->atan2(Math::BigNum->new($_[1]));
3705             my $r = _big2mpfr($_[0]);
3706             Math::MPFR::Rmpfr_atan2($r, $r, $f, $ROUND);
3707             _mpfr2big($r);
3708             };
3709              
3710             Class::Multimethods::multimethod atan2 => qw($ Math::BigNum) => sub {
3711             my $r = _str2mpfr($_[0]) // return Math::BigNum->new($_[0])->atan2($_[1]);
3712             Math::MPFR::Rmpfr_atan2($r, $r, _big2mpfr($_[1]), $ROUND);
3713             _mpfr2big($r);
3714             };
3715              
3716             Class::Multimethods::multimethod atan2 => qw(* Math::BigNum) => sub {
3717             Math::BigNum->new($_[0])->atan2($_[1]);
3718             };
3719              
3720             Class::Multimethods::multimethod atan2 => qw(Math::BigNum *) => sub {
3721             $_[0]->atan2(Math::BigNum->new($_[1]));
3722             };
3723              
3724             Class::Multimethods::multimethod atan2 => qw(Math::BigNum Math::BigNum::Inf) => sub {
3725             $_[1]->is_neg
3726             ? ((Math::GMPq::Rmpq_sgn(${$_[0]}) >= 0) ? pi() : (pi()->neg))
3727             : zero;
3728             };
3729              
3730             Class::Multimethods::multimethod atan2 => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
3731              
3732             =head1 * Special methods
3733              
3734             =cut
3735              
3736             =head2 agm
3737              
3738             $x->agm(BigNum) # => BigNum
3739             $x->agm(Scalar) # => BigNum
3740              
3741             Arithmetic-geometric mean of C and C.
3742              
3743             =cut
3744              
3745             Class::Multimethods::multimethod agm => qw(Math::BigNum Math::BigNum) => sub {
3746             my $r = _big2mpfr($_[0]);
3747             Math::MPFR::Rmpfr_agm($r, $r, _big2mpfr($_[1]), $ROUND);
3748             _mpfr2big($r);
3749             };
3750              
3751             Class::Multimethods::multimethod agm => qw(Math::BigNum $) => sub {
3752             my $f = _str2mpfr($_[1]) // return $_[0]->agm(Math::BigNum->new($_[1]));
3753             my $r = _big2mpfr($_[0]);
3754             Math::MPFR::Rmpfr_agm($r, $r, $f, $ROUND);
3755             _mpfr2big($r);
3756             };
3757              
3758             Class::Multimethods::multimethod agm => qw(Math::BigNum *) => sub {
3759             $_[0]->agm(Math::BigNum->new($_[1]));
3760             };
3761              
3762             Class::Multimethods::multimethod agm => qw(Math::BigNum Math::BigNum::Inf) => sub {
3763             $_[1]->is_pos ? $_[1]->copy : nan();
3764             };
3765              
3766             Class::Multimethods::multimethod agm => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
3767              
3768             =head2 hypot
3769              
3770             $x->hypot(BigNum) # => BigNum
3771             $x->hypot(Scalar) # => BigNum
3772              
3773             The value of the hypotenuse for catheti C and C. (C)
3774              
3775             =cut
3776              
3777             Class::Multimethods::multimethod hypot => qw(Math::BigNum Math::BigNum) => sub {
3778             my $r = _big2mpfr($_[0]);
3779             Math::MPFR::Rmpfr_hypot($r, $r, _big2mpfr($_[1]), $ROUND);
3780             _mpfr2big($r);
3781             };
3782              
3783             Class::Multimethods::multimethod hypot => qw(Math::BigNum $) => sub {
3784             my $f = _str2mpfr($_[1]) // return $_[0]->hypot(Math::BigNum->new($_[1]));
3785             my $r = _big2mpfr($_[0]);
3786             Math::MPFR::Rmpfr_hypot($r, $r, $f, $ROUND);
3787             _mpfr2big($r);
3788             };
3789              
3790             Class::Multimethods::multimethod hypot => qw(Math::BigNum *) => sub {
3791             $_[0]->hypot(Math::BigNum->new($_[1]));
3792             };
3793              
3794             Class::Multimethods::multimethod hypot => qw(Math::BigNum Math::BigNum::Inf) => \&inf;
3795             Class::Multimethods::multimethod hypot => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
3796              
3797             =head2 gamma
3798              
3799             $x->gamma # => BigNum | Inf | Nan
3800              
3801             The Gamma function on C. Returns Inf when C is zero, and Nan when C is negative.
3802              
3803             =cut
3804              
3805             sub gamma {
3806             my $r = _big2mpfr($_[0]);
3807             Math::MPFR::Rmpfr_gamma($r, $r, $ROUND);
3808             _mpfr2big($r);
3809             }
3810              
3811             =head2 lngamma
3812              
3813             $x->lngamma # => BigNum | Inf
3814              
3815             The natural logarithm of the Gamma function on C.
3816             Returns Inf when C is negative or equal to zero.
3817              
3818             =cut
3819              
3820             sub lngamma {
3821             my $r = _big2mpfr($_[0]);
3822             Math::MPFR::Rmpfr_lngamma($r, $r, $ROUND);
3823             _mpfr2big($r);
3824             }
3825              
3826             =head2 lgamma
3827              
3828             $x->lgamma # => BigNum | Inf
3829              
3830             The logarithm of the absolute value of the Gamma function.
3831             Returns Inf when C is negative or equal to zero.
3832              
3833             =cut
3834              
3835             sub lgamma {
3836             my $r = _big2mpfr($_[0]);
3837             Math::MPFR::Rmpfr_lgamma($r, $r, $ROUND);
3838             _mpfr2big($r);
3839             }
3840              
3841             =head2 digamma
3842              
3843             $x->digamma # => BigNum | Inf | Nan
3844              
3845             The Digamma function (sometimes also called Psi).
3846             Returns Nan when C is negative, and -Inf when C is 0.
3847              
3848             =cut
3849              
3850             sub digamma {
3851             my $r = _big2mpfr($_[0]);
3852             Math::MPFR::Rmpfr_digamma($r, $r, $ROUND);
3853             _mpfr2big($r);
3854             }
3855              
3856             =head2 beta
3857              
3858             $x->beta(BigNum) # => BigNum | Inf | Nan
3859              
3860             The beta function (also called the Euler integral of the first kind).
3861              
3862             Defined as:
3863              
3864             beta(x,y) = gamma(x)*gamma(y) / gamma(x+y)
3865              
3866             for x > 0 and y > 0.
3867              
3868             =cut
3869              
3870             Class::Multimethods::multimethod beta => qw(Math::BigNum Math::BigNum) => sub {
3871             my ($x, $y) = @_;
3872              
3873             $x = _big2mpfr($x);
3874             $y = _big2mpfr($y);
3875              
3876             my $t = Math::MPFR::Rmpfr_init2($PREC);
3877             Math::MPFR::Rmpfr_add($t, $x, $y, $ROUND);
3878             Math::MPFR::Rmpfr_gamma($t, $t, $ROUND);
3879             Math::MPFR::Rmpfr_gamma($x, $x, $ROUND);
3880             Math::MPFR::Rmpfr_gamma($y, $y, $ROUND);
3881             Math::MPFR::Rmpfr_mul($x, $x, $y, $ROUND);
3882             Math::MPFR::Rmpfr_div($x, $x, $t, $ROUND);
3883              
3884             _mpfr2big($x);
3885             };
3886              
3887             Class::Multimethods::multimethod beta => qw(Math::BigNum *) => sub {
3888             Math::BigNum->new($_[1])->beta($_[0]);
3889             };
3890              
3891             Class::Multimethods::multimethod beta => qw(Math::BigNum Math::BigNum::Inf) => \&nan;
3892             Class::Multimethods::multimethod beta => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
3893              
3894             =head2 zeta
3895              
3896             $x->zeta # => BigNum | Inf
3897              
3898             The Riemann zeta function at C. Returns Inf when C is 1.
3899              
3900             =cut
3901              
3902             sub zeta {
3903             my $r = _big2mpfr($_[0]);
3904             Math::MPFR::Rmpfr_zeta($r, $r, $ROUND);
3905             _mpfr2big($r);
3906             }
3907              
3908             =head2 eta
3909              
3910             $x->eta # => BigNum
3911              
3912             The Dirichlet eta function at C.
3913              
3914             Defined as:
3915              
3916             eta(1) = ln(2)
3917             eta(x) = (1 - 2**(1-x)) * zeta(x)
3918              
3919             =cut
3920              
3921             sub eta {
3922             my $r = _big2mpfr($_[0]);
3923              
3924             # Special case for eta(1) = log(2)
3925             if (!Math::MPFR::Rmpfr_cmp_ui($r, 1)) {
3926             Math::MPFR::Rmpfr_add_ui($r, $r, 1, $ROUND);
3927             Math::MPFR::Rmpfr_log($r, $r, $ROUND);
3928             return _mpfr2big($r);
3929             }
3930              
3931             my $p = Math::MPFR::Rmpfr_init2($PREC);
3932             Math::MPFR::Rmpfr_set($p, $r, $ROUND);
3933             Math::MPFR::Rmpfr_ui_sub($p, 1, $p, $ROUND);
3934             Math::MPFR::Rmpfr_ui_pow($p, 2, $p, $ROUND);
3935             Math::MPFR::Rmpfr_ui_sub($p, 1, $p, $ROUND);
3936              
3937             Math::MPFR::Rmpfr_zeta($r, $r, $ROUND);
3938             Math::MPFR::Rmpfr_mul($r, $r, $p, $ROUND);
3939              
3940             _mpfr2big($r);
3941             }
3942              
3943             =head2 bessel_j
3944              
3945             $x->bessel_j(BigNum) # => BigNum
3946             $x->bessel_j(Scalar) # => BigNum
3947              
3948             The first order Bessel function, C, where C is a signed integer.
3949              
3950             Example:
3951              
3952             $x->bessel_j($n) # represents J_n(x)
3953              
3954             =cut
3955              
3956             Class::Multimethods::multimethod bessel_j => qw(Math::BigNum Math::BigNum) => sub {
3957             my ($x, $n) = @_;
3958              
3959             $n = Math::GMPq::Rmpq_get_d($$n);
3960              
3961             if ($n < MIN_SI or $n > MAX_UI) {
3962             return zero();
3963             }
3964              
3965             $n = CORE::int($n);
3966             $x = _big2mpfr($x);
3967              
3968             if ($n == 0) {
3969             Math::MPFR::Rmpfr_j0($x, $x, $ROUND);
3970             }
3971             elsif ($n == 1) {
3972             Math::MPFR::Rmpfr_j1($x, $x, $ROUND);
3973             }
3974             else {
3975             Math::MPFR::Rmpfr_jn($x, $n, $x, $ROUND);
3976             }
3977              
3978             _mpfr2big($x);
3979             };
3980              
3981             Class::Multimethods::multimethod bessel_j => qw(Math::BigNum $) => sub {
3982             my ($x, $n) = @_;
3983              
3984             if (CORE::int($n) eq $n) {
3985              
3986             if ($n < MIN_SI or $n > MAX_UI) {
3987             return zero();
3988             }
3989              
3990             $x = _big2mpfr($x);
3991              
3992             if ($n == 0) {
3993             Math::MPFR::Rmpfr_j0($x, $x, $ROUND);
3994             }
3995             elsif ($n == 1) {
3996             Math::MPFR::Rmpfr_j1($x, $x, $ROUND);
3997             }
3998             else {
3999             Math::MPFR::Rmpfr_jn($x, $n, $x, $ROUND);
4000             }
4001             _mpfr2big($x);
4002             }
4003             else {
4004             $x->bessel_j(Math::BigNum->new($n));
4005             }
4006             };
4007              
4008             Class::Multimethods::multimethod bessel_j => qw(Math::BigNum *) => sub {
4009             $_[0]->bessel_j(Math::BigNum->new($_[1]));
4010             };
4011              
4012             Class::Multimethods::multimethod bessel_j => qw(Math::BigNum Math::BigNum::Inf) => \&zero;
4013             Class::Multimethods::multimethod bessel_j => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
4014              
4015             =head2 bessel_y
4016              
4017             $x->bessel_y(BigNum) # => BigNum | Inf | Nan
4018             $x->bessel_y(Scalar) # => BigNum | Inf | Nan
4019              
4020             The second order Bessel function, C, where C is a signed integer. Returns Nan for negative values of C.
4021              
4022             Example:
4023              
4024             $x->bessel_y($n) # represents Y_n(x)
4025              
4026             =cut
4027              
4028             Class::Multimethods::multimethod bessel_y => qw(Math::BigNum Math::BigNum) => sub {
4029             my ($x, $n) = @_;
4030              
4031             $n = Math::GMPq::Rmpq_get_d($$n);
4032              
4033             if ($n < MIN_SI or $n > MAX_UI) {
4034              
4035             if (Math::GMPq::Rmpq_sgn($$x) < 0) {
4036             return nan();
4037             }
4038              
4039             return ($n < 0 ? inf() : ninf());
4040             }
4041              
4042             $x = _big2mpfr($x);
4043             $n = CORE::int($n);
4044              
4045             if ($n == 0) {
4046             Math::MPFR::Rmpfr_y0($x, $x, $ROUND);
4047             }
4048             elsif ($n == 1) {
4049             Math::MPFR::Rmpfr_y1($x, $x, $ROUND);
4050             }
4051             else {
4052             Math::MPFR::Rmpfr_yn($x, $n, $x, $ROUND);
4053             }
4054              
4055             _mpfr2big($x);
4056             };
4057              
4058             Class::Multimethods::multimethod bessel_y => qw(Math::BigNum $) => sub {
4059             my ($x, $n) = @_;
4060              
4061             if (CORE::int($n) eq $n) {
4062              
4063             if ($n < MIN_SI or $n > MAX_UI) {
4064              
4065             if (Math::GMPq::Rmpq_sgn($$x) < 0) {
4066             return nan();
4067             }
4068              
4069             return ($n < 0 ? inf() : ninf());
4070             }
4071              
4072             $x = _big2mpfr($x);
4073              
4074             if ($n == 0) {
4075             Math::MPFR::Rmpfr_y0($x, $x, $ROUND);
4076             }
4077             elsif ($n == 1) {
4078             Math::MPFR::Rmpfr_y1($x, $x, $ROUND);
4079             }
4080             else {
4081             Math::MPFR::Rmpfr_yn($x, $n, $x, $ROUND);
4082             }
4083             _mpfr2big($x);
4084             }
4085             else {
4086             $x->bessel_y(Math::BigNum->new($n));
4087             }
4088             };
4089              
4090             Class::Multimethods::multimethod bessel_y => qw(Math::BigNum *) => sub {
4091             $_[0]->bessel_y(Math::BigNum->new($_[1]));
4092             };
4093              
4094             Class::Multimethods::multimethod bessel_y => qw(Math::BigNum Math::BigNum::Inf) => sub {
4095             Math::GMPq::Rmpq_sgn(${$_[0]}) < 0 ? nan() : $_[1]->neg;
4096             };
4097              
4098             Class::Multimethods::multimethod bessel_y => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
4099              
4100             =head2 bernreal
4101              
4102             $n->bernreal # => BigNum | Nan
4103              
4104             Returns the nth-Bernoulli number, as a floating-point approximation, with C.
4105              
4106             Returns Nan for negative values of C.
4107              
4108             =cut
4109              
4110             sub bernreal {
4111             my $n = CORE::int(Math::GMPq::Rmpq_get_d(${$_[0]}));
4112              
4113             # |B(n)| = zeta(n) * n! / 2^(n-1) / pi^n
4114              
4115             $n < 0 and return nan();
4116             $n == 0 and return one();
4117             $n == 1 and return Math::BigNum->new('1/2');
4118             $n % 2 and return zero(); # Bn = 0 for odd n>1
4119              
4120             #local $PREC = CORE::int($n*CORE::log($n)+1);
4121              
4122             my $f = Math::MPFR::Rmpfr_init2($PREC);
4123             my $p = Math::MPFR::Rmpfr_init2($PREC);
4124              
4125             Math::MPFR::Rmpfr_zeta_ui($f, $n, $ROUND); # f = zeta(n)
4126             Math::MPFR::Rmpfr_const_pi($p, $ROUND); # p = PI
4127             Math::MPFR::Rmpfr_pow_ui($p, $p, $n, $ROUND); # p = p^n
4128              
4129             my $z = Math::GMPz::Rmpz_init();
4130             Math::GMPz::Rmpz_fac_ui($z, $n); # z = n!
4131             Math::MPFR::Rmpfr_mul_z($f, $f, $z, $ROUND); # f = f * z
4132             Math::MPFR::Rmpfr_div_2exp($f, $f, $n - 1, $ROUND); # f = f / 2^(n-1)
4133              
4134             Math::MPFR::Rmpfr_div($f, $f, $p, $ROUND); # f = f/p
4135             Math::MPFR::Rmpfr_neg($f, $f, $ROUND) if $n % 4 == 0;
4136              
4137             _mpfr2big($f);
4138             }
4139              
4140             =head2 harmreal
4141              
4142             $n->harmreal # => BigNum | Nan
4143              
4144             Returns the nth-Harmonic number, as a floating-point approximation, for any real value of C >= 0.
4145              
4146             Defined as:
4147              
4148             harmreal(n) = digamma(n+1) + gamma
4149              
4150             where C is the Euler-Mascheroni constant.
4151              
4152             =cut
4153              
4154             sub harmreal {
4155             my ($n) = @_;
4156              
4157             $n = _big2mpfr($n);
4158             Math::MPFR::Rmpfr_add_ui($n, $n, 1, $ROUND);
4159             Math::MPFR::Rmpfr_digamma($n, $n, $ROUND);
4160              
4161             my $y = Math::MPFR::Rmpfr_init2($PREC);
4162             Math::MPFR::Rmpfr_const_euler($y, $ROUND);
4163             Math::MPFR::Rmpfr_add($n, $n, $y, $ROUND);
4164              
4165             _mpfr2big($n);
4166             }
4167              
4168             =head2 erf
4169              
4170             $x->erf # => BigNum
4171              
4172             The error function on C.
4173              
4174             =cut
4175              
4176             sub erf {
4177             my $r = _big2mpfr($_[0]);
4178             Math::MPFR::Rmpfr_erf($r, $r, $ROUND);
4179             _mpfr2big($r);
4180             }
4181              
4182             =head2 erfc
4183              
4184             $x->erfc # => BigNum
4185              
4186             Complementary error function on C.
4187              
4188             =cut
4189              
4190             sub erfc {
4191             my $r = _big2mpfr($_[0]);
4192             Math::MPFR::Rmpfr_erfc($r, $r, $ROUND);
4193             _mpfr2big($r);
4194             }
4195              
4196             =head2 eint
4197              
4198             $x->eint # => BigNum | Inf | Nan
4199              
4200             Exponential integral of C. Returns -Inf when C is zero, and Nan when C is negative.
4201              
4202             =cut
4203              
4204             sub eint {
4205             my $r = _big2mpfr($_[0]);
4206             Math::MPFR::Rmpfr_eint($r, $r, $ROUND);
4207             _mpfr2big($r);
4208             }
4209              
4210             =head2 li
4211              
4212             $x->li # => BigNum | Inf | Nan
4213              
4214             The logarithmic integral of C, defined as: C.
4215             Returns -Inf when C is 1, and Nan when C is less than or equal to 0.
4216              
4217             =cut
4218              
4219             sub li {
4220             my $r = _big2mpfr($_[0]);
4221             Math::MPFR::Rmpfr_log($r, $r, $ROUND);
4222             Math::MPFR::Rmpfr_eint($r, $r, $ROUND);
4223             _mpfr2big($r);
4224             }
4225              
4226             =head2 li2
4227              
4228             $x->li2 # => BigNum
4229              
4230             The dilogarithm function, defined as the integral of C<-log(1-t)/t> from 0 to C.
4231              
4232             =cut
4233              
4234             sub li2 {
4235             my $r = _big2mpfr($_[0]);
4236             Math::MPFR::Rmpfr_li2($r, $r, $ROUND);
4237             _mpfr2big($r);
4238             }
4239              
4240             ############################ INTEGER OPERATIONS ############################
4241              
4242             =head1 INTEGER OPERATIONS
4243              
4244             All the operations in this section are done with integers.
4245              
4246             =cut
4247              
4248             =head2 iadd
4249              
4250             $x->iadd(BigNum) # => BigNum
4251             $x->iadd(Scalar) # => BigNum
4252              
4253             Integer addition of C to C. Both values
4254             are truncated to integers before addition.
4255              
4256             =cut
4257              
4258             Class::Multimethods::multimethod iadd => qw(Math::BigNum Math::BigNum) => sub {
4259             my $r = _big2mpz($_[0]);
4260             Math::GMPz::Rmpz_add($r, $r, _big2mpz($_[1]));
4261             _mpz2big($r);
4262             };
4263              
4264             Class::Multimethods::multimethod iadd => qw(Math::BigNum $) => sub {
4265             my ($x, $y) = @_;
4266              
4267             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4268             my $r = _big2mpz($x);
4269             $y < 0
4270             ? Math::GMPz::Rmpz_sub_ui($r, $r, CORE::abs($y))
4271             : Math::GMPz::Rmpz_add_ui($r, $r, $y);
4272             _mpz2big($r);
4273             }
4274             else {
4275             Math::BigNum->new($y)->biadd($x);
4276             }
4277             };
4278              
4279             Class::Multimethods::multimethod iadd => qw(Math::BigNum *) => sub {
4280             Math::BigNum->new($_[1])->biadd($_[0]);
4281             };
4282              
4283             Class::Multimethods::multimethod iadd => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1] };
4284             Class::Multimethods::multimethod iadd => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
4285              
4286             =head2 biadd
4287              
4288             $x->biadd(BigNum) # => BigNum
4289             $x->biadd(Scalar) # => BigNum
4290              
4291             Integer addition of C from C, changing C in-place.
4292             Both values are truncated to integers before addition.
4293              
4294             =cut
4295              
4296             Class::Multimethods::multimethod biadd => qw(Math::BigNum Math::BigNum) => sub {
4297             my $r = _big2mpz($_[0]);
4298             Math::GMPz::Rmpz_add($r, $r, _big2mpz($_[1]));
4299             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
4300             $_[0];
4301             };
4302              
4303             Class::Multimethods::multimethod biadd => qw(Math::BigNum $) => sub {
4304             my ($x, $y) = @_;
4305              
4306             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4307             my $r = _big2mpz($x);
4308             $y < 0
4309             ? Math::GMPz::Rmpz_sub_ui($r, $r, CORE::abs($y))
4310             : Math::GMPz::Rmpz_add_ui($r, $r, $y);
4311             Math::GMPq::Rmpq_set_z(${$x}, $r);
4312             $x;
4313             }
4314             else {
4315             $x->biadd(Math::BigNum->new($y));
4316             }
4317             };
4318              
4319             Class::Multimethods::multimethod biadd => qw(Math::BigNum *) => sub {
4320             $_[0]->biadd(Math::BigNum->new($_[1]));
4321             };
4322              
4323             Class::Multimethods::multimethod biadd => qw(Math::BigNum Math::BigNum::Inf) => \&_big2inf;
4324             Class::Multimethods::multimethod biadd => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
4325              
4326             =head2 isub
4327              
4328             $x->isub(BigNum) # => BigNum
4329             $x->isub(Scalar) # => BigNum
4330              
4331             Integer subtraction of C from C. Both values
4332             are truncated to integers before subtraction.
4333              
4334             =cut
4335              
4336             Class::Multimethods::multimethod isub => qw(Math::BigNum Math::BigNum) => sub {
4337             my $r = _big2mpz($_[0]);
4338             Math::GMPz::Rmpz_sub($r, $r, _big2mpz($_[1]));
4339             _mpz2big($r);
4340             };
4341              
4342             Class::Multimethods::multimethod isub => qw(Math::BigNum $) => sub {
4343             my ($x, $y) = @_;
4344              
4345             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4346             my $r = _big2mpz($x);
4347             $y < 0
4348             ? Math::GMPz::Rmpz_add_ui($r, $r, CORE::abs($y))
4349             : Math::GMPz::Rmpz_sub_ui($r, $r, $y);
4350             _mpz2big($r);
4351             }
4352             else {
4353             Math::BigNum->new($y)->bneg->biadd($x);
4354             }
4355             };
4356              
4357             Class::Multimethods::multimethod isub => qw(Math::BigNum *) => sub {
4358             Math::BigNum->new($_[1])->bneg->biadd($_[0]);
4359             };
4360              
4361             Class::Multimethods::multimethod isub => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->neg };
4362             Class::Multimethods::multimethod isub => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
4363              
4364             =head2 bisub
4365              
4366             $x->bisub(BigNum) # => BigNum
4367             $x->bisub(Scalar) # => BigNum
4368              
4369             Integer subtraction of C from x, changing C in-place.
4370             Both values are truncated to integers before subtraction.
4371              
4372             =cut
4373              
4374             Class::Multimethods::multimethod bisub => qw(Math::BigNum Math::BigNum) => sub {
4375             my $r = _big2mpz($_[0]);
4376             Math::GMPz::Rmpz_sub($r, $r, _big2mpz($_[1]));
4377             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
4378             $_[0];
4379             };
4380              
4381             Class::Multimethods::multimethod bisub => qw(Math::BigNum $) => sub {
4382             my ($x, $y) = @_;
4383              
4384             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4385             my $r = _big2mpz($x);
4386             $y < 0
4387             ? Math::GMPz::Rmpz_add_ui($r, $r, CORE::abs($y))
4388             : Math::GMPz::Rmpz_sub_ui($r, $r, $y);
4389             Math::GMPq::Rmpq_set_z(${$x}, $r);
4390             $x;
4391             }
4392             else {
4393             $x->bisub(Math::BigNum->new($y));
4394             }
4395             };
4396              
4397             Class::Multimethods::multimethod bisub => qw(Math::BigNum *) => sub {
4398             $_[0]->bisub(Math::BigNum->new($_[1]));
4399             };
4400              
4401             Class::Multimethods::multimethod bisub => qw(Math::BigNum Math::BigNum::Inf) => \&_big2ninf;
4402             Class::Multimethods::multimethod bisub => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
4403              
4404             =head2 imul
4405              
4406             $x->imul(BigNum) # => BigNum
4407             $x->imul(Scalar) # => BigNum
4408              
4409             Integer multiplication of C by C. Both values
4410             are truncated to integers before multiplication.
4411              
4412             =cut
4413              
4414             Class::Multimethods::multimethod imul => qw(Math::BigNum Math::BigNum) => sub {
4415             my $r = _big2mpz($_[0]);
4416             Math::GMPz::Rmpz_mul($r, $r, _big2mpz($_[1]));
4417             _mpz2big($r);
4418             };
4419              
4420             Class::Multimethods::multimethod imul => qw(Math::BigNum $) => sub {
4421             my ($x, $y) = @_;
4422              
4423             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4424             my $r = _big2mpz($x);
4425             $y < 0
4426             ? Math::GMPz::Rmpz_mul_si($r, $r, $y)
4427             : Math::GMPz::Rmpz_mul_ui($r, $r, $y);
4428             _mpz2big($r);
4429             }
4430             else {
4431             Math::BigNum->new($y)->bimul($x);
4432             }
4433             };
4434              
4435             Class::Multimethods::multimethod imul => qw(Math::BigNum *) => sub {
4436             Math::BigNum->new($_[1])->bimul($_[0]);
4437             };
4438              
4439             Class::Multimethods::multimethod imul => qw(Math::BigNum Math::BigNum::Inf) => sub {
4440             my $sign = Math::GMPq::Rmpq_sgn(${$_[0]});
4441             $sign < 0 ? $_[1]->neg : $sign > 0 ? $_[1]->copy : nan;
4442             };
4443              
4444             Class::Multimethods::multimethod imul => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
4445              
4446             =head2 bimul
4447              
4448             $x->bimul(BigNum) # => BigNum
4449             $x->bimul(Scalar) # => BigNum
4450              
4451             Integer multiplication of C by C, changing C in-place.
4452             Both values are truncated to integers before multiplication.
4453              
4454             =cut
4455              
4456             Class::Multimethods::multimethod bimul => qw(Math::BigNum Math::BigNum) => sub {
4457             my $r = _big2mpz($_[0]);
4458             Math::GMPz::Rmpz_mul($r, $r, _big2mpz($_[1]));
4459             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
4460             $_[0];
4461             };
4462              
4463             Class::Multimethods::multimethod bimul => qw(Math::BigNum $) => sub {
4464             my ($x, $y) = @_;
4465              
4466             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4467             my $r = _big2mpz($x);
4468             $y < 0
4469             ? Math::GMPz::Rmpz_mul_si($r, $r, $y)
4470             : Math::GMPz::Rmpz_mul_ui($r, $r, $y);
4471             Math::GMPq::Rmpq_set_z(${$x}, $r);
4472             $x;
4473             }
4474             else {
4475             $x->bimul(Math::BigNum->new($y));
4476             }
4477             };
4478              
4479             Class::Multimethods::multimethod bimul => qw(Math::BigNum *) => sub {
4480             $_[0]->bimul(Math::BigNum->new($_[1]));
4481             };
4482              
4483             Class::Multimethods::multimethod bimul => qw(Math::BigNum Math::BigNum::Inf) => sub {
4484             my ($x) = @_;
4485             my $sign = Math::GMPq::Rmpq_sgn($$x);
4486             $sign < 0 ? _big2ninf(@_) : $sign > 0 ? _big2inf(@_) : $x->bnan;
4487             };
4488              
4489             Class::Multimethods::multimethod bimul => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
4490              
4491             =head2 idiv
4492              
4493             $x->idiv(BigNum) # => BigNum | Nan | Inf
4494             $x->idiv(Scalar) # => BigNum | Nan | Inf
4495              
4496             Integer division of C by C.
4497              
4498             =cut
4499              
4500             Class::Multimethods::multimethod idiv => qw(Math::BigNum Math::BigNum) => sub {
4501             my ($x, $y) = @_;
4502              
4503             $y = _big2mpz($y);
4504             my $r = _big2mpz($x);
4505              
4506             if (!Math::GMPz::Rmpz_sgn($y)) {
4507             my $sign = Math::GMPz::Rmpz_sgn($r);
4508             return (!$sign ? nan : $sign > 0 ? inf : ninf);
4509             }
4510              
4511             Math::GMPz::Rmpz_div($r, $r, $y);
4512             _mpz2big($r);
4513             };
4514              
4515             Class::Multimethods::multimethod idiv => qw(Math::BigNum $) => sub {
4516             my ($x, $y) = @_;
4517              
4518             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4519              
4520             my $r = _big2mpz($x);
4521              
4522             # When `y` is zero, return +/-Inf or NaN
4523             $y || do {
4524             my $sign = Math::GMPz::Rmpz_sgn($r);
4525             return (
4526             $sign > 0 ? inf
4527             : $sign < 0 ? ninf
4528             : nan
4529             );
4530             };
4531              
4532             Math::GMPz::Rmpz_div_ui($r, $r, CORE::abs($y));
4533             Math::GMPz::Rmpz_neg($r, $r) if $y < 0;
4534             _mpz2big($r);
4535             }
4536             else {
4537             $x->idiv(Math::BigNum->new($y));
4538             }
4539             };
4540              
4541             Class::Multimethods::multimethod idiv => qw(Math::BigNum *) => sub {
4542             $_[0]->idiv(Math::BigNum->new($_[1]));
4543             };
4544              
4545             Class::Multimethods::multimethod idiv => qw(Math::BigNum Math::BigNum::Inf) => \&zero;
4546             Class::Multimethods::multimethod idiv => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
4547              
4548             =head2 bidiv
4549              
4550             $x->bidiv(BigNum) # => BigNum | Nan | Inf
4551             $x->bidiv(Scalar) # => BigNum | Nan | Inf
4552              
4553             Integer division of C by C, changing C in-place.
4554              
4555             =cut
4556              
4557             Class::Multimethods::multimethod bidiv => qw(Math::BigNum Math::BigNum) => sub {
4558             my ($x, $y) = @_;
4559              
4560             $y = _big2mpz($y);
4561             my $r = _big2mpz($x);
4562              
4563             if (!Math::GMPz::Rmpz_sgn($y)) {
4564             my $sign = Math::GMPz::Rmpz_sgn($r);
4565             return
4566             $sign > 0 ? $x->binf
4567             : $sign < 0 ? $x->bninf
4568             : $x->bnan;
4569             }
4570              
4571             Math::GMPz::Rmpz_div($r, $r, $y);
4572             Math::GMPq::Rmpq_set_z($$x, $r);
4573             $x;
4574             };
4575              
4576             Class::Multimethods::multimethod bidiv => qw(Math::BigNum $) => sub {
4577             my ($x, $y) = @_;
4578              
4579             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4580              
4581             my $r = _big2mpz($x);
4582              
4583             # When `y` is zero, return +/-Inf or NaN
4584             $y || do {
4585             my $sign = Math::GMPz::Rmpz_sgn($r);
4586             return
4587             $sign > 0 ? $x->binf
4588             : $sign < 0 ? $x->bninf
4589             : $x->bnan;
4590             };
4591              
4592             Math::GMPz::Rmpz_div_ui($r, $r, CORE::abs($y));
4593             Math::GMPq::Rmpq_set_z($$x, $r);
4594             Math::GMPq::Rmpq_neg($$x, $$x) if $y < 0;
4595             $x;
4596             }
4597             else {
4598             $x->bidiv(Math::BigNum->new($y));
4599             }
4600             };
4601              
4602             Class::Multimethods::multimethod bidiv => qw(Math::BigNum *) => sub {
4603             $_[0]->bidiv(Math::BigNum->new($_[1]));
4604             };
4605              
4606             Class::Multimethods::multimethod bidiv => qw(Math::BigNum Math::BigNum::Inf) => \&bzero;
4607             Class::Multimethods::multimethod bidiv => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
4608              
4609             =head2 ipow
4610              
4611             $x->ipow(BigNum) # => BigNum
4612             $x->ipow(Scalar) # => BigNum
4613              
4614             Raises C to power C, truncating C and C to integers, if necessarily.
4615              
4616             =cut
4617              
4618             Class::Multimethods::multimethod ipow => qw(Math::BigNum Math::BigNum) => sub {
4619             my ($x, $y) = @_;
4620              
4621             my $pow = CORE::int(Math::GMPq::Rmpq_get_d($$y));
4622              
4623             my $z = _big2mpz($x);
4624             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
4625              
4626             if ($pow < 0) {
4627             return inf() if !Math::GMPz::Rmpz_sgn($z);
4628             Math::GMPz::Rmpz_tdiv_q($z, $ONE_Z, $z);
4629             }
4630              
4631             _mpz2big($z);
4632             };
4633              
4634             Class::Multimethods::multimethod ipow => qw(Math::BigNum $) => sub {
4635             my ($x, $y) = @_;
4636              
4637             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4638              
4639             my $z = _big2mpz($x);
4640             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($y));
4641              
4642             if ($y < 0) {
4643             return inf() if !Math::GMPz::Rmpz_sgn($z);
4644             Math::GMPz::Rmpz_tdiv_q($z, $ONE_Z, $z);
4645             }
4646              
4647             _mpz2big($z);
4648             }
4649             else {
4650             $x->ipow(Math::BigNum->new($y));
4651             }
4652             };
4653              
4654             Class::Multimethods::multimethod ipow => qw(Math::BigNum *) => sub {
4655             $_[0]->ipow(Math::BigNum->new($_[1]));
4656             };
4657              
4658             Class::Multimethods::multimethod ipow => qw(Math::BigNum Math::BigNum::Inf) => sub {
4659             $_[0]->int->pow($_[1]);
4660             };
4661              
4662             Class::Multimethods::multimethod ipow => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
4663              
4664             =head2 bipow
4665              
4666             $x->bipow(BigNum) # => BigNum
4667             $x->bipow(Scalar) # => BigNum
4668              
4669             Raises C to power C, changing C in-place.
4670              
4671             =cut
4672              
4673             Class::Multimethods::multimethod bipow => qw(Math::BigNum Math::BigNum) => sub {
4674             my ($x, $y) = @_;
4675              
4676             my $pow = CORE::int(Math::GMPq::Rmpq_get_d($$y));
4677              
4678             my $z = Math::GMPz::Rmpz_init();
4679             Math::GMPz::Rmpz_set_q($z, $$x);
4680             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($pow));
4681              
4682             if ($pow < 0) {
4683             return $x->binf if !Math::GMPz::Rmpz_sgn($z);
4684             Math::GMPz::Rmpz_tdiv_q($z, $ONE_Z, $z);
4685             }
4686              
4687             Math::GMPq::Rmpq_set_z($$x, $z);
4688             return $x;
4689             };
4690              
4691             Class::Multimethods::multimethod bipow => qw(Math::BigNum $) => sub {
4692             my ($x, $y) = @_;
4693              
4694             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4695              
4696             my $z = Math::GMPz::Rmpz_init();
4697             Math::GMPz::Rmpz_set_q($z, $$x);
4698             Math::GMPz::Rmpz_pow_ui($z, $z, CORE::abs($y));
4699              
4700             if ($y < 0) {
4701             return $x->binf if !Math::GMPz::Rmpz_sgn($z);
4702             Math::GMPz::Rmpz_tdiv_q($z, $ONE_Z, $z);
4703             }
4704              
4705             Math::GMPq::Rmpq_set_z($$x, $z);
4706             $x;
4707             }
4708             else {
4709             $x->bipow(Math::BigNum->new($y));
4710             }
4711             };
4712              
4713             Class::Multimethods::multimethod bipow => qw(Math::BigNum *) => sub {
4714             $_[0]->bipow(Math::BigNum->new($_[1]));
4715             };
4716              
4717             Class::Multimethods::multimethod bipow => qw(Math::BigNum Math::BigNum::Inf) => sub {
4718             $_[0]->bint->bpow($_[1]);
4719             };
4720              
4721             Class::Multimethods::multimethod bipow => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
4722              
4723             =head2 isqrt
4724              
4725             $x->isqrt # => BigNum | Nan
4726              
4727             Integer square root of C. Returns Nan when C is negative.
4728              
4729             =cut
4730              
4731             sub isqrt {
4732             my $r = _big2mpz($_[0]);
4733             return nan() if Math::GMPz::Rmpz_sgn($r) < 0;
4734             Math::GMPz::Rmpz_sqrt($r, $r);
4735             _mpz2big($r);
4736             }
4737              
4738             =head2 bisqrt
4739              
4740             $x->bisqrt # => BigNum | Nan
4741              
4742             Integer square root of C, changing C in-place. Promotes C to Nan when C is negative.
4743              
4744             =cut
4745              
4746             sub bisqrt {
4747             my ($x) = @_;
4748             my $r = _big2mpz($x);
4749             return $x->bnan() if Math::GMPz::Rmpz_sgn($r) < 0;
4750             Math::GMPz::Rmpz_sqrt($r, $r);
4751             Math::GMPq::Rmpq_set_z($$x, $r);
4752             $x;
4753             }
4754              
4755             =head2 isqrtrem
4756              
4757             $x->isqrtrem # => (BigNum, BigNum) | (Nan, Nan)
4758              
4759             The integer part of the square root of C and the remainder C, which will be zero when is a perfect square.
4760              
4761             Returns (Nan,Nan) when C is negative.
4762              
4763             =cut
4764              
4765             sub isqrtrem {
4766             my ($x) = @_;
4767             $x = _big2mpz($x);
4768             Math::GMPz::Rmpz_sgn($x) < 0 && return (nan(), nan());
4769             my $r = Math::GMPz::Rmpz_init();
4770             Math::GMPz::Rmpz_sqrtrem($x, $r, $x);
4771             (_mpz2big($x), _mpz2big($r));
4772             }
4773              
4774             =head2 iroot
4775              
4776             $x->iroot(BigNum) # => BigNum | Nan
4777             $x->iroot(Scalar) # => BigNum | Nan
4778              
4779             Nth integer root of C.
4780              
4781             Returns Nan when C is negative and C is even.
4782              
4783             =cut
4784              
4785             Class::Multimethods::multimethod iroot => qw(Math::BigNum Math::BigNum) => sub {
4786             my ($x, $y) = @_;
4787              
4788             my $z = _big2mpz($x);
4789              
4790             my $root = CORE::int(Math::GMPq::Rmpq_get_d($$y));
4791              
4792             if ($root == 0) {
4793             Math::GMPz::Rmpz_sgn($z) || return zero(); # 0^Inf = 0
4794             Math::GMPz::Rmpz_cmpabs($z, $ONE_Z) == 0 and return one(); # 1^Inf = 1 ; (-1)^Inf = 1
4795             return inf();
4796             }
4797             elsif ($root < 0) {
4798             my $sign = Math::GMPz::Rmpz_sgn($z) || return inf(); # 1 / 0^k = Inf
4799             Math::GMPz::Rmpz_cmp($z, $ONE_Z) == 0 and return one(); # 1 / 1^k = 1
4800             return $sign < 0 ? nan() : zero();
4801             }
4802             elsif ($root % 2 == 0 and Math::GMPz::Rmpz_sgn($z) < 0) {
4803             return nan();
4804             }
4805              
4806             Math::GMPz::Rmpz_root($z, $z, $root);
4807             _mpz2big($z);
4808             };
4809              
4810             Class::Multimethods::multimethod iroot => qw(Math::BigNum $) => sub {
4811             my ($x, $y) = @_;
4812              
4813             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4814              
4815             my $z = _big2mpz($x);
4816              
4817             my $root = $y;
4818             if ($root == 0) {
4819             Math::GMPz::Rmpz_sgn($z) || return zero(); # 0^Inf = 0
4820             Math::GMPz::Rmpz_cmpabs($z, $ONE_Z) == 0 and return one(); # 1^Inf = 1 ; (-1)^Inf = 1
4821             return inf();
4822             }
4823             elsif ($root < 0) {
4824             my $sign = Math::GMPz::Rmpz_sgn($z) || return inf(); # 1 / 0^k = Inf
4825             Math::GMPz::Rmpz_cmp($z, $ONE_Z) == 0 and return one(); # 1 / 1^k = 1
4826             return $sign < 0 ? nan() : zero();
4827             }
4828             elsif ($root % 2 == 0 and Math::GMPz::Rmpz_sgn($z) < 0) {
4829             return nan();
4830             }
4831              
4832             Math::GMPz::Rmpz_root($z, $z, $root);
4833             _mpz2big($z);
4834             }
4835             else {
4836             $x->iroot(Math::BigNum->new($y));
4837             }
4838             };
4839              
4840             Class::Multimethods::multimethod iroot => qw(Math::BigNum *) => sub {
4841             $_[0]->iroot(Math::BigNum->new($_[1]));
4842             };
4843              
4844             Class::Multimethods::multimethod iroot => qw(Math::BigNum Math::BigNum::Inf) => \&one;
4845             Class::Multimethods::multimethod iroot => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
4846              
4847             =head2 biroot
4848              
4849             $x->biroot(BigNum) # => BigNum | Nan
4850             $x->biroot(Scalar) # => BigNum | Nan
4851              
4852             Nth integer root of C, changing C in-place. Promotes
4853             C to Nan when C is negative and C is even.
4854              
4855             =cut
4856              
4857             Class::Multimethods::multimethod biroot => qw(Math::BigNum Math::BigNum) => sub {
4858             my ($x, $y) = @_;
4859              
4860             my $z = _big2mpz($x);
4861              
4862             my $root = CORE::int(Math::GMPq::Rmpq_get_d($$y));
4863              
4864             if ($root == 0) {
4865             Math::GMPz::Rmpz_sgn($z) || return $x->bzero(); # 0^Inf = 0
4866             Math::GMPz::Rmpz_cmpabs($z, $ONE_Z) == 0 and return $x->bone(); # 1^Inf = 1 ; (-1)^Inf = 1
4867             return $x->binf();
4868             }
4869             elsif ($root < 0) {
4870             my $sign = Math::GMPz::Rmpz_sgn($z) || return $x->binf(); # 1 / 0^k = Inf
4871             Math::GMPz::Rmpz_cmp($z, $ONE_Z) == 0 and return $x->bone(); # 1 / 1^k = 1
4872             return $sign < 0 ? $x->bnan() : $x->bzero();
4873             }
4874             elsif ($root % 2 == 0 and Math::GMPz::Rmpz_sgn($z) < 0) {
4875             return $x->bnan();
4876             }
4877              
4878             Math::GMPz::Rmpz_root($z, $z, $root);
4879             Math::GMPq::Rmpq_set_z($$x, $z);
4880             $x;
4881             };
4882              
4883             Class::Multimethods::multimethod biroot => qw(Math::BigNum $) => sub {
4884             my ($x, $y) = @_;
4885              
4886             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4887              
4888             my $z = _big2mpz($x);
4889              
4890             my $root = $y;
4891             if ($root == 0) {
4892             Math::GMPz::Rmpz_sgn($z) || return $x->bzero(); # 0^Inf = 0
4893             Math::GMPz::Rmpz_cmpabs($z, $ONE_Z) == 0 and return $x->bone(); # 1^Inf = 1 ; (-1)^Inf = 1
4894             return $x->binf();
4895             }
4896             elsif ($root < 0) {
4897             my $sign = Math::GMPz::Rmpz_sgn($z) || return $x->binf(); # 1 / 0^k = Inf
4898             Math::GMPz::Rmpz_cmp($z, $ONE_Z) == 0 and return $x->bone(); # 1 / 1^k = 1
4899             return $sign < 0 ? $x->bnan() : $x->bzero();
4900             }
4901             elsif ($root % 2 == 0 and Math::GMPz::Rmpz_sgn($z) < 0) {
4902             return $x->bnan();
4903             }
4904              
4905             Math::GMPz::Rmpz_root($z, $z, $root);
4906             Math::GMPq::Rmpq_set_z($$x, $z);
4907             $x;
4908             }
4909             else {
4910             $x->biroot(Math::BigNum->new($y));
4911             }
4912             };
4913              
4914             Class::Multimethods::multimethod biroot => qw(Math::BigNum *) => sub {
4915             $_[0]->biroot(Math::BigNum->new($_[1]));
4916             };
4917              
4918             Class::Multimethods::multimethod biroot => qw(Math::BigNum Math::BigNum::Inf) => \&bone;
4919             Class::Multimethods::multimethod biroot => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
4920              
4921             =head2 irootrem
4922              
4923             $x->irootrem(BigNum) # => (BigNum, BigNum) | (Nan, Nan)
4924             $x->irootrem(Scalar) # => (BigNum, BigNum) | (Nan, Nan)
4925              
4926             The nth integer part of the root of C and the remainder C.
4927              
4928             Returns (Nan,Nan) when C is negative.
4929              
4930             =cut
4931              
4932             Class::Multimethods::multimethod irootrem => qw(Math::BigNum Math::BigNum) => sub {
4933             my ($x, $y) = @_;
4934             $x = _big2mpz($x);
4935             my $root = CORE::int(Math::GMPq::Rmpq_get_d($$y));
4936              
4937             if ($root == 0) {
4938             Math::GMPz::Rmpz_sgn($x) || return (zero(), mone()); # 0^Inf = 0
4939             Math::GMPz::Rmpz_cmpabs_ui($x, 1) == 0 and return (one(), _mpz2big($x)->bdec); # 1^Inf = 1 ; (-1)^Inf = 1
4940             return (inf(), _mpz2big($x)->bdec);
4941             }
4942             elsif ($root < 0) {
4943             my $sign = Math::GMPz::Rmpz_sgn($x) || return (inf(), zero()); # 1 / 0^k = Inf
4944             Math::GMPz::Rmpz_cmp_ui($x, 1) == 0 and return (one(), zero()); # 1 / 1^k = 1
4945             return ($sign < 0 ? (nan(), nan()) : (zero(), ninf()));
4946             }
4947             elsif ($root % 2 == 0 and Math::GMPz::Rmpz_sgn($x) < 0) {
4948             return (nan(), nan());
4949             }
4950              
4951             my $r = Math::GMPz::Rmpz_init();
4952             Math::GMPz::Rmpz_rootrem($x, $r, $x, $root);
4953             (_mpz2big($x), _mpz2big($r));
4954             };
4955              
4956             Class::Multimethods::multimethod irootrem => qw(Math::BigNum $) => sub {
4957             my ($x, $y) = @_;
4958              
4959             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
4960             $x = _big2mpz($x);
4961              
4962             if ($y == 0) {
4963             Math::GMPz::Rmpz_sgn($x) || return (zero(), mone()); # 0^Inf = 0
4964             Math::GMPz::Rmpz_cmpabs_ui($x, 1) == 0 and return (one(), _mpz2big($x)->bdec); # 1^Inf = 1 ; (-1)^Inf = 1
4965             return (inf(), _mpz2big($x)->bdec);
4966             }
4967             elsif ($y < 0) {
4968             my $sign = Math::GMPz::Rmpz_sgn($x) || return (inf(), zero()); # 1 / 0^k = Inf
4969             Math::GMPz::Rmpz_cmp_ui($x, 1) == 0 and return (one(), zero()); # 1 / 1^k = 1
4970             return ($sign < 0 ? (nan(), nan()) : (zero(), ninf()));
4971             }
4972             elsif ($y % 2 == 0 and Math::GMPz::Rmpz_sgn($x) < 0) {
4973             return (nan(), nan());
4974             }
4975              
4976             my $r = Math::GMPz::Rmpz_init();
4977             Math::GMPz::Rmpz_rootrem($x, $r, $x, $y);
4978             (_mpz2big($x), _mpz2big($r));
4979             }
4980             else {
4981             $x->irootrem(Math::BigNum->new($y));
4982             }
4983             };
4984              
4985             # Equivalent with the following definition:
4986             # irootrem(x, +/-Inf) = (1, x-1)
4987             Class::Multimethods::multimethod irootrem => qw(Math::BigNum Math::BigNum::Inf) => sub {
4988             my ($x, $y) = @_;
4989             my $root = $x->iroot($y);
4990             ($root, $x->isub($root->bipow($y)));
4991             };
4992              
4993             Class::Multimethods::multimethod irootrem => qw(Math::BigNum Math::BigNum::Nan) => sub {
4994             (nan(), nan());
4995             };
4996              
4997             Class::Multimethods::multimethod irootrem => qw(Math::BigNum *) => sub {
4998             $_[0]->irootrem(Math::BigNum->new($_[1]));
4999             };
5000              
5001             =head2 imod
5002              
5003             $x->imod(BigNum) # => BigNum | Nan
5004             $x->imod(Scalar) # => BigNum | Nan
5005              
5006             Integer remainder of C when is divided by C. If necessary, C and C
5007             are implicitly truncated to integers. Nan is returned when C is zero.
5008              
5009             =cut
5010              
5011             Class::Multimethods::multimethod imod => qw(Math::BigNum Math::BigNum) => sub {
5012             my ($x, $y) = @_;
5013              
5014             my $yz = _big2mpz($y);
5015             my $sign_y = Math::GMPz::Rmpz_sgn($yz);
5016             return nan if !$sign_y;
5017              
5018             my $r = _big2mpz($x);
5019             Math::GMPz::Rmpz_mod($r, $r, $yz);
5020             if (!Math::GMPz::Rmpz_sgn($r)) {
5021             return (zero); # return faster
5022             }
5023             elsif ($sign_y < 0) {
5024             Math::GMPz::Rmpz_add($r, $r, $yz);
5025             }
5026             _mpz2big($r);
5027             };
5028              
5029             Class::Multimethods::multimethod imod => qw(Math::BigNum $) => sub {
5030             my ($x, $y) = @_;
5031              
5032             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
5033              
5034             $y || return nan();
5035              
5036             my $r = _big2mpz($x);
5037             my $neg_y = $y < 0;
5038             $y = CORE::abs($y) if $neg_y;
5039             Math::GMPz::Rmpz_mod_ui($r, $r, $y);
5040             if (!Math::GMPz::Rmpz_sgn($r)) {
5041             return (zero); # return faster
5042             }
5043             elsif ($neg_y) {
5044             Math::GMPz::Rmpz_sub_ui($r, $r, $y);
5045             }
5046             _mpz2big($r);
5047             }
5048             else {
5049             $x->imod(Math::BigNum->new($y));
5050             }
5051             };
5052              
5053             Class::Multimethods::multimethod imod => qw(Math::BigNum *) => sub {
5054             $_[0]->imod(Math::BigNum->new($_[1]));
5055             };
5056              
5057             Class::Multimethods::multimethod imod => qw(Math::BigNum Math::BigNum::Inf) => sub {
5058             $_[0]->copy->bimod($_[1]);
5059             };
5060              
5061             Class::Multimethods::multimethod imod => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
5062              
5063             =head2 bimod
5064              
5065             $x->bimod(BigNum) # => BigNum | Nan
5066             $x->bimod(Scalar) # => BigNum | Nan
5067              
5068             Sets C to the remainder of C divided by C. If necessary, C and C
5069             are implicitly truncated to integers. Sets C to Nan when C is zero.
5070              
5071             =cut
5072              
5073             Class::Multimethods::multimethod bimod => qw(Math::BigNum Math::BigNum) => sub {
5074             my ($x, $y) = @_;
5075              
5076             my $yz = _big2mpz($y);
5077             my $sign_y = Math::GMPz::Rmpz_sgn($yz);
5078             return $x->bnan if !$sign_y;
5079              
5080             my $r = _big2mpz($x);
5081             Math::GMPz::Rmpz_mod($r, $r, $yz);
5082             if ($sign_y < 0 and Math::GMPz::Rmpz_sgn($r)) {
5083             Math::GMPz::Rmpz_add($r, $r, $yz);
5084             }
5085             Math::GMPq::Rmpq_set_z($$x, $r);
5086             $x;
5087             };
5088              
5089             Class::Multimethods::multimethod bimod => qw(Math::BigNum $) => sub {
5090             my ($x, $y) = @_;
5091              
5092             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
5093              
5094             $y || return $x->bnan;
5095              
5096             my $r = _big2mpz($x);
5097             my $neg_y = $y < 0;
5098             $y = CORE::abs($y) if $neg_y;
5099             Math::GMPz::Rmpz_mod_ui($r, $r, $y);
5100             if ($neg_y and Math::GMPz::Rmpz_sgn($r)) {
5101             Math::GMPz::Rmpz_sub_ui($r, $r, $y);
5102             }
5103             Math::GMPq::Rmpq_set_z($$x, $r);
5104              
5105             $x;
5106             }
5107             else {
5108             $x->bimod(Math::BigNum->new($y));
5109             }
5110             };
5111              
5112             Class::Multimethods::multimethod bimod => qw(Math::BigNum *) => sub {
5113             $_[0]->bimod(Math::BigNum->new($_[1]));
5114             };
5115              
5116             # +x mod +Inf = x
5117             # +x mod -Inf = -Inf
5118             # -x mod +Inf = +Inf
5119             # -x mod -Inf = x
5120             Class::Multimethods::multimethod bimod => qw(Math::BigNum Math::BigNum::Inf) => sub {
5121             $_[0]->int->bmod($_[1]);
5122             };
5123              
5124             Class::Multimethods::multimethod bimod => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
5125              
5126             =head2 divmod
5127              
5128             $x->divmod(BigNum) # => (BigNum, BigNum) | (Nan, Nan)
5129             $x->divmod(Scalar) # => (BigNum, BigNum) | (Nan, Nan)
5130              
5131             Returns the quotient and the remainder from division of C by C,
5132             where both are integers. When C is zero, it returns two Nan values.
5133              
5134             =cut
5135              
5136             Class::Multimethods::multimethod divmod => qw(Math::BigNum Math::BigNum) => sub {
5137             my ($x, $y) = @_;
5138              
5139             my $r1 = _big2mpz($x);
5140             my $r2 = _big2mpz($y);
5141              
5142             Math::GMPz::Rmpz_sgn($$y) || return (nan, nan);
5143              
5144             Math::GMPz::Rmpz_divmod($r1, $r2, $r1, $r2);
5145             (_mpz2big($r1), _mpz2big($r2));
5146             };
5147              
5148             Class::Multimethods::multimethod divmod => qw(Math::BigNum $) => sub {
5149             my ($x, $y) = @_;
5150              
5151             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
5152              
5153             $y || return (nan, nan);
5154              
5155             my $r1 = _big2mpz($x);
5156             my $r2 = Math::GMPz::Rmpz_init();
5157              
5158             Math::GMPz::Rmpz_divmod_ui($r1, $r2, $r1, $y);
5159             (_mpz2big($r1), _mpz2big($r2));
5160             }
5161             else {
5162             $x->divmod(Math::BigNum->new($y));
5163             }
5164             };
5165              
5166             Class::Multimethods::multimethod divmod => qw(Math::BigNum *) => sub {
5167             $_[0]->divmod(Math::BigNum->new($_[1]));
5168             };
5169              
5170             Class::Multimethods::multimethod divmod => qw(Math::BigNum Math::BigNum::Inf) => sub { (zero, $_[0]->mod($_[1])) };
5171             Class::Multimethods::multimethod divmod => qw(Math::BigNum Math::BigNum::Nan) => sub { (nan, nan) };
5172              
5173             =head1 * Number theory
5174              
5175             =cut
5176              
5177             =head2 modinv
5178              
5179             $x->modinv(BigNum) # => BigNum | Nan
5180             $x->modinv(Scalar) # => BigNum | Nan
5181              
5182             Computes the inverse of C modulo C and returns the result.
5183             If an inverse does not exists, the Nan value is returned.
5184              
5185             =cut
5186              
5187             Class::Multimethods::multimethod modinv => qw(Math::BigNum Math::BigNum) => sub {
5188             my ($x, $y) = @_;
5189             my $r = _big2mpz($x);
5190             Math::GMPz::Rmpz_invert($r, $r, _big2mpz($y)) || return nan;
5191             _mpz2big($r);
5192             };
5193              
5194             Class::Multimethods::multimethod modinv => qw(Math::BigNum $) => sub {
5195             my ($x, $y) = @_;
5196             my $z = _str2mpz($y) // return $x->modinv(Math::BigNum->new($y));
5197             my $r = _big2mpz($x);
5198             Math::GMPz::Rmpz_invert($r, $r, $z) || return nan;
5199             _mpz2big($r);
5200             };
5201              
5202             Class::Multimethods::multimethod modinv => qw(Math::BigNum *) => sub {
5203             $_[0]->modinv(Math::BigNum->new($_[1]));
5204             };
5205              
5206             Class::Multimethods::multimethod modinv => qw(Math::BigNum Math::BigNum::Inf) => \&nan;
5207             Class::Multimethods::multimethod modinv => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
5208              
5209             =head2 modpow
5210              
5211             $x->modpow(BigNum, BigNum) # => BigNum | Nan
5212             $x->modpow(Scalar, Scalar) # => BigNum | Nan
5213             $x->modpow(BigNum, Scalar) # => BigNum | Nan
5214             $x->modpow(Scalar, BigNum) # => BigNum | Nan
5215              
5216             Calculates C<(x ^ y) mod z>, where all three values are integers.
5217              
5218             Returns Nan when the third argument is 0.
5219              
5220             =cut
5221              
5222             Class::Multimethods::multimethod modpow => qw(Math::BigNum Math::BigNum Math::BigNum) => sub {
5223             my ($x, $y, $z) = @_;
5224             my $mod = _big2mpz($z);
5225             Math::GMPz::Rmpz_sgn($mod) || return nan();
5226             my $r = _big2mpz($x);
5227             Math::GMPz::Rmpz_powm($r, $r, _big2mpz($y), $mod);
5228             _mpz2big($r);
5229             };
5230              
5231             Class::Multimethods::multimethod modpow => qw(Math::BigNum Math::BigNum $) => sub {
5232             my ($x, $y, $z) = @_;
5233             my $mod = _str2mpz($z) // return $x->modpow($y, Math::BigNum->new($z));
5234             Math::GMPz::Rmpz_sgn($mod) || return nan();
5235             my $r = _big2mpz($x);
5236             Math::GMPz::Rmpz_powm($r, $r, _big2mpz($y), $mod);
5237             _mpz2big($r);
5238             };
5239              
5240             Class::Multimethods::multimethod modpow => qw(Math::BigNum $ $) => sub {
5241             my ($x, $y, $z) = @_;
5242              
5243             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
5244             my $mod = _str2mpz($z) // return $x->modpow($y, Math::BigNum->new($z));
5245             Math::GMPz::Rmpz_sgn($mod) || return nan();
5246             my $r = _big2mpz($x);
5247             if ($y >= 0) {
5248             Math::GMPz::Rmpz_powm_ui($r, $r, $y, $mod);
5249             }
5250             else {
5251             Math::GMPz::Rmpz_powm($r, $r, _str2mpz($y) // (return $x->modpow(Math::BigNum->new($y), $z)), $mod);
5252             }
5253             _mpz2big($r);
5254             }
5255             else {
5256             $x->modpow(Math::BigNum->new($y), Math::BigNum->new($z));
5257             }
5258             };
5259              
5260             Class::Multimethods::multimethod modpow => qw(Math::BigNum $ Math::BigNum) => sub {
5261             my ($x, $y, $z) = @_;
5262              
5263             my $mod = _big2mpz($z);
5264             Math::GMPz::Rmpz_sgn($mod) || return nan();
5265              
5266             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
5267             my $r = _big2mpz($x);
5268             if ($y >= 0) {
5269             Math::GMPz::Rmpz_powm_ui($r, $r, $y, $mod);
5270             }
5271             else {
5272             Math::GMPz::Rmpz_powm($r, $r, _str2mpz($y) // (return $x->modpow(Math::BigNum->new($y), $z)), $mod);
5273             }
5274             _mpz2big($r);
5275             }
5276             else {
5277             $x->modpow(Math::BigNum->new($y), $z);
5278             }
5279             };
5280              
5281             Class::Multimethods::multimethod modpow => qw(Math::BigNum Math::BigNum *) => sub {
5282             $_[0]->modpow($_[1], Math::BigNum->new($_[2]));
5283             };
5284              
5285             Class::Multimethods::multimethod modpow => qw(Math::BigNum * Math::BigNum) => sub {
5286             $_[0]->modpow(Math::BigNum->new($_[1]), $_[2]);
5287             };
5288              
5289             Class::Multimethods::multimethod modpow => qw(Math::BigNum * *) => sub {
5290             $_[0]->modpow(Math::BigNum->new($_[1]), Math::BigNum->new($_[2]));
5291             };
5292              
5293             Class::Multimethods::multimethod modpow => qw(Math::BigNum Math::BigNum::Inf *) => sub {
5294             $_[0]->pow($_[1])->bmod($_[3]);
5295             };
5296              
5297             Class::Multimethods::multimethod modpow => qw(Math::BigNum * Math::BigNum::Inf) => sub {
5298             $_[0]->pow($_[1])->bmod($_[3]);
5299             };
5300              
5301             Class::Multimethods::multimethod modpow => qw(Math::BigNum Math::BigNum::Nan *) => \&nan;
5302             Class::Multimethods::multimethod modpow => qw(Math::BigNum * Math::BigNum::Nan) => \&nan;
5303              
5304             =head2 gcd
5305              
5306             $x->gcd(BigNum) # => BigNum
5307             $x->gcd(Scalar) # => BigNum
5308              
5309             The greatest common divisor of C and C.
5310              
5311             =cut
5312              
5313             Class::Multimethods::multimethod gcd => qw(Math::BigNum Math::BigNum) => sub {
5314             my ($x, $y) = @_;
5315             my $r = _big2mpz($x);
5316             Math::GMPz::Rmpz_gcd($r, $r, _big2mpz($y));
5317             _mpz2big($r);
5318             };
5319              
5320             Class::Multimethods::multimethod gcd => qw(Math::BigNum $) => sub {
5321             my ($x, $y) = @_;
5322             my $r = _big2mpz($x);
5323             Math::GMPz::Rmpz_gcd($r, $r, _str2mpz($y) // (return $x->gcd(Math::BigNum->new($y))));
5324             _mpz2big($r);
5325             };
5326              
5327             Class::Multimethods::multimethod gcd => qw(Math::BigNum *) => sub {
5328             $_[0]->gcd(Math::BigNum->new($_[1]));
5329             };
5330              
5331             Class::Multimethods::multimethod gcd => qw(Math::BigNum Math::BigNum::Inf) => \&nan;
5332             Class::Multimethods::multimethod gcd => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
5333              
5334             =head2 lcm
5335              
5336             $x->lcd(BigNum) # => BigNum
5337             $x->lcd(Scalar) # => BigNum
5338              
5339             The least common multiple of C and C.
5340              
5341             =cut
5342              
5343             Class::Multimethods::multimethod lcm => qw(Math::BigNum Math::BigNum) => sub {
5344             my ($x, $y) = @_;
5345             my $r = _big2mpz($x);
5346             Math::GMPz::Rmpz_lcm($r, $r, _big2mpz($y));
5347             _mpz2big($r);
5348             };
5349              
5350             Class::Multimethods::multimethod lcm => qw(Math::BigNum $) => sub {
5351             my ($x, $y) = @_;
5352              
5353             my $r = _big2mpz($x);
5354              
5355             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
5356             Math::GMPz::Rmpz_lcm_ui($r, $r, CORE::abs($y));
5357             }
5358             else {
5359             my $z = _str2mpz($y) // return $x->lcm(Math::BigNum->new($y));
5360             Math::GMPz::Rmpz_lcm($r, $r, $z);
5361             }
5362              
5363             _mpz2big($r);
5364             };
5365              
5366             Class::Multimethods::multimethod lcm => qw(Math::BigNum *) => sub {
5367             $_[0]->lcm(Math::BigNum->new($_[1]));
5368             };
5369              
5370             Class::Multimethods::multimethod lcm => qw(Math::BigNum Math::BigNum::Inf) => \&nan;
5371             Class::Multimethods::multimethod lcm => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
5372              
5373             =head2 valuation
5374              
5375             $n->valuation(BigNum) # => Scalar
5376             $n->valuation(Scalar) # => Scalar
5377              
5378             Returns the number of times n is divisible by k.
5379              
5380             =cut
5381              
5382             Class::Multimethods::multimethod valuation => qw(Math::BigNum Math::BigNum) => sub {
5383             my ($x, $y) = @_;
5384              
5385             my $z = _big2mpz($y);
5386             my $sgn = Math::GMPz::Rmpz_sgn($z) || return 0;
5387             Math::GMPz::Rmpz_abs($z, $z) if $sgn < 0;
5388              
5389             my $r = _big2mpz($x);
5390             Math::GMPz::Rmpz_remove($r, $r, $z);
5391             };
5392              
5393             Class::Multimethods::multimethod valuation => qw(Math::BigNum $) => sub {
5394             my ($x, $y) = @_;
5395              
5396             my $z = _str2mpz($y) // return $x->valuation(Math::BigNum->new($y));
5397             my $sgn = Math::GMPz::Rmpz_sgn($z) || return 0;
5398             Math::GMPz::Rmpz_abs($z, $z) if $sgn < 0;
5399              
5400             my $r = _big2mpz($x);
5401             Math::GMPz::Rmpz_remove($r, $r, $z);
5402             };
5403              
5404             Class::Multimethods::multimethod valuation => qw(Math::BigNum *) => sub {
5405             $_[0]->valuation(Math::BigNum->new($_[1]));
5406             };
5407              
5408             Class::Multimethods::multimethod valuation => qw(Math::BigNum Math::BigNum::Inf) => sub { 0 };
5409             Class::Multimethods::multimethod valuation => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
5410              
5411             =head2 kronecker
5412              
5413             $n->kronecker(BigNum) # => Scalar
5414             $n->kronecker(Scalar) # => Scalar
5415              
5416             Returns the Kronecker symbol I<(n|m)>, which is a generalization of the Jacobi symbol for all integers I.
5417              
5418             =cut
5419              
5420             Class::Multimethods::multimethod kronecker => qw(Math::BigNum Math::BigNum) => sub {
5421             Math::GMPz::Rmpz_kronecker(_big2mpz($_[0]), _big2mpz($_[1]));
5422             };
5423              
5424             Class::Multimethods::multimethod kronecker => qw(Math::BigNum $) => sub {
5425             my ($x, $y) = @_;
5426             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
5427             $y >= 0
5428             ? Math::GMPz::Rmpz_kronecker_ui(_big2mpz($x), $y)
5429             : Math::GMPz::Rmpz_kronecker_si(_big2mpz($x), $y);
5430             }
5431             else {
5432             $x->kronecker(Math::BigNum->new($y));
5433             }
5434             };
5435              
5436             Class::Multimethods::multimethod kronecker => qw(Math::BigNum *) => sub {
5437             $_[0]->kronecker(Math::BigNum->new($_[1]));
5438             };
5439              
5440             Class::Multimethods::multimethod kronecker => qw(Math::BigNum Math::BigNum::Inf) => \&nan;
5441             Class::Multimethods::multimethod kronecker => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
5442              
5443             =head2 is_psqr
5444              
5445             $n->is_psqr # => Bool
5446              
5447             Returns a true value when C is a perfect square.
5448             When C is not an integer, returns C<0>.
5449              
5450             =cut
5451              
5452             sub is_psqr {
5453             my ($x) = @_;
5454             Math::GMPq::Rmpq_integer_p($$x) || return 0;
5455             my $z = Math::GMPz::Rmpz_init();
5456             Math::GMPq::Rmpq_numref($z, $$x);
5457             Math::GMPz::Rmpz_perfect_square_p($z);
5458             }
5459              
5460             =head2 is_ppow
5461              
5462             $n->is_ppow # => Bool
5463              
5464             Returns a true value when C is a perfect power of some integer C.
5465             When C is not an integer, returns C<0>.
5466              
5467             =cut
5468              
5469             sub is_ppow {
5470             my ($x) = @_;
5471             Math::GMPq::Rmpq_integer_p($$x) || return 0;
5472             my $z = Math::GMPz::Rmpz_init();
5473             Math::GMPq::Rmpq_numref($z, $$x);
5474             Math::GMPz::Rmpz_perfect_power_p($z);
5475             }
5476              
5477             =head2 is_pow
5478              
5479             $n->is_pow(BigNum) # => Bool
5480             $n->is_pow(Scalar) # => Bool
5481              
5482             Return a true value when C is a perfect power of a given integer C.
5483             When C is not an integer, returns C<0>. On the other hand, when C is not an integer,
5484             it will be truncated implicitly to an integer. If C is not positive after truncation, C<0> is returned.
5485              
5486             A true value is returned iff there exists some integer I satisfying the equation: I.
5487              
5488             Example:
5489              
5490             100->is_pow(2) # true: 100 is a square (10^2)
5491             125->is_pow(3) # true: 125 is a cube ( 5^3)
5492              
5493             =cut
5494              
5495             Class::Multimethods::multimethod is_pow => qw(Math::BigNum Math::BigNum) => sub {
5496             my ($x, $y) = @_;
5497              
5498             Math::GMPq::Rmpq_integer_p($$x) || return 0;
5499             Math::GMPq::Rmpq_equal($$x, $ONE) && return 1;
5500              
5501             $x = $$x;
5502             $y = CORE::int(Math::GMPq::Rmpq_get_d($$y));
5503              
5504             # Everything is a first power
5505             $y == 1 and return 1;
5506              
5507             # Return a true value when $x=-1 and $y is odd
5508             $y % 2 and Math::GMPq::Rmpq_equal($x, $MONE) and return 1;
5509              
5510             # Don't accept a non-positive power
5511             # Also, when $x is negative and $y is even, return faster
5512             if ($y <= 0 or ($y % 2 == 0 and Math::GMPq::Rmpq_sgn($x) < 0)) {
5513             return 0;
5514             }
5515              
5516             my $z = Math::GMPz::Rmpz_init_set($x);
5517              
5518             # Optimization for perfect squares
5519             $y == 2 and return Math::GMPz::Rmpz_perfect_square_p($z);
5520              
5521             Math::GMPz::Rmpz_perfect_power_p($z) || return 0;
5522             Math::GMPz::Rmpz_root($z, $z, $y);
5523             };
5524              
5525             Class::Multimethods::multimethod is_pow => qw(Math::BigNum $) => sub {
5526             my ($x, $y) = @_;
5527              
5528             Math::GMPq::Rmpq_integer_p($$x) || return 0;
5529             Math::GMPq::Rmpq_equal($$x, $ONE) && return 1;
5530              
5531             if (CORE::int($y) eq $y and $y <= MAX_UI) {
5532              
5533             # Everything is a first power
5534             $y == 1 and return 1;
5535              
5536             # Deref $x
5537             $x = $$x;
5538              
5539             # Return a true value when $x=-1 and $y is odd
5540             $y % 2 and Math::GMPq::Rmpq_equal($x, $MONE) and return 1;
5541              
5542             # Don't accept a non-positive power
5543             # Also, when $x is negative and $y is even, return faster
5544             if ($y <= 0 or ($y % 2 == 0 and Math::GMPq::Rmpq_sgn($x) < 0)) {
5545             return 0;
5546             }
5547              
5548             my $z = Math::GMPz::Rmpz_init_set($x);
5549              
5550             # Optimization for perfect squares
5551             $y == 2 and return Math::GMPz::Rmpz_perfect_square_p($z);
5552              
5553             Math::GMPz::Rmpz_perfect_power_p($z) || return 0;
5554             Math::GMPz::Rmpz_root($z, $z, $y);
5555             }
5556             else {
5557             $x->is_pow(Math::BigNum->new($y));
5558             }
5559             };
5560              
5561             Class::Multimethods::multimethod is_pow => qw(Math::BigNum *) => sub {
5562             $_[0]->is_pow(Math::BigNum->new($_[1]));
5563             };
5564              
5565             Class::Multimethods::multimethod is_pow => qw(Math::BigNum Math::BigNum::Inf) => sub { 0 };
5566             Class::Multimethods::multimethod is_pow => qw(Math::BigNum Math::BigNum::Nan) => sub { 0 };
5567              
5568             =head2 is_prime
5569              
5570             $n->is_prime # => Scalar
5571             $x->is_prime(BigNum) # => Scalar
5572             $n->is_prime(Scalar) # => Scalar
5573              
5574             Returns 2 if C is definitely prime, 1 if C is probably prime (without
5575             being certain), or 0 if C is definitely composite. This method does some
5576             trial divisions, then some Miller-Rabin probabilistic primality tests. It
5577             also accepts an optional argument for specifying the accuracy of the test.
5578             By default, it uses an accuracy value of 20.
5579              
5580             Reasonable accuracy values are between 15 and 50.
5581              
5582             See also:
5583              
5584             https://en.wikipedia.org/wiki/Miller–Rabin_primality_test
5585             https://gmplib.org/manual/Number-Theoretic-Functions.html
5586              
5587             =cut
5588              
5589             Class::Multimethods::multimethod is_prime => qw(Math::BigNum) => sub {
5590             Math::GMPz::Rmpz_probab_prime_p(_big2mpz($_[0]), 20);
5591             };
5592              
5593             Class::Multimethods::multimethod is_prime => qw(Math::BigNum $) => sub {
5594             Math::GMPz::Rmpz_probab_prime_p(_big2mpz($_[0]), CORE::abs(CORE::int($_[1])));
5595             };
5596              
5597             Class::Multimethods::multimethod is_prime => qw(Math::BigNum Math::BigNum) => sub {
5598             Math::GMPz::Rmpz_probab_prime_p(_big2mpz($_[0]), CORE::abs(CORE::int(Math::GMPq::Rmpq_get_d(${$_[1]}))));
5599             };
5600              
5601             =head2 next_prime
5602              
5603             $n->next_prime # => BigNum
5604              
5605             Returns the next prime after C.
5606              
5607             =cut
5608              
5609             sub next_prime {
5610             my ($x) = @_;
5611             my $r = _big2mpz($x);
5612             Math::GMPz::Rmpz_nextprime($r, $r);
5613             _mpz2big($r);
5614             }
5615              
5616             =head2 fac
5617              
5618             $n->fac # => BigNum | Nan
5619              
5620             Factorial of C. Returns Nan when C is negative. (C<1*2*3*...*n>)
5621              
5622             =cut
5623              
5624             sub fac {
5625             my ($n) = @_;
5626             $n = CORE::int(Math::GMPq::Rmpq_get_d($$n));
5627             return nan() if $n < 0;
5628             my $r = Math::GMPz::Rmpz_init();
5629             Math::GMPz::Rmpz_fac_ui($r, $n);
5630             _mpz2big($r);
5631             }
5632              
5633             =head2 bfac
5634              
5635             $n->bfac # => BigNum | Nan
5636              
5637             Factorial of C, modifying C in-place.
5638              
5639             =cut
5640              
5641             sub bfac {
5642             my ($x) = @_;
5643             my $n = CORE::int(Math::GMPq::Rmpq_get_d($$x));
5644             return $x->bnan() if $n < 0;
5645             my $r = Math::GMPz::Rmpz_init();
5646             Math::GMPz::Rmpz_fac_ui($r, $n);
5647             Math::GMPq::Rmpq_set_z($$x, $r);
5648             $x;
5649             }
5650              
5651             =head2 dfac
5652              
5653             $n->dfac # => BigNum | Nan
5654              
5655             Double factorial of C. Returns Nan when C is negative.
5656              
5657             Example:
5658              
5659             7->dfac # 1*3*5*7 = 105
5660             8->dfac # 2*4*6*8 = 384
5661              
5662             =cut
5663              
5664             sub dfac {
5665             my ($n) = @_;
5666             $n = CORE::int(Math::GMPq::Rmpq_get_d($$n));
5667             return nan() if $n < 0;
5668             my $r = Math::GMPz::Rmpz_init();
5669             Math::GMPz::Rmpz_2fac_ui($r, $n);
5670             _mpz2big($r);
5671             }
5672              
5673             =head2 primorial
5674              
5675             $n->primorial # => BigNum | Nan
5676              
5677             Returns the product of all the primes less than or equal to C.
5678              
5679             =cut
5680              
5681             sub primorial {
5682             my ($n) = @_;
5683             $n = CORE::int(Math::GMPq::Rmpq_get_d($$n));
5684             return nan() if $n < 0;
5685             my $r = Math::GMPz::Rmpz_init();
5686             Math::GMPz::Rmpz_primorial_ui($r, $n);
5687             _mpz2big($r);
5688             }
5689              
5690             =head2 fib
5691              
5692             $n->fib # => BigNum | Nan
5693              
5694             The n-th Fibonacci number. Returns Nan when C is negative.
5695              
5696             Defined as:
5697              
5698             fib(0) = 0
5699             fib(1) = 1
5700             fib(n) = fib(n-1) + fib(n-2)
5701              
5702             =cut
5703              
5704             sub fib {
5705             my ($n) = @_;
5706             $n = CORE::int(Math::GMPq::Rmpq_get_d($$n));
5707             return nan() if $n < 0;
5708             my $r = Math::GMPz::Rmpz_init();
5709             Math::GMPz::Rmpz_fib_ui($r, $n);
5710             _mpz2big($r);
5711             }
5712              
5713             =head2 lucas
5714              
5715             $n->lucas # => BigNum | Nan
5716              
5717             The n-th Lucas number. Returns Nan when C is negative.
5718              
5719             Defined as:
5720              
5721             lucas(0) = 2
5722             lucas(1) = 1
5723             lucas(n) = lucas(n-1) + lucas(n-2)
5724              
5725             =cut
5726              
5727             sub lucas {
5728             my ($n) = @_;
5729             $n = CORE::int(Math::GMPq::Rmpq_get_d($$n));
5730             return nan() if $n < 0;
5731             my $r = Math::GMPz::Rmpz_init();
5732             Math::GMPz::Rmpz_lucnum_ui($r, $n);
5733             _mpz2big($r);
5734             }
5735              
5736             =head2 binomial
5737              
5738             $n->binomial(BigNum) # => BigNum
5739             $n->binomial(Scalar) # => BigNum
5740              
5741             Calculates the binomial coefficient n over k, also called the
5742             "choose" function. The result is equivalent to:
5743              
5744             ( n ) n!
5745             | | = -------
5746             ( k ) k!(n-k)!
5747              
5748             =cut
5749              
5750             Class::Multimethods::multimethod binomial => qw(Math::BigNum Math::BigNum) => sub {
5751             my ($x, $y) = @_;
5752             my $r = _big2mpz($x);
5753             $y = CORE::int(Math::GMPq::Rmpq_get_d($$y));
5754             $y >= 0
5755             ? Math::GMPz::Rmpz_bin_ui($r, $r, $y)
5756             : Math::GMPz::Rmpz_bin_si($r, $r, $y);
5757             _mpz2big($r);
5758             };
5759              
5760             Class::Multimethods::multimethod binomial => qw(Math::BigNum $) => sub {
5761             my ($x, $y) = @_;
5762             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
5763             my $r = _big2mpz($x);
5764             $y >= 0
5765             ? Math::GMPz::Rmpz_bin_ui($r, $r, $y)
5766             : Math::GMPz::Rmpz_bin_si($r, $r, $y);
5767             _mpz2big($r);
5768             }
5769             else {
5770             $x->binomial(Math::BigNum->new($y));
5771             }
5772             };
5773              
5774             Class::Multimethods::multimethod binomial => qw(Math::BigNum *) => sub {
5775             $_[0]->binomial(Math::BigNum->new($_[1]));
5776             };
5777              
5778             Class::Multimethods::multimethod binomial => qw(Math::BigNum Math::BigNum::Inf) => \&nan;
5779             Class::Multimethods::multimethod binomial => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
5780              
5781             =head1 * Bitwise operations
5782              
5783             =cut
5784              
5785             =head2 and
5786              
5787             $x->and(BigNum) # => BigNum
5788             $x->and(Scalar) # => BigNum
5789              
5790             BigNum & BigNum # => BigNum
5791             BigNum & Scalar # => BigNum
5792             Scalar & BigNum # => BigNum
5793              
5794             Integer logical-and operation.
5795              
5796             =cut
5797              
5798             Class::Multimethods::multimethod and => qw(Math::BigNum Math::BigNum) => sub {
5799             my $r = _big2mpz($_[0]);
5800             Math::GMPz::Rmpz_and($r, $r, _big2mpz($_[1]));
5801             _mpz2big($r);
5802             };
5803              
5804             Class::Multimethods::multimethod and => qw(Math::BigNum $) => sub {
5805             my $z = _str2mpz($_[1]) // return Math::BigNum->new($_[1])->band($_[0]);
5806             my $r = _big2mpz($_[0]);
5807             Math::GMPz::Rmpz_and($r, $r, $z);
5808             _mpz2big($r);
5809             };
5810              
5811             Class::Multimethods::multimethod and => qw($ Math::BigNum) => sub {
5812             my $r = _str2mpz($_[0]) // return Math::BigNum->new($_[0])->band($_[1]);
5813             Math::GMPz::Rmpz_and($r, $r, _big2mpz($_[1]));
5814             _mpz2big($r);
5815             };
5816              
5817             Class::Multimethods::multimethod and => qw(* Math::BigNum) => sub {
5818             Math::BigNum->new($_[0])->band($_[1]);
5819             };
5820              
5821             Class::Multimethods::multimethod and => qw(Math::BigNum *) => sub {
5822             Math::BigNum->new($_[1])->band($_[0]);
5823             };
5824              
5825             Class::Multimethods::multimethod and => qw(Math::BigNum Math::BigNum::Inf) => \&nan;
5826             Class::Multimethods::multimethod and => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
5827              
5828             =head2 band
5829              
5830             $x->band(BigNum) # => BigNum
5831             $x->band(Scalar) # => BigNum
5832              
5833             BigNum &= BigNum # => BigNum
5834             BigNum &= Scalar # => BigNum
5835              
5836             Integer logical-and operation, changing C in-place.
5837              
5838             =cut
5839              
5840             Class::Multimethods::multimethod band => qw(Math::BigNum Math::BigNum) => sub {
5841             my $r = _big2mpz($_[0]);
5842             Math::GMPz::Rmpz_and($r, $r, _big2mpz($_[1]));
5843             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
5844             $_[0];
5845             };
5846              
5847             Class::Multimethods::multimethod band => qw(Math::BigNum $) => sub {
5848             my $z = _str2mpz($_[1]) // return $_[0]->band(Math::BigNum->new($_[1]));
5849             my $r = _big2mpz($_[0]);
5850             Math::GMPz::Rmpz_and($r, $r, $z);
5851             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
5852             $_[0];
5853             };
5854              
5855             Class::Multimethods::multimethod band => qw(Math::BigNum *) => sub {
5856             $_[0]->band(Math::BigNum->new($_[1]));
5857             };
5858              
5859             Class::Multimethods::multimethod band => qw(Math::BigNum Math::BigNum::Inf) => \&bnan;
5860             Class::Multimethods::multimethod band => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
5861              
5862             =head2 ior
5863              
5864             $x->ior(BigNum) # => BigNum
5865             $x->ior(Scalar) # => BigNum
5866              
5867             BigNum | BigNum # => BigNum
5868             BigNum | Scalar # => BigNum
5869             Scalar | BigNum # => BigNum
5870              
5871             Integer logical inclusive-or operation.
5872              
5873             =cut
5874              
5875             Class::Multimethods::multimethod ior => qw(Math::BigNum Math::BigNum) => sub {
5876             my $r = _big2mpz($_[0]);
5877             Math::GMPz::Rmpz_ior($r, $r, _big2mpz($_[1]));
5878             _mpz2big($r);
5879             };
5880              
5881             Class::Multimethods::multimethod ior => qw(Math::BigNum $) => sub {
5882             my $z = _str2mpz($_[1]) // return Math::BigNum->new($_[1])->bior($_[0]);
5883             my $r = _big2mpz($_[0]);
5884             Math::GMPz::Rmpz_ior($r, $r, $z);
5885             _mpz2big($r);
5886             };
5887              
5888             Class::Multimethods::multimethod ior => qw($ Math::BigNum) => sub {
5889             my $r = _str2mpz($_[0]) // return Math::BigNum->new($_[0])->bior($_[1]);
5890             Math::GMPz::Rmpz_ior($r, $r, _big2mpz($_[1]));
5891             _mpz2big($r);
5892             };
5893              
5894             Class::Multimethods::multimethod ior => qw(* Math::BigNum) => sub {
5895             Math::BigNum->new($_[0])->bior($_[1]);
5896             };
5897              
5898             Class::Multimethods::multimethod ior => qw(Math::BigNum *) => sub {
5899             $_[0]->ior(Math::BigNum->new($_[1]));
5900             };
5901              
5902             Class::Multimethods::multimethod ior => qw(Math::BigNum Math::BigNum::Inf) => \&nan;
5903             Class::Multimethods::multimethod ior => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
5904              
5905             =head2 bior
5906              
5907             $x->bior(BigNum) # => BigNum
5908             $x->bior(Scalar) # => BigNum
5909              
5910             BigNum |= BigNum # => BigNum
5911             BigNum |= Scalar # => BigNum
5912              
5913             Integer logical inclusive-or operation, changing C in-place.
5914              
5915             =cut
5916              
5917             Class::Multimethods::multimethod bior => qw(Math::BigNum Math::BigNum) => sub {
5918             my $r = _big2mpz($_[0]);
5919             Math::GMPz::Rmpz_ior($r, $r, _big2mpz($_[1]));
5920             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
5921             $_[0];
5922             };
5923              
5924             Class::Multimethods::multimethod bior => qw(Math::BigNum $) => sub {
5925             my $z = _str2mpz($_[1]) // return $_[0]->bior(Math::BigNum->new($_[1]));
5926             my $r = _big2mpz($_[0]);
5927             Math::GMPz::Rmpz_ior($r, $r, $z);
5928             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
5929             $_[0];
5930             };
5931              
5932             Class::Multimethods::multimethod bior => qw(Math::BigNum *) => sub {
5933             $_[0]->bior(Math::BigNum->new($_[1]));
5934             };
5935              
5936             Class::Multimethods::multimethod bior => qw(Math::BigNum Math::BigNum::Inf) => \&bnan;
5937             Class::Multimethods::multimethod bior => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
5938              
5939             =head2 xor
5940              
5941             $x->xor(BigNum) # => BigNum
5942             $x->xor(Scalar) # => BigNum
5943              
5944             BigNum ^ BigNum # => BigNum
5945             BigNum ^ Scalar # => BigNum
5946             Scalar ^ BigNum # => BigNum
5947              
5948             Integer logical exclusive-or operation.
5949              
5950             =cut
5951              
5952             Class::Multimethods::multimethod xor => qw(Math::BigNum Math::BigNum) => sub {
5953             my $r = _big2mpz($_[0]);
5954             Math::GMPz::Rmpz_xor($r, $r, _big2mpz($_[1]));
5955             _mpz2big($r);
5956             };
5957              
5958             Class::Multimethods::multimethod xor => qw(Math::BigNum $) => sub {
5959             my $z = _str2mpz($_[1]) // return $_[0]->xor(Math::BigNum->new($_[1]));
5960             my $r = _big2mpz($_[0]);
5961             Math::GMPz::Rmpz_xor($r, $r, $z);
5962             _mpz2big($r);
5963             };
5964              
5965             Class::Multimethods::multimethod xor => qw($ Math::BigNum) => sub {
5966             my $r = _str2mpz($_[0]) // return Math::BigNum->new($_[0])->bxor($_[1]);
5967             Math::GMPz::Rmpz_xor($r, $r, _big2mpz($_[1]));
5968             _mpz2big($r);
5969             };
5970              
5971             Class::Multimethods::multimethod xor => qw(* Math::BigNum) => sub {
5972             Math::BigNum->new($_[0])->bxor($_[1]);
5973             };
5974              
5975             Class::Multimethods::multimethod xor => qw(Math::BigNum *) => sub {
5976             $_[0]->xor(Math::BigNum->new($_[1]));
5977             };
5978              
5979             Class::Multimethods::multimethod xor => qw(Math::BigNum Math::BigNum::Inf) => \&nan;
5980             Class::Multimethods::multimethod xor => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
5981              
5982             =head2 bxor
5983              
5984             $x->bxor(BigNum) # => BigNum
5985             $x->bxor(Scalar) # => BigNum
5986              
5987             BigNum ^= BigNum # => BigNum
5988             BigNum ^= Scalar # => BigNum
5989              
5990             Integer logical exclusive-or operation, changing C in-place.
5991              
5992             =cut
5993              
5994             Class::Multimethods::multimethod bxor => qw(Math::BigNum Math::BigNum) => sub {
5995             my $r = _big2mpz($_[0]);
5996             Math::GMPz::Rmpz_xor($r, $r, _big2mpz($_[1]));
5997             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
5998             $_[0];
5999             };
6000              
6001             Class::Multimethods::multimethod bxor => qw(Math::BigNum $) => sub {
6002             my $z = _str2mpz($_[1]) // return $_[0]->bxor(Math::BigNum->new($_[1]));
6003             my $r = _big2mpz($_[0]);
6004             Math::GMPz::Rmpz_xor($r, $r, $z);
6005             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
6006             $_[0];
6007             };
6008              
6009             Class::Multimethods::multimethod bxor => qw(Math::BigNum *) => sub {
6010             $_[0]->bxor(Math::BigNum->new($_[1]));
6011             };
6012              
6013             Class::Multimethods::multimethod bxor => qw(Math::BigNum Math::BigNum::Inf) => \&bnan;
6014             Class::Multimethods::multimethod bxor => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
6015              
6016             =head2 not
6017              
6018             $x->not # => BigNum
6019             ~BigNum # => BigNum
6020              
6021             Integer logical-not operation. (The one's complement of C).
6022              
6023             =cut
6024              
6025             sub not {
6026             my $r = _big2mpz($_[0]);
6027             Math::GMPz::Rmpz_com($r, $r);
6028             _mpz2big($r);
6029             }
6030              
6031             =head2 bnot
6032              
6033             $x->bnot # => BigNum
6034              
6035             Integer logical-not operation, changing C in-place.
6036              
6037             =cut
6038              
6039             sub bnot {
6040             my $r = _big2mpz($_[0]);
6041             Math::GMPz::Rmpz_com($r, $r);
6042             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
6043             $_[0];
6044             }
6045              
6046             =head2 lsft
6047              
6048             $x->lsft(BigNum) # => BigNum
6049             $x->lsft(Scalar) # => BigNum
6050              
6051             BigNum << BigNum # => BigNum
6052             BigNum << Scalar # => BigNum
6053             Scalar << BigNum # => BigNum
6054              
6055             Integer left-shift operation. (C)
6056              
6057             =cut
6058              
6059             Class::Multimethods::multimethod lsft => qw(Math::BigNum Math::BigNum) => sub {
6060             my $r = _big2mpz($_[0]);
6061             my $i = CORE::int(Math::GMPq::Rmpq_get_d(${$_[1]}));
6062             $i < 0
6063             ? Math::GMPz::Rmpz_div_2exp($r, $r, CORE::abs($i))
6064             : Math::GMPz::Rmpz_mul_2exp($r, $r, $i);
6065             _mpz2big($r);
6066             };
6067              
6068             Class::Multimethods::multimethod lsft => qw(Math::BigNum $) => sub {
6069             my ($x, $y) = @_;
6070              
6071             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
6072             my $r = _big2mpz($x);
6073             $y < 0
6074             ? Math::GMPz::Rmpz_div_2exp($r, $r, CORE::abs($y))
6075             : Math::GMPz::Rmpz_mul_2exp($r, $r, $y);
6076             _mpz2big($r);
6077             }
6078             else {
6079             $x->lsft(Math::BigNum->new($y));
6080             }
6081             };
6082              
6083             Class::Multimethods::multimethod lsft => qw($ Math::BigNum) => sub {
6084             my ($x, $y) = @_;
6085              
6086             my $r = _str2mpz($_[0]) // return Math::BigNum->new($x)->blsft($y);
6087             my $i = CORE::int(Math::GMPq::Rmpq_get_d(${$_[1]}));
6088             $i < 0
6089             ? Math::GMPz::Rmpz_div_2exp($r, $r, CORE::abs($i))
6090             : Math::GMPz::Rmpz_mul_2exp($r, $r, $i);
6091             _mpz2big($r);
6092             };
6093              
6094             Class::Multimethods::multimethod lsft => qw(* Math::BigNum) => sub {
6095             Math::BigNum->new($_[0])->blsft($_[1]);
6096             };
6097              
6098             Class::Multimethods::multimethod lsft => qw(Math::BigNum *) => sub {
6099             $_[0]->lsft(Math::BigNum->new($_[1]));
6100             };
6101              
6102             Class::Multimethods::multimethod lsft => qw(Math::BigNum Math::BigNum::Inf) => sub {
6103             $_[1]->is_neg || $_[0]->int->is_zero ? zero()
6104             : $_[0]->is_neg ? ninf()
6105             : inf();
6106             };
6107              
6108             Class::Multimethods::multimethod lsft => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
6109              
6110             =head2 blsft
6111              
6112             $x->blsft(BigNum) # => BigNum
6113             $x->blsft(Scalar) # => BigNum
6114              
6115             BigNum <<= BigNum # => BigNum
6116             BigNum <<= Scalar # => BigNum
6117              
6118             Integer left-shift operation, changing C in-place. Promotes C to Nan when C is negative.
6119             (C)
6120              
6121             =cut
6122              
6123             Class::Multimethods::multimethod blsft => qw(Math::BigNum Math::BigNum) => sub {
6124             my $r = _big2mpz($_[0]);
6125             my $i = CORE::int(Math::GMPq::Rmpq_get_d(${$_[1]}));
6126             $i < 0
6127             ? Math::GMPz::Rmpz_div_2exp($r, $r, CORE::abs($i))
6128             : Math::GMPz::Rmpz_mul_2exp($r, $r, $i);
6129             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
6130             $_[0];
6131             };
6132              
6133             Class::Multimethods::multimethod blsft => qw(Math::BigNum $) => sub {
6134             my ($x, $y) = @_;
6135              
6136             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
6137             my $r = _big2mpz($x);
6138             $y < 0
6139             ? Math::GMPz::Rmpz_div_2exp($r, $r, CORE::abs($y))
6140             : Math::GMPz::Rmpz_mul_2exp($r, $r, $y);
6141             Math::GMPq::Rmpq_set_z($$x, $r);
6142             $x;
6143             }
6144             else {
6145             $x->blsft(Math::BigNum->new($y));
6146             }
6147             };
6148              
6149             Class::Multimethods::multimethod blsft => qw(Math::BigNum *) => sub {
6150             $_[0]->blsft(Math::BigNum->new($_[1]));
6151             };
6152              
6153             Class::Multimethods::multimethod blsft => qw(Math::BigNum Math::BigNum::Inf) => sub {
6154             $_[1]->is_neg || $_[0]->int->is_zero ? $_[0]->bzero()
6155             : $_[0]->is_neg ? $_[0]->bninf()
6156             : $_[0]->binf();
6157             };
6158              
6159             Class::Multimethods::multimethod blsft => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
6160              
6161             =head2 rsft
6162              
6163             $x->rsft(BigNum) # => BigNum
6164             $x->rsft(Scalar) # => BigNum
6165              
6166             BigNum >> BigNum # => BigNum
6167             BigNum >> Scalar # => BigNum
6168             Scalar >> BigNum # => BigNum
6169              
6170             Integer right-shift operation. (C)
6171              
6172             =cut
6173              
6174             Class::Multimethods::multimethod rsft => qw(Math::BigNum Math::BigNum) => sub {
6175             my $r = _big2mpz($_[0]);
6176             my $i = CORE::int(Math::GMPq::Rmpq_get_d(${$_[1]}));
6177             $i < 0
6178             ? Math::GMPz::Rmpz_mul_2exp($r, $r, CORE::abs($i))
6179             : Math::GMPz::Rmpz_div_2exp($r, $r, $i);
6180             _mpz2big($r);
6181             };
6182              
6183             Class::Multimethods::multimethod rsft => qw(Math::BigNum $) => sub {
6184             my ($x, $y) = @_;
6185              
6186             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
6187             my $r = _big2mpz($x);
6188             $y < 0
6189             ? Math::GMPz::Rmpz_mul_2exp($r, $r, CORE::abs($y))
6190             : Math::GMPz::Rmpz_div_2exp($r, $r, $y);
6191             _mpz2big($r);
6192             }
6193             else {
6194             $x->rsft(Math::BigNum->new($y));
6195             }
6196             };
6197              
6198             Class::Multimethods::multimethod rsft => qw($ Math::BigNum) => sub {
6199             my $r = _str2mpz($_[0]) // return Math::BigNum->new($_[0])->brsft($_[1]);
6200             my $i = CORE::int(Math::GMPq::Rmpq_get_d(${$_[1]}));
6201             $i < 0
6202             ? Math::GMPz::Rmpz_mul_2exp($r, $r, CORE::abs($i))
6203             : Math::GMPz::Rmpz_div_2exp($r, $r, $i);
6204             _mpz2big($r);
6205             };
6206              
6207             Class::Multimethods::multimethod rsft => qw(* Math::BigNum) => sub {
6208             Math::BigNum->new($_[0])->brsft($_[1]);
6209             };
6210              
6211             Class::Multimethods::multimethod rsft => qw(Math::BigNum *) => sub {
6212             $_[0]->rsft(Math::BigNum->new($_[1]));
6213             };
6214              
6215             Class::Multimethods::multimethod rsft => qw(Math::BigNum Math::BigNum::Inf) => sub {
6216             $_[1]->is_pos || $_[0]->int->is_zero ? zero()
6217             : $_[0]->is_neg ? ninf()
6218             : inf();
6219             };
6220              
6221             Class::Multimethods::multimethod rsft => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
6222              
6223             =head2 brsft
6224              
6225             $x->brsft(BigNum) # => BigNum
6226             $x->brsft(Scalar) # => BigNum
6227              
6228             BigNum >>= BigNum # => BigNum
6229             BigNum >>= Scalar # => BigNum
6230              
6231             Integer right-shift operation, changing C in-place. (C)
6232              
6233             =cut
6234              
6235             Class::Multimethods::multimethod brsft => qw(Math::BigNum Math::BigNum) => sub {
6236             my $r = _big2mpz($_[0]);
6237             my $i = CORE::int(Math::GMPq::Rmpq_get_d(${$_[1]}));
6238             $i < 0
6239             ? Math::GMPz::Rmpz_mul_2exp($r, $r, CORE::abs($i))
6240             : Math::GMPz::Rmpz_div_2exp($r, $r, $i);
6241             Math::GMPq::Rmpq_set_z(${$_[0]}, $r);
6242             $_[0];
6243             };
6244              
6245             Class::Multimethods::multimethod brsft => qw(Math::BigNum $) => sub {
6246             my ($x, $y) = @_;
6247              
6248             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
6249             my $r = _big2mpz($x);
6250             $y < 0
6251             ? Math::GMPz::Rmpz_mul_2exp($r, $r, CORE::abs($y))
6252             : Math::GMPz::Rmpz_div_2exp($r, $r, $y);
6253             Math::GMPq::Rmpq_set_z($$x, $r);
6254             $x;
6255             }
6256             else {
6257             $x->brsft(Math::BigNum->new($y));
6258             }
6259             };
6260              
6261             Class::Multimethods::multimethod brsft => qw(Math::BigNum *) => sub {
6262             $_[0]->brsft(Math::BigNum->new($_[1]));
6263             };
6264              
6265             Class::Multimethods::multimethod brsft => qw(Math::BigNum Math::BigNum::Inf) => sub {
6266             $_[1]->is_pos || $_[0]->int->is_zero ? $_[0]->bzero()
6267             : $_[0]->is_neg ? $_[0]->bninf()
6268             : $_[0]->binf();
6269             };
6270              
6271             Class::Multimethods::multimethod brsft => qw(Math::BigNum Math::BigNum::Nan) => \&bnan;
6272              
6273             =head2 popcount
6274              
6275             $x->popcount # => Scalar
6276              
6277             Returns the population count of C, which is the number of 1 bits in the binary representation.
6278             When C is negative, the population count of its absolute value is returned.
6279              
6280             This method is also known as the Hamming weight value.
6281              
6282             =cut
6283              
6284             sub popcount {
6285             my $z = _big2mpz($_[0]);
6286             Math::GMPz::Rmpz_neg($z, $z) if Math::GMPz::Rmpz_sgn($z) < 0;
6287             Math::GMPz::Rmpz_popcount($z);
6288             }
6289              
6290             ############################ MISCELLANEOUS ############################
6291              
6292             =head1 MISCELLANEOUS
6293              
6294             This section includes various useful methods.
6295              
6296             =cut
6297              
6298             =head2 rand
6299              
6300             $x->rand # => BigNum
6301             $x->rand(BigNum) # => BigNum
6302             $x->rand(Scalar) # => BigNum
6303              
6304             Returns a pseudorandom floating-point value. When an additional argument is provided,
6305             it returns a number between C and C, otherwise, a number between C<0> (inclusive) and
6306             C (exclusive) is returned.
6307              
6308             The PRNG behind this method is called the "Mersenne Twister". Although it generates pseudorandom
6309             numbers of very good quality, it is B cryptographically secure!
6310              
6311             Example:
6312              
6313             10->rand # a random number between 0 and 10 (exclusive)
6314             10->rand(20) # a random number between 10 and 20 (exclusive)
6315              
6316             =cut
6317              
6318             {
6319             my $srand = srand();
6320              
6321             {
6322             state $state = Math::MPFR::Rmpfr_randinit_mt_nobless();
6323             Math::MPFR::Rmpfr_randseed_ui($state, $srand);
6324              
6325             Class::Multimethods::multimethod rand => qw(Math::BigNum) => sub {
6326             my ($x) = @_;
6327              
6328             my $rand = Math::MPFR::Rmpfr_init2($PREC);
6329             Math::MPFR::Rmpfr_urandom($rand, $state, $ROUND);
6330              
6331             my $q = Math::GMPq::Rmpq_init();
6332             Math::MPFR::Rmpfr_get_q($q, $rand);
6333              
6334             Math::GMPq::Rmpq_mul($q, $q, $$x);
6335             bless \$q, __PACKAGE__;
6336             };
6337              
6338             Class::Multimethods::multimethod rand => qw(Math::BigNum Math::BigNum) => sub {
6339             my ($x, $y) = @_;
6340              
6341             my $rand = Math::MPFR::Rmpfr_init2($PREC);
6342             Math::MPFR::Rmpfr_urandom($rand, $state, $ROUND);
6343              
6344             my $q = Math::GMPq::Rmpq_init();
6345             Math::MPFR::Rmpfr_get_q($q, $rand);
6346              
6347             my $diff = Math::GMPq::Rmpq_init();
6348             Math::GMPq::Rmpq_sub($diff, $$y, $$x);
6349             Math::GMPq::Rmpq_mul($q, $q, $diff);
6350             Math::GMPq::Rmpq_add($q, $q, $$x);
6351              
6352             bless \$q, __PACKAGE__;
6353             };
6354              
6355             Class::Multimethods::multimethod rand => qw(Math::BigNum *) => sub {
6356             $_[0]->rand(Math::BigNum->new($_[1]));
6357             };
6358              
6359             Class::Multimethods::multimethod rand => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->copy };
6360             Class::Multimethods::multimethod rand => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
6361              
6362             =head2 seed
6363              
6364             $n->seed # => BigNum
6365              
6366             Reseeds the C method with the value of C, where C can be any arbitrary large integer.
6367              
6368             Returns back the original value of C.
6369              
6370             =cut
6371              
6372             sub seed {
6373             Math::MPFR::Rmpfr_randseed($state, _big2mpz($_[0]));
6374             $_[0];
6375             }
6376             }
6377              
6378             =head2 irand
6379              
6380             $x->irand # => BigNum
6381             $x->irand(BigNum) # => BigNum
6382             $x->irand(Scalar) # => BigNum
6383              
6384             Returns a pseudorandom integer. When an additional argument is provided, it returns
6385             an integer between C and C, otherwise, an integer between C<0> (inclusive)
6386             and C (exclusive) is returned.
6387              
6388             The PRNG behind this method is called the "Mersenne Twister".
6389             Although it generates high-quality pseudorandom integers, it is B cryptographically secure!
6390              
6391             Example:
6392              
6393             10->irand # a random integer between 0 and 10 (exclusive)
6394             10->irand(20) # a random integer between 10 and 20 (exclusive)
6395              
6396             =cut
6397              
6398             {
6399             state $state = Math::GMPz::zgmp_randinit_mt_nobless();
6400             Math::GMPz::zgmp_randseed_ui($state, $srand);
6401              
6402             Class::Multimethods::multimethod irand => qw(Math::BigNum) => sub {
6403             my ($x) = @_;
6404              
6405             $x = _big2mpz($x);
6406              
6407             my $sgn = Math::GMPz::Rmpz_sgn($x) || return zero();
6408             Math::GMPz::Rmpz_urandomm($x, $state, $x, 1);
6409             Math::GMPz::Rmpz_neg($x, $x) if $sgn < 0;
6410             _mpz2big($x);
6411             };
6412              
6413             Class::Multimethods::multimethod irand => qw(Math::BigNum Math::BigNum) => sub {
6414             my ($x, $y) = @_;
6415              
6416             $x = _big2mpz($x);
6417              
6418             my $rand = _big2mpz($y);
6419             my $cmp = Math::GMPz::Rmpz_cmp($rand, $x);
6420              
6421             if ($cmp == 0) {
6422             return _mpz2big($rand);
6423             }
6424             elsif ($cmp < 0) {
6425             ($x, $rand) = ($rand, $x);
6426             }
6427              
6428             Math::GMPz::Rmpz_sub($rand, $rand, $x);
6429             Math::GMPz::Rmpz_urandomm($rand, $state, $rand, 1);
6430             Math::GMPz::Rmpz_add($rand, $rand, $x);
6431              
6432             _mpz2big($rand);
6433             };
6434              
6435             Class::Multimethods::multimethod irand => qw(Math::BigNum *) => sub {
6436             $_[0]->irand(Math::BigNum->new($_[1]));
6437             };
6438              
6439             Class::Multimethods::multimethod irand => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->copy };
6440             Class::Multimethods::multimethod irand => qw(Math::BigNum Math::BigNum::Nan) => \&nan;
6441              
6442             =head2 iseed
6443              
6444             $n->iseed # => BigNum
6445              
6446             Reseeds the C method with the value of C, where C can be any arbitrary large integer.
6447              
6448             Returns back the original value of C.
6449              
6450             =cut
6451              
6452             sub iseed {
6453             Math::GMPz::zgmp_randseed($state, _big2mpz($_[0]));
6454             $_[0];
6455             }
6456             }
6457             }
6458              
6459             =head2 copy
6460              
6461             $x->copy # => BigNum
6462              
6463             Returns a deep copy of C.
6464              
6465             =cut
6466              
6467             sub copy {
6468             my $r = Math::GMPq::Rmpq_init();
6469             Math::GMPq::Rmpq_set($r, ${$_[0]});
6470             bless \$r, ref($_[0]);
6471             }
6472              
6473             =head2 floor
6474              
6475             $x->floor # => BigNum
6476              
6477             Returns C if C is an integer, otherwise it rounds C towards -Infinity.
6478              
6479             Example:
6480              
6481             floor( 2.5) = 2
6482             floor(-2.5) = -3
6483              
6484             =cut
6485              
6486             sub floor {
6487             my ($x) = @_;
6488             Math::GMPq::Rmpq_integer_p($$x) && return $x->copy;
6489              
6490             if (Math::GMPq::Rmpq_sgn($$x) > 0) {
6491             my $z = Math::GMPz::Rmpz_init();
6492             Math::GMPz::Rmpz_set_q($z, $$x);
6493             _mpz2big($z);
6494             }
6495             else {
6496             my $z = Math::GMPz::Rmpz_init();
6497             Math::GMPz::Rmpz_set_q($z, $$x);
6498             Math::GMPz::Rmpz_sub_ui($z, $z, 1);
6499             _mpz2big($z);
6500             }
6501             }
6502              
6503             =head2 ceil
6504              
6505             $x->ceil # => BigNum
6506              
6507             Returns C if C is an integer, otherwise it rounds C towards +Infinity.
6508              
6509             Example:
6510              
6511             ceil( 2.5) = 3
6512             ceil(-2.5) = -2
6513              
6514             =cut
6515              
6516             sub ceil {
6517             my ($x) = @_;
6518             Math::GMPq::Rmpq_integer_p($$x) && return $x->copy;
6519              
6520             if (Math::GMPq::Rmpq_sgn($$x) > 0) {
6521             my $z = Math::GMPz::Rmpz_init();
6522             Math::GMPz::Rmpz_set_q($z, $$x);
6523             Math::GMPz::Rmpz_add_ui($z, $z, 1);
6524             _mpz2big($z);
6525             }
6526             else {
6527             my $z = Math::GMPz::Rmpz_init();
6528             Math::GMPz::Rmpz_set_q($z, $$x);
6529             _mpz2big($z);
6530             }
6531             }
6532              
6533             =head2 int
6534              
6535             $x->int # => BigNum
6536             int($x) # => BigNum
6537              
6538             Returns a truncated integer from the value of C.
6539              
6540             Example:
6541              
6542             int( 2.5) = 2
6543             int(-2.5) = -2
6544              
6545             =cut
6546              
6547             sub int {
6548             my $q = ${$_[0]};
6549             Math::GMPq::Rmpq_integer_p($q) && return $_[0]->copy;
6550             my $z = Math::GMPz::Rmpz_init();
6551             Math::GMPz::Rmpz_set_q($z, $q);
6552             _mpz2big($z);
6553             }
6554              
6555             =head2 bint
6556              
6557             $x->bint # => BigNum
6558              
6559             Truncates C to an integer in-place.
6560              
6561             =cut
6562              
6563             sub bint {
6564             my $q = ${$_[0]};
6565             Math::GMPq::Rmpq_integer_p($q) && return $_[0];
6566             my $z = Math::GMPz::Rmpz_init();
6567             Math::GMPz::Rmpz_set_q($z, $q);
6568             Math::GMPq::Rmpq_set_z($q, $z);
6569             $_[0];
6570             }
6571              
6572             =head2 float
6573              
6574             $x->float # => BigNum
6575             $x->float(Scalar) # => BigNum
6576              
6577             Returns a truncated number that fits inside number of bits specified
6578             as an argument. When no argument is specified or when the argument is
6579             undefined, the value of C<$Math::BigNum::PREC> will be used instead.
6580              
6581             =cut
6582              
6583             sub float {
6584             my ($x, $prec) = @_;
6585             my $f = Math::MPFR::Rmpfr_init2(CORE::int($prec // $PREC));
6586             Math::MPFR::Rmpfr_set_q($f, $$x, $ROUND);
6587             _mpfr2big($f);
6588             }
6589              
6590             =head2 bfloat
6591              
6592             $x->bfloat # => BigNum
6593             $x->bfloat(Scalar) # => BigNum
6594              
6595             Same as the method C, except that C is truncated in-place.
6596              
6597             =cut
6598              
6599             sub bfloat {
6600             my ($x, $prec) = @_;
6601             my $f = Math::MPFR::Rmpfr_init2(CORE::int($prec // $PREC));
6602             Math::MPFR::Rmpfr_set_q($f, $$x, $ROUND);
6603             Math::MPFR::Rmpfr_get_q($$x, $f);
6604             $x;
6605             }
6606              
6607             =head2 round
6608              
6609             $x->round(BigNum) # => BigNum
6610             $x->round(Scalar) # => BigNum
6611              
6612             Rounds C to the nth place. A negative argument rounds that many digits
6613             after the decimal point, while a positive argument rounds before the decimal
6614             point. This method uses the "round half to even" algorithm, which is the
6615             default rounding mode used in IEEE 754 computing functions and operators.
6616              
6617             =cut
6618              
6619             Class::Multimethods::multimethod round => qw(Math::BigNum $) => sub {
6620             $_[0]->copy->bround($_[1]);
6621             };
6622              
6623             Class::Multimethods::multimethod round => qw(Math::BigNum Math::BigNum) => sub {
6624             $_[0]->copy->bround(Math::GMPq::Rmpq_get_d(${$_[1]}));
6625             };
6626              
6627             =head2 bround
6628              
6629             $x->bround(BigNum) # => BigNum
6630             $x->bround(Scalar) # => BigNum
6631              
6632             Rounds C in-place to nth places.
6633              
6634             =cut
6635              
6636             Class::Multimethods::multimethod bround => qw(Math::BigNum $) => sub {
6637             my ($x, $prec) = @_;
6638              
6639             my $n = $$x;
6640             my $nth = -CORE::int($prec);
6641             my $sgn = Math::GMPq::Rmpq_sgn($n);
6642              
6643             Math::GMPq::Rmpq_abs($n, $n) if $sgn < 0;
6644              
6645             my $p = Math::GMPq::Rmpq_init();
6646             Math::GMPq::Rmpq_set_str($p, '1' . ('0' x CORE::abs($nth)), 10);
6647              
6648             if ($nth < 0) {
6649             Math::GMPq::Rmpq_div($n, $n, $p);
6650             }
6651             else {
6652             Math::GMPq::Rmpq_mul($n, $n, $p);
6653             }
6654              
6655             state $half = do {
6656             my $q = Math::GMPq::Rmpq_init_nobless();
6657             Math::GMPq::Rmpq_set_ui($q, 1, 2);
6658             $q;
6659             };
6660              
6661             Math::GMPq::Rmpq_add($n, $n, $half);
6662              
6663             my $z = Math::GMPz::Rmpz_init();
6664             Math::GMPz::Rmpz_set_q($z, $n);
6665              
6666             if (Math::GMPz::Rmpz_odd_p($z) and Math::GMPq::Rmpq_integer_p($n)) {
6667             Math::GMPz::Rmpz_sub_ui($z, $z, 1);
6668             }
6669              
6670             Math::GMPq::Rmpq_set_z($n, $z);
6671              
6672             if ($nth < 0) {
6673             Math::GMPq::Rmpq_mul($n, $n, $p);
6674             }
6675             else {
6676             Math::GMPq::Rmpq_div($n, $n, $p);
6677             }
6678              
6679             if ($sgn < 0) {
6680             Math::GMPq::Rmpq_neg($n, $n);
6681             }
6682              
6683             $x;
6684             };
6685              
6686             Class::Multimethods::multimethod bround => qw(Math::BigNum Math::BigNum) => sub {
6687             $_[0]->bround(Math::GMPq::Rmpq_get_d(${$_[1]}));
6688             };
6689              
6690             =head2 neg
6691              
6692             $x->neg # => BigNum
6693             -$x # => BigNum
6694              
6695             Negative value of C.
6696              
6697             =cut
6698              
6699             sub neg {
6700             my ($x) = @_;
6701             my $r = Math::GMPq::Rmpq_init();
6702             Math::GMPq::Rmpq_neg($r, $$x);
6703             bless \$r, __PACKAGE__;
6704             }
6705              
6706             =head2 bneg
6707              
6708             $x->bneg # => BigNum
6709              
6710             Negative value of C, changing C in-place.
6711              
6712             =cut
6713              
6714             sub bneg {
6715             Math::GMPq::Rmpq_neg(${$_[0]}, ${$_[0]});
6716             $_[0];
6717             }
6718              
6719             =head2 abs
6720              
6721             $x->abs # => BigNum
6722             abs($x) # => BigNum
6723              
6724             Absolute value of C.
6725              
6726             Example:
6727              
6728             abs(-42) = 42
6729             abs( 42) = 42
6730              
6731             =cut
6732              
6733             sub abs {
6734             my ($x) = @_;
6735             my $r = Math::GMPq::Rmpq_init();
6736             Math::GMPq::Rmpq_abs($r, $$x);
6737             bless \$r, __PACKAGE__;
6738             }
6739              
6740             =head2 babs
6741              
6742             $x->babs # => BigNum
6743              
6744             Absolute value of C, changing C in-place.
6745              
6746             =cut
6747              
6748             sub babs {
6749             Math::GMPq::Rmpq_abs(${$_[0]}, ${$_[0]});
6750             $_[0];
6751             }
6752              
6753             =head2 inc
6754              
6755             $x->inc # => BigNum
6756              
6757             Returns C.
6758              
6759             =cut
6760              
6761             sub inc {
6762             my ($x) = @_;
6763             my $r = Math::GMPq::Rmpq_init();
6764             Math::GMPq::Rmpq_add($r, $$x, $ONE);
6765             bless \$r, __PACKAGE__;
6766             }
6767              
6768             =head2 binc
6769              
6770             $x->binc # => BigNum
6771             ++$x # => BigNum
6772             $x++ # => BigNum
6773              
6774             Increments C in-place by 1.
6775              
6776             =cut
6777              
6778             sub binc {
6779             my ($x) = @_;
6780             Math::GMPq::Rmpq_add($$x, $$x, $ONE);
6781             $x;
6782             }
6783              
6784             =head2 dec
6785              
6786             $x->dec # => BigNum
6787              
6788             Returns C.
6789              
6790             =cut
6791              
6792             sub dec {
6793             my ($x) = @_;
6794             my $r = Math::GMPq::Rmpq_init();
6795             Math::GMPq::Rmpq_sub($r, $$x, $ONE);
6796             bless \$r, __PACKAGE__;
6797             }
6798              
6799             =head2 bdec
6800              
6801             $x->bdec # => BigNum
6802             --$x # => BigNum
6803             $x-- # => BigNum
6804              
6805             Decrements C in-place by 1.
6806              
6807             =cut
6808              
6809             sub bdec {
6810             my ($x) = @_;
6811             Math::GMPq::Rmpq_sub($$x, $$x, $ONE);
6812             $x;
6813             }
6814              
6815             =head1 * Introspection
6816              
6817             =cut
6818              
6819             =head2 is_zero
6820              
6821             $x->is_zero # => Bool
6822              
6823             Returns a true value when C is 0.
6824              
6825             =cut
6826              
6827             sub is_zero {
6828             !Math::GMPq::Rmpq_sgn(${$_[0]});
6829             }
6830              
6831             =head2 is_one
6832              
6833             $x->is_one # => Bool
6834              
6835             Returns a true value when C is +1.
6836              
6837             =cut
6838              
6839             sub is_one {
6840             Math::GMPq::Rmpq_equal(${$_[0]}, $ONE);
6841             }
6842              
6843             =head2 is_mone
6844              
6845             $x->is_mone # => Bool
6846              
6847             Returns a true value when C is -1.
6848              
6849             =cut
6850              
6851             sub is_mone {
6852             Math::GMPq::Rmpq_equal(${$_[0]}, $MONE);
6853             }
6854              
6855             =head2 is_pos
6856              
6857             $x->is_pos # => Bool
6858              
6859             Returns a true value when C is greater than zero.
6860              
6861             =cut
6862              
6863             sub is_pos {
6864             Math::GMPq::Rmpq_sgn(${$_[0]}) > 0;
6865             }
6866              
6867             =head2 is_neg
6868              
6869             $x->is_neg # => Bool
6870              
6871             Returns a true value when C is less than zero.
6872              
6873             =cut
6874              
6875             sub is_neg {
6876             Math::GMPq::Rmpq_sgn(${$_[0]}) < 0;
6877             }
6878              
6879             =head2 is_int
6880              
6881             $x->is_int # => Bool
6882              
6883             Returns a true value when C is an integer.
6884              
6885             =cut
6886              
6887             sub is_int {
6888             Math::GMPq::Rmpq_integer_p(${$_[0]});
6889             }
6890              
6891             =head2 is_real
6892              
6893             $x->is_real # => Bool
6894              
6895             Always returns a true value when invoked on a Math::BigNum object.
6896              
6897             =cut
6898              
6899             sub is_real { 1 }
6900              
6901             =head2 is_inf
6902              
6903             $x->is_inf # => Bool
6904              
6905             Always returns a false value when invoked on a Math::BigNum object.
6906              
6907             =cut
6908              
6909             sub is_inf { 0 }
6910              
6911             =head2 is_nan
6912              
6913             $x->is_nan # => Bool
6914              
6915             Always returns a false value when invoked on a Math::BigNum object.
6916              
6917             =cut
6918              
6919             sub is_nan { 0 }
6920              
6921             =head2 is_ninf
6922              
6923             $x->is_ninf # => Bool
6924              
6925             Always returns a false value when invoked on a Math::BigNum object.
6926              
6927             =cut
6928              
6929             sub is_ninf { 0 }
6930              
6931             =head2 is_odd
6932              
6933             $x->is_odd # => Bool
6934              
6935             Returns a true value when C is NOT divisible by 2. Returns C<0> if C is NOT an integer.
6936              
6937             =cut
6938              
6939             sub is_odd {
6940             my ($x) = @_;
6941             Math::GMPq::Rmpq_integer_p($$x) || return 0;
6942             my $nz = Math::GMPz::Rmpz_init();
6943             Math::GMPq::Rmpq_numref($nz, $$x);
6944             Math::GMPz::Rmpz_odd_p($nz);
6945             }
6946              
6947             =head2 is_even
6948              
6949             $x->is_even # => Bool
6950              
6951             Returns a true value when C is divisible by 2. Returns C<0> if C is NOT an integer.
6952              
6953             =cut
6954              
6955             sub is_even {
6956             my ($x) = @_;
6957             Math::GMPq::Rmpq_integer_p($$x) || return 0;
6958             my $nz = Math::GMPz::Rmpz_init();
6959             Math::GMPq::Rmpq_numref($nz, $$x);
6960             Math::GMPz::Rmpz_even_p($nz);
6961             }
6962              
6963             =head2 is_div
6964              
6965             $x->is_div(BigNum) # => Bool
6966             $x->is_div(Scalar) # => Bool
6967              
6968             Returns a true value if C is divisible by C (i.e. when the
6969             result of division of C by C is an integer). False otherwise.
6970              
6971             Example:
6972              
6973             is_div(15, 3) = true
6974             is_div(15, 4) = false
6975              
6976             It is also defined for rational numbers, returning a true value when the quotient of division is an integer:
6977              
6978             is_div(17, 3.4) = true # because: 17/3.4 = 5
6979              
6980             This method is very efficient when the first argument is an integer and the second argument is a I integer.
6981              
6982             =cut
6983              
6984             Class::Multimethods::multimethod is_div => qw(Math::BigNum Math::BigNum) => sub {
6985             my ($x, $y) = @_;
6986              
6987             Math::GMPq::Rmpq_sgn($$y) || return 0;
6988              
6989             #<<<
6990             #---------------------------------------------------------------------------------
6991             ## Optimization for integers, but it turned out to be slower for small integers...
6992             #---------------------------------------------------------------------------------
6993             #~ if (Math::GMPq::Rmpq_integer_p($$y) and Math::GMPq::Rmpq_integer_p($$x)) {
6994             #~ my $d = CORE::int(CORE::abs(Math::GMPq::Rmpq_get_d($$y)));
6995             #~ if ($d <= MAX_UI) {
6996             #~ Math::GMPz::Rmpz_set_q((my $z = Math::GMPz::Rmpz_init()), $$x);
6997             #~ return Math::GMPz::Rmpz_divisible_ui_p($z, $d);
6998             #~ }
6999             #~ else {
7000             #~ return Math::GMPz::Rmpz_divisible_p(_int2mpz($x), _int2mpz($y));
7001             #~ }
7002             #~ }
7003             #>>>
7004              
7005             my $q = Math::GMPq::Rmpq_init();
7006             Math::GMPq::Rmpq_div($q, $$x, $$y);
7007             Math::GMPq::Rmpq_integer_p($q);
7008             };
7009              
7010             Class::Multimethods::multimethod is_div => qw(Math::BigNum $) => sub {
7011             my ($x, $y) = @_;
7012              
7013             $y || return 0;
7014              
7015             # Use a faster method when both $x and $y are integers
7016             if (CORE::int($y) eq $y and CORE::abs($y) <= MAX_UI and Math::GMPq::Rmpq_integer_p($$x)) {
7017             Math::GMPz::Rmpz_divisible_ui_p(_int2mpz($x), CORE::abs($y));
7018             }
7019              
7020             # Otherwise, do the division and check the result
7021             else {
7022             my $q = _str2mpq($y) // return $x->is_div(Math::BigNum->new($y));
7023             Math::GMPq::Rmpq_div($q, $$x, $q);
7024             Math::GMPq::Rmpq_integer_p($q);
7025             }
7026             };
7027              
7028             Class::Multimethods::multimethod is_div => qw(Math::BigNum *) => sub {
7029             $_[0]->is_div(Math::BigNum->new($_[1]));
7030             };
7031              
7032             Class::Multimethods::multimethod is_div => qw(Math::BigNum Math::BigNum::Inf) => sub { 0 };
7033             Class::Multimethods::multimethod is_div => qw(Math::BigNum Math::BigNum::Nan) => sub { 0 };
7034              
7035             =head2 sign
7036              
7037             $x->sign # => Scalar
7038              
7039             Returns C<-1> when C is negative, C<1> when C is positive, and C<0> when C is zero.
7040              
7041             =cut
7042              
7043             sub sign {
7044             Math::GMPq::Rmpq_sgn(${$_[0]});
7045             }
7046              
7047             =head2 length
7048              
7049             $x->length # => Scalar
7050              
7051             Returns the number of digits of C in base 10 before the decimal point.
7052              
7053             For C, it returns C<4>.
7054              
7055             =cut
7056              
7057             sub length {
7058             my $z = Math::GMPz::Rmpz_init();
7059             Math::GMPz::Rmpz_set_q($z, ${$_[0]});
7060             Math::GMPz::Rmpz_abs($z, $z);
7061             Math::GMPz::Rmpz_snprintf(my $buf, 0, "%Zd", $z, 0);
7062             }
7063              
7064             =head1 * Conversions
7065              
7066             =cut
7067              
7068             =head2 stringify
7069              
7070             $x->stringify # => Scalar
7071              
7072             Returns a string representing the value of C, either as a base-10 integer,
7073             or a decimal expansion.
7074              
7075             Example:
7076              
7077             stringify(1/2) = "0.5"
7078             stringify(100) = "100"
7079              
7080             =cut
7081              
7082             sub stringify {
7083             my $x = ${$_[0]};
7084             Math::GMPq::Rmpq_integer_p($x)
7085             ? Math::GMPq::Rmpq_get_str($x, 10)
7086             : do {
7087             $PREC = CORE::int($PREC) if ref($PREC);
7088              
7089             my $prec = CORE::int($PREC / 4);
7090             my $sgn = Math::GMPq::Rmpq_sgn($x);
7091              
7092             my $n = Math::GMPq::Rmpq_init();
7093             Math::GMPq::Rmpq_set($n, $x);
7094             Math::GMPq::Rmpq_abs($n, $n) if $sgn < 0;
7095              
7096             my $p = Math::GMPq::Rmpq_init();
7097             Math::GMPq::Rmpq_set_str($p, '1' . ('0' x CORE::abs($prec)), 10);
7098              
7099             if ($prec < 0) {
7100             Math::GMPq::Rmpq_div($n, $n, $p);
7101             }
7102             else {
7103             Math::GMPq::Rmpq_mul($n, $n, $p);
7104             }
7105              
7106             state $half = do {
7107             my $q = Math::GMPq::Rmpq_init_nobless();
7108             Math::GMPq::Rmpq_set_ui($q, 1, 2);
7109             $q;
7110             };
7111              
7112             my $z = Math::GMPz::Rmpz_init();
7113             Math::GMPq::Rmpq_add($n, $n, $half);
7114             Math::GMPz::Rmpz_set_q($z, $n);
7115              
7116             # Too much rounding... Give up and return an MPFR stringified number.
7117             !Math::GMPz::Rmpz_sgn($z) && $PREC >= 2 && do {
7118             my $mpfr = Math::MPFR::Rmpfr_init2($PREC);
7119             Math::MPFR::Rmpfr_set_q($mpfr, $x, $ROUND);
7120             return Math::MPFR::Rmpfr_get_str($mpfr, 10, $prec, $ROUND);
7121             };
7122              
7123             if (Math::GMPz::Rmpz_odd_p($z) and Math::GMPq::Rmpq_integer_p($n)) {
7124             Math::GMPz::Rmpz_sub_ui($z, $z, 1);
7125             }
7126              
7127             Math::GMPq::Rmpq_set_z($n, $z);
7128              
7129             if ($prec < 0) {
7130             Math::GMPq::Rmpq_mul($n, $n, $p);
7131             }
7132             else {
7133             Math::GMPq::Rmpq_div($n, $n, $p);
7134             }
7135              
7136             my $num = Math::GMPz::Rmpz_init();
7137             my $den = Math::GMPz::Rmpz_init();
7138              
7139             Math::GMPq::Rmpq_numref($num, $n);
7140             Math::GMPq::Rmpq_denref($den, $n);
7141              
7142             my @r;
7143             while (1) {
7144             Math::GMPz::Rmpz_div($z, $num, $den);
7145             push @r, Math::GMPz::Rmpz_get_str($z, 10);
7146              
7147             Math::GMPz::Rmpz_mul($z, $z, $den);
7148             Math::GMPz::Rmpz_sub($num, $num, $z);
7149             last if !Math::GMPz::Rmpz_sgn($num);
7150              
7151             my $s = -1;
7152             while (Math::GMPz::Rmpz_cmp($den, $num) > 0) {
7153             Math::GMPz::Rmpz_mul_ui($num, $num, 10);
7154             ++$s;
7155             }
7156              
7157             push(@r, '0' x $s) if ($s > 0);
7158             }
7159              
7160             ($sgn < 0 ? "-" : '') . shift(@r) . (('.' . join('', @r)) =~ s/0+\z//r =~ s/\.\z//r);
7161             }
7162             }
7163              
7164             =head2 numify
7165              
7166             $x->numify # => Scalar
7167              
7168             Returns a Perl numerical scalar with the value of C, truncated if needed.
7169              
7170             =cut
7171              
7172             sub numify {
7173             Math::GMPq::Rmpq_get_d(${$_[0]});
7174             }
7175              
7176             =head2 boolify
7177              
7178             $x->boolify # => Bool
7179              
7180             Returns a true value when the number is not zero. False otherwise.
7181              
7182             =cut
7183              
7184             sub boolify {
7185             !!Math::GMPq::Rmpq_sgn(${$_[0]});
7186             }
7187              
7188             =head2 as_frac
7189              
7190             $x->as_frac # => Scalar
7191              
7192             Returns a string representing the number as a base-10 fraction.
7193              
7194             Example:
7195              
7196             as_frac(3.5) = "7/2"
7197             as_frac(3.0) = "3/1"
7198              
7199             =cut
7200              
7201             sub as_frac {
7202             my $rat = Math::GMPq::Rmpq_get_str(${$_[0]}, 10);
7203             index($rat, '/') == -1 ? "$rat/1" : $rat;
7204             }
7205              
7206             =head2 as_rat
7207              
7208             $x->as_rat # => Scalar
7209              
7210             Almost the same as C, except that integers are returned as they are,
7211             without adding a denominator of 1.
7212              
7213             Example:
7214              
7215             as_rat(3.5) = "7/2"
7216             as_rat(3.0) = "3"
7217              
7218             =cut
7219              
7220             sub as_rat {
7221             Math::GMPq::Rmpq_get_str(${$_[0]}, 10);
7222             }
7223              
7224             =head2 as_float
7225              
7226             $x->as_float # => Scalar
7227             $x->as_float(Scalar) # => Scalar
7228             $x->as_float(BigNum) # => Scalar
7229              
7230             Returns the self-number as a floating-point scalar. The method also accepts
7231             an optional argument for precision after the decimal point. When no argument
7232             is provided, it uses the default precision.
7233              
7234             Example:
7235              
7236             as_float(1/3, 4) = "0.3333"
7237              
7238             If the self number is an integer, it will be returned as it is.
7239              
7240             =cut
7241              
7242             Class::Multimethods::multimethod as_float => qw(Math::BigNum) => sub {
7243             $_[0]->stringify;
7244             };
7245              
7246             Class::Multimethods::multimethod as_float => qw(Math::BigNum $) => sub {
7247             local $Math::BigNum::PREC = 4 * $_[1];
7248             $_[0]->stringify;
7249             };
7250              
7251             Class::Multimethods::multimethod as_float => qw(Math::BigNum Math::BigNum) => sub {
7252             local $Math::BigNum::PREC = 4 * Math::GMPq::Rmpq_get_d(${$_[1]});
7253             $_[0]->stringify;
7254             };
7255              
7256             =head2 as_int
7257              
7258             $x->as_int # => Scalar
7259             $x->as_int(Scalar) # => Scalar
7260             $x->as_int(BigNum) # => Scalar
7261              
7262             Returns the self-number as an integer in a given base. When the base is omitted, it
7263             defaults to 10.
7264              
7265             Example:
7266              
7267             as_int(255) = "255"
7268             as_int(255, 16) = "ff"
7269              
7270             =cut
7271              
7272             Class::Multimethods::multimethod as_int => qw(Math::BigNum) => sub {
7273             my $z = Math::GMPz::Rmpz_init();
7274             Math::GMPz::Rmpz_set_q($z, ${$_[0]});
7275             Math::GMPz::Rmpz_get_str($z, 10);
7276             };
7277              
7278             Class::Multimethods::multimethod as_int => qw(Math::BigNum $) => sub {
7279             my $z = Math::GMPz::Rmpz_init();
7280             Math::GMPz::Rmpz_set_q($z, ${$_[0]});
7281              
7282             my $base = CORE::int($_[1]);
7283             if ($base < 2 or $base > 36) {
7284             require Carp;
7285             Carp::croak("base must be between 2 and 36, got $base");
7286             }
7287              
7288             Math::GMPz::Rmpz_get_str($z, $base);
7289             };
7290              
7291             Class::Multimethods::multimethod as_int => qw(Math::BigNum Math::BigNum) => sub {
7292             $_[0]->as_int(Math::GMPq::Rmpq_get_d(${$_[1]}));
7293             };
7294              
7295             =head2 as_bin
7296              
7297             $x->as_bin # => Scalar
7298              
7299             Returns a string representing the value of C in binary.
7300              
7301             Example:
7302              
7303             as_bin(42) = "101010"
7304              
7305             =cut
7306              
7307             sub as_bin {
7308             my $z = Math::GMPz::Rmpz_init();
7309             Math::GMPz::Rmpz_set_q($z, ${$_[0]});
7310             Math::GMPz::Rmpz_get_str($z, 2);
7311             }
7312              
7313             =head2 as_oct
7314              
7315             $x->as_oct # => Scalar
7316              
7317             Returns a string representing the value of C in octal.
7318              
7319             Example:
7320              
7321             as_oct(42) = "52"
7322              
7323             =cut
7324              
7325             sub as_oct {
7326             my $z = Math::GMPz::Rmpz_init();
7327             Math::GMPz::Rmpz_set_q($z, ${$_[0]});
7328             Math::GMPz::Rmpz_get_str($z, 8);
7329             }
7330              
7331             =head2 as_hex
7332              
7333             $x->as_hex # => Scalar
7334              
7335             Returns a string representing the value of C in hexadecimal.
7336              
7337             Example:
7338              
7339             as_hex(42) = "2a"
7340              
7341             =cut
7342              
7343             sub as_hex {
7344             my $z = Math::GMPz::Rmpz_init();
7345             Math::GMPz::Rmpz_set_q($z, ${$_[0]});
7346             Math::GMPz::Rmpz_get_str($z, 16);
7347             }
7348              
7349             =head2 in_base
7350              
7351             $x->in_base(Scalar) # => Scalar
7352              
7353             Returns a string with the value of C in a given base,
7354             where the base can range from 2 to 36 inclusive. If C
7355             is not an integer, the result is returned in rationalized
7356             form.
7357              
7358             Example:
7359              
7360             in_base(42, 3) = "1120"
7361             in_base(12.34, 36) = "h5/1e"
7362              
7363             =cut
7364              
7365             Class::Multimethods::multimethod in_base => qw(Math::BigNum $) => sub {
7366             my ($x, $y) = @_;
7367              
7368             if ($y < 2 or $y > 36) {
7369             require Carp;
7370             Carp::croak("base must be between 2 and 36, got $y");
7371             }
7372              
7373             Math::GMPq::Rmpq_get_str($$x, $y);
7374             };
7375              
7376             Class::Multimethods::multimethod in_base => qw(Math::BigNum Math::BigNum) => sub {
7377             $_[0]->in_base(CORE::int(Math::GMPq::Rmpq_get_d(${$_[1]})));
7378             };
7379              
7380             =head2 deg2rad
7381              
7382             $x->deg2rad # => BigNum
7383              
7384             Returns the value of C converted from degrees to radians.
7385              
7386             Example:
7387              
7388             deg2rad(180) = pi
7389              
7390             =cut
7391              
7392             sub deg2rad {
7393             Math::MPFR::Rmpfr_const_pi((my $pi = Math::MPFR::Rmpfr_init2($PREC)), $ROUND);
7394             Math::MPFR::Rmpfr_div_ui((my $fr = Math::MPFR::Rmpfr_init2($PREC)), $pi, 180, $ROUND);
7395              
7396             ## Version 1
7397             #~ my $q = Math::GMPq::Rmpq_init();
7398             #~ Math::MPFR::Rmpfr_get_q($q, $fr);
7399             #~ Math::GMPq::Rmpq_mul($q, $q, ${$_[0]});
7400             #~ bless \$q, __PACKAGE__;
7401              
7402             ## Version 2
7403             Math::MPFR::Rmpfr_mul_q($fr, $fr, ${$_[0]}, $ROUND);
7404             _mpfr2big($fr);
7405             }
7406              
7407             =head2 rad2deg
7408              
7409             $x->rad2deg # => BigNum
7410              
7411             Returns the value of C converted from radians to degrees.
7412              
7413             Example:
7414              
7415             rad2deg(pi) = 180
7416              
7417             =cut
7418              
7419             sub rad2deg {
7420             Math::MPFR::Rmpfr_const_pi((my $pi = Math::MPFR::Rmpfr_init2($PREC)), $ROUND);
7421             Math::MPFR::Rmpfr_ui_div((my $fr = Math::MPFR::Rmpfr_init2($PREC)), 180, $pi, $ROUND);
7422              
7423             ## Version 1
7424             #~ my $q = Math::GMPq::Rmpq_init();
7425             #~ Math::MPFR::Rmpfr_get_q($q, $fr);
7426             #~ Math::GMPq::Rmpq_mul($q, $q, ${$_[0]});
7427             #~ bless \$q, __PACKAGE__;
7428              
7429             ## Version 2
7430             Math::MPFR::Rmpfr_mul_q($fr, $fr, ${$_[0]}, $ROUND);
7431             _mpfr2big($fr);
7432             }
7433              
7434             =head1 * Dissections
7435              
7436             =cut
7437              
7438             =head2 digits
7439              
7440             $x->digits # => (Scalar, Scalar, ...)
7441             $x->digits(Scalar) # => (Scalar, Scalar, ...)
7442              
7443             Returns a list with the digits of C in a given base. When no base is specified, it defaults to base 10.
7444              
7445             Only the absolute integer part of C is considered.
7446              
7447             Example:
7448              
7449             digits(-1234.56) = (1,2,3,4)
7450             digits(4095, 16) = ('f','f','f')
7451              
7452             =cut
7453              
7454             Class::Multimethods::multimethod digits => qw(Math::BigNum) => sub {
7455             my $z = Math::GMPz::Rmpz_init();
7456             Math::GMPz::Rmpz_set_q($z, ${$_[0]});
7457             Math::GMPz::Rmpz_abs($z, $z);
7458             split(//, Math::GMPz::Rmpz_get_str($z, 10));
7459             };
7460              
7461             Class::Multimethods::multimethod digits => qw(Math::BigNum $) => sub {
7462             my ($x, $y) = @_;
7463              
7464             if ($y < 2 or $y > 36) {
7465             require Carp;
7466             Carp::croak("base must be between 2 and 36, got $y");
7467             }
7468              
7469             my $z = Math::GMPz::Rmpz_init();
7470             Math::GMPz::Rmpz_set_q($z, $$x);
7471             Math::GMPz::Rmpz_abs($z, $z);
7472             split(//, Math::GMPz::Rmpz_get_str($z, $y));
7473             };
7474              
7475             Class::Multimethods::multimethod digits => qw(Math::BigNum Math::BigNum) => sub {
7476             $_[0]->digits(CORE::int(Math::GMPq::Rmpq_get_d(${$_[1]})));
7477             };
7478              
7479             =head2 numerator
7480              
7481             $x->numerator # => BigNum
7482              
7483             Returns a copy of the numerator as signed BigNum.
7484              
7485             =cut
7486              
7487             sub numerator {
7488             my ($x) = @_;
7489             my $z = Math::GMPz::Rmpz_init();
7490             Math::GMPq::Rmpq_numref($z, $$x);
7491             _mpz2big($z);
7492             }
7493              
7494             =head2 denominator
7495              
7496             $x->denominator # => BigNum
7497              
7498             Returns a copy of the denominator as positive BigNum.
7499              
7500             =cut
7501              
7502             sub denominator {
7503             my ($x) = @_;
7504             my $z = Math::GMPz::Rmpz_init();
7505             Math::GMPq::Rmpq_denref($z, $$x);
7506             _mpz2big($z);
7507             }
7508              
7509             =head2 parts
7510              
7511             $x->parts # => (BigNum, BigNum)
7512              
7513             Returns a copy of the numerator (signed) and a copy of the denominator (unsigned) as BigNum objects.
7514              
7515             Example:
7516              
7517             parts(-0.75) = (-3, 4)
7518              
7519             =cut
7520              
7521             sub parts {
7522             my ($x) = @_;
7523             my $num_z = Math::GMPz::Rmpz_init();
7524             my $den_z = Math::GMPz::Rmpz_init();
7525             Math::GMPq::Rmpq_numref($num_z, $$x);
7526             Math::GMPq::Rmpq_denref($den_z, $$x);
7527             (_mpz2big($num_z), _mpz2big($den_z));
7528             }
7529              
7530             =head1 * Comparisons
7531              
7532             =cut
7533              
7534             =head2 eq
7535              
7536             $x->eq(BigNum) # => Bool
7537             $x->eq(Scalar) # => Bool
7538              
7539             $x == $y # => Bool
7540              
7541             Equality check: returns a true value when C and C are equal.
7542              
7543             =cut
7544              
7545             Class::Multimethods::multimethod eq => qw(Math::BigNum Math::BigNum) => sub {
7546             Math::GMPq::Rmpq_equal(${$_[0]}, ${$_[1]});
7547             };
7548              
7549             Class::Multimethods::multimethod eq => qw(Math::BigNum $) => sub {
7550             Math::GMPq::Rmpq_equal(${$_[0]}, _str2mpq($_[1]) // return $_[0]->eq(Math::BigNum->new($_[1])));
7551             };
7552              
7553             =for comment
7554             Class::Multimethods::multimethod eq => qw(Math::BigNum Math::BigNum::Complex) => sub {
7555             my ($x, $y) = @_;
7556             $y->im->is_zero && Math::GMPq::Rmpq_equal($$x, ${$y->re});
7557             };
7558             =cut
7559              
7560             Class::Multimethods::multimethod eq => qw(Math::BigNum *) => sub {
7561             $_[0]->eq(Math::BigNum->new($_[1]));
7562             };
7563              
7564             Class::Multimethods::multimethod eq => qw(Math::BigNum Math::BigNum::Inf) => sub { 0 };
7565             Class::Multimethods::multimethod eq => qw(Math::BigNum Math::BigNum::Nan) => sub { 0 };
7566              
7567             =head2 ne
7568              
7569             $x->ne(BigNum) # => Bool
7570             $x->ne(Scalar) # => Bool
7571              
7572             $x != $y # => Bool
7573              
7574             Inequality check: returns a true value when C and C are not equal.
7575              
7576             =cut
7577              
7578             Class::Multimethods::multimethod ne => qw(Math::BigNum Math::BigNum) => sub {
7579             !Math::GMPq::Rmpq_equal(${$_[0]}, ${$_[1]});
7580             };
7581              
7582             Class::Multimethods::multimethod ne => qw(Math::BigNum $) => sub {
7583             !Math::GMPq::Rmpq_equal(${$_[0]}, _str2mpq($_[1]) // return $_[0]->ne(Math::BigNum->new($_[1])));
7584             };
7585              
7586             =for comment
7587             Class::Multimethods::multimethod ne => qw(Math::BigNum Math::BigNum::Complex) => sub {
7588             my ($x, $y) = @_;
7589             !($y->im->is_zero && Math::GMPq::Rmpq_equal($$x, ${$y->re}));
7590             };
7591             =cut
7592              
7593             Class::Multimethods::multimethod ne => qw(Math::BigNum *) => sub {
7594             $_[0]->ne(Math::BigNum->new($_[1]));
7595             };
7596              
7597             Class::Multimethods::multimethod ne => qw(Math::BigNum Math::BigNum::Inf) => sub { 1 };
7598             Class::Multimethods::multimethod ne => qw(Math::BigNum Math::BigNum::Nan) => sub { 1 };
7599              
7600             =head2 gt
7601              
7602             $x->gt(BigNum) # => Bool
7603             $x->gt(Scalar) # => Bool
7604              
7605             BigNum > BigNum # => Bool
7606             BigNum > Scalar # => Bool
7607             Scalar > BigNum # => Bool
7608              
7609             Returns a true value when C is greater than C.
7610              
7611             =cut
7612              
7613             Class::Multimethods::multimethod gt => qw(Math::BigNum Math::BigNum) => sub {
7614             Math::GMPq::Rmpq_cmp(${$_[0]}, ${$_[1]}) > 0;
7615             };
7616              
7617             Class::Multimethods::multimethod gt => qw(Math::BigNum $) => sub {
7618             $_[0]->cmp($_[1]) > 0;
7619             };
7620              
7621             Class::Multimethods::multimethod gt => qw($ Math::BigNum) => sub {
7622             $_[1]->cmp($_[0]) < 0;
7623             };
7624              
7625             =for comment
7626             Class::Multimethods::multimethod gt => qw(Math::BigNum Math::BigNum::Complex) => sub {
7627             $_[1]->lt($_[0]);
7628             };
7629             =cut
7630              
7631             Class::Multimethods::multimethod gt => qw(* Math::BigNum) => sub {
7632             Math::BigNum->new($_[0])->gt($_[1]);
7633             };
7634              
7635             Class::Multimethods::multimethod gt => qw(Math::BigNum *) => sub {
7636             $_[0]->gt(Math::BigNum->new($_[1]));
7637             };
7638              
7639             Class::Multimethods::multimethod gt => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->is_neg };
7640             Class::Multimethods::multimethod gt => qw(Math::BigNum Math::BigNum::Nan) => sub { 0 };
7641              
7642             =head2 ge
7643              
7644             $x->ge(BigNum) # => Bool
7645             $x->ge(Scalar) # => Bool
7646              
7647             BigNum >= BigNum # => Bool
7648             BigNum >= Scalar # => Bool
7649             Scalar >= BigNum # => Bool
7650              
7651             Returns a true value when C is equal or greater than C.
7652              
7653             =cut
7654              
7655             Class::Multimethods::multimethod ge => qw(Math::BigNum Math::BigNum) => sub {
7656             Math::GMPq::Rmpq_cmp(${$_[0]}, ${$_[1]}) >= 0;
7657             };
7658              
7659             Class::Multimethods::multimethod ge => qw(Math::BigNum $) => sub {
7660             $_[0]->cmp($_[1]) >= 0;
7661             };
7662              
7663             Class::Multimethods::multimethod ge => qw($ Math::BigNum) => sub {
7664             $_[1]->cmp($_[0]) <= 0;
7665             };
7666              
7667             =for comment
7668             Class::Multimethods::multimethod ge => qw(Math::BigNum Math::BigNum::Complex) => sub {
7669             $_[1]->le($_[0]);
7670             };
7671             =cut
7672              
7673             Class::Multimethods::multimethod ge => qw(* Math::BigNum) => sub {
7674             Math::BigNum->new($_[0])->ge($_[1]);
7675             };
7676              
7677             Class::Multimethods::multimethod ge => qw(Math::BigNum *) => sub {
7678             $_[0]->ge(Math::BigNum->new($_[1]));
7679             };
7680              
7681             Class::Multimethods::multimethod ge => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->is_neg };
7682             Class::Multimethods::multimethod ge => qw(Math::BigNum Math::BigNum::Nan) => sub { 0 };
7683              
7684             =head2 lt
7685              
7686             $x->lt(BigNum) # => Bool
7687             $x->lt(Scalar) # => Bool
7688              
7689             BigNum < BigNum # => Bool
7690             BigNum < Scalar # => Bool
7691             Scalar < BigNum # => Bool
7692              
7693             Returns a true value when C is less than C.
7694              
7695             =cut
7696              
7697             Class::Multimethods::multimethod lt => qw(Math::BigNum Math::BigNum) => sub {
7698             Math::GMPq::Rmpq_cmp(${$_[0]}, ${$_[1]}) < 0;
7699             };
7700              
7701             Class::Multimethods::multimethod lt => qw(Math::BigNum $) => sub {
7702             $_[0]->cmp($_[1]) < 0;
7703             };
7704              
7705             Class::Multimethods::multimethod lt => qw($ Math::BigNum) => sub {
7706             $_[1]->cmp($_[0]) > 0;
7707             };
7708              
7709             =for comment
7710             Class::Multimethods::multimethod lt => qw(Math::BigNum Math::BigNum::Complex) => sub {
7711             $_[1]->gt($_[0]);
7712             };
7713             =cut
7714              
7715             Class::Multimethods::multimethod lt => qw(* Math::BigNum) => sub {
7716             Math::BigNum->new($_[0])->lt($_[1]);
7717             };
7718              
7719             Class::Multimethods::multimethod lt => qw(Math::BigNum *) => sub {
7720             $_[0]->lt(Math::BigNum->new($_[1]));
7721             };
7722              
7723             Class::Multimethods::multimethod lt => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->is_pos };
7724             Class::Multimethods::multimethod lt => qw(Math::BigNum Math::BigNum::Nan) => sub { 0 };
7725              
7726             =head2 le
7727              
7728             $x->le(BigNum) # => Bool
7729             $x->le(Scalar) # => Bool
7730              
7731             BigNum <= BigNum # => Bool
7732             BigNum <= Scalar # => Bool
7733             Scalar <= BigNum # => Bool
7734              
7735             Returns a true value when C is equal or less than C.
7736              
7737             =cut
7738              
7739             Class::Multimethods::multimethod le => qw(Math::BigNum Math::BigNum) => sub {
7740             Math::GMPq::Rmpq_cmp(${$_[0]}, ${$_[1]}) <= 0;
7741             };
7742              
7743             Class::Multimethods::multimethod le => qw(Math::BigNum $) => sub {
7744             $_[0]->cmp($_[1]) <= 0;
7745             };
7746              
7747             Class::Multimethods::multimethod le => qw($ Math::BigNum) => sub {
7748             $_[1]->cmp($_[0]) >= 0;
7749             };
7750              
7751             =for comment
7752             Class::Multimethods::multimethod le => qw(Math::BigNum Math::BigNum::Complex) => sub {
7753             $_[1]->ge($_[0]);
7754             };
7755             =cut
7756              
7757             Class::Multimethods::multimethod le => qw(* Math::BigNum) => sub {
7758             Math::BigNum->new($_[0])->le($_[1]);
7759             };
7760              
7761             Class::Multimethods::multimethod le => qw(Math::BigNum *) => sub {
7762             $_[0]->le(Math::BigNum->new($_[1]));
7763             };
7764              
7765             Class::Multimethods::multimethod le => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->is_pos };
7766             Class::Multimethods::multimethod le => qw(Math::BigNum Math::BigNum::Nan) => sub { 0 };
7767              
7768             =head2 cmp
7769              
7770             $x->cmp(BigNum) # => Scalar
7771             $x->cmp(Scalar) # => Scalar
7772              
7773             BigNum <=> BigNum # => Scalar
7774             BigNum <=> Scalar # => Scalar
7775             Scalar <=> BigNum # => Scalar
7776              
7777             Compares C to C and returns a negative value when C is less than C,
7778             0 when C and C are equal, and a positive value when C is greater than C.
7779              
7780             =cut
7781              
7782             Class::Multimethods::multimethod cmp => qw(Math::BigNum Math::BigNum) => sub {
7783             Math::GMPq::Rmpq_cmp(${$_[0]}, ${$_[1]});
7784             };
7785              
7786             Class::Multimethods::multimethod cmp => qw(Math::BigNum $) => sub {
7787             my ($x, $y) = @_;
7788              
7789             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
7790             $y >= 0
7791             ? Math::GMPq::Rmpq_cmp_ui($$x, $y, 1)
7792             : Math::GMPq::Rmpq_cmp_si($$x, $y, 1);
7793             }
7794             else {
7795             Math::GMPq::Rmpq_cmp($$x, _str2mpq($y) // return $x->cmp(Math::BigNum->new($y)));
7796             }
7797             };
7798              
7799             Class::Multimethods::multimethod cmp => qw($ Math::BigNum) => sub {
7800             my ($x, $y) = @_;
7801              
7802             if (CORE::int($x) eq $x and $x >= MIN_SI and $x <= MAX_UI) {
7803             -(
7804             $x >= 0
7805             ? Math::GMPq::Rmpq_cmp_ui($$y, $x, 1)
7806             : Math::GMPq::Rmpq_cmp_si($$y, $x, 1)
7807             );
7808             }
7809             else {
7810             Math::GMPq::Rmpq_cmp(_str2mpq($x) // (return Math::BigNum->new($x)->cmp($y)), $$y);
7811             }
7812             };
7813              
7814             Class::Multimethods::multimethod cmp => qw(* Math::BigNum) => sub {
7815             Math::BigNum->new($_[0])->cmp($_[1]);
7816             };
7817              
7818             Class::Multimethods::multimethod cmp => qw(Math::BigNum *) => sub {
7819             $_[0]->cmp(Math::BigNum->new($_[1]));
7820             };
7821              
7822             Class::Multimethods::multimethod cmp => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->is_pos ? -1 : 1 };
7823             Class::Multimethods::multimethod cmp => qw(Math::BigNum Math::BigNum::Nan) => sub { };
7824              
7825             =head2 acmp
7826              
7827             $x->acmp(BigNum) # => Scalar
7828             cmp(Scalar, BigNum) # => Scalar
7829              
7830             Compares the absolute values of C and C. Returns a negative value
7831             when the absolute value of C is less than the absolute value of C,
7832             0 when the absolute value of C is equal to the absolute value of C,
7833             and a positive value when the absolute value of C is greater than the
7834             absolute value of C.
7835              
7836             =cut
7837              
7838             Class::Multimethods::multimethod acmp => qw(Math::BigNum Math::BigNum) => sub {
7839             my ($x, $y) = @_;
7840              
7841             my $xn = $$x;
7842             my $yn = $$y;
7843              
7844             if (Math::GMPq::Rmpq_sgn($xn) < 0) {
7845             my $r = Math::GMPq::Rmpq_init();
7846             Math::GMPq::Rmpq_abs($r, $xn);
7847             $xn = $r;
7848             }
7849              
7850             if (Math::GMPq::Rmpq_sgn($yn) < 0) {
7851             my $r = Math::GMPq::Rmpq_init();
7852             Math::GMPq::Rmpq_abs($r, $yn);
7853             $yn = $r;
7854             }
7855              
7856             Math::GMPq::Rmpq_cmp($xn, $yn);
7857             };
7858              
7859             Class::Multimethods::multimethod acmp => qw(Math::BigNum $) => sub {
7860             my ($x, $y) = @_;
7861              
7862             my $xn = $$x;
7863              
7864             if (Math::GMPq::Rmpq_sgn($xn) < 0) {
7865             my $r = Math::GMPq::Rmpq_init();
7866             Math::GMPq::Rmpq_abs($r, $xn);
7867             $xn = $r;
7868             }
7869              
7870             if (CORE::int($y) eq $y and $y >= MIN_SI and $y <= MAX_UI) {
7871             Math::GMPq::Rmpq_cmp_ui($xn, CORE::abs($y), 1);
7872             }
7873             else {
7874             my $q = _str2mpq($y) // return $x->acmp(Math::BigNum->new($y));
7875             Math::GMPq::Rmpq_abs($q, $q);
7876             Math::GMPq::Rmpq_cmp($xn, $q);
7877             }
7878             };
7879              
7880             Class::Multimethods::multimethod acmp => qw(Math::BigNum *) => sub {
7881             $_[0]->acmp(Math::BigNum->new($_[1]));
7882             };
7883              
7884             Class::Multimethods::multimethod acmp => qw(Math::BigNum Math::BigNum::Inf) => sub { -1 };
7885             Class::Multimethods::multimethod acmp => qw(Math::BigNum Math::BigNum::Nan) => sub { };
7886              
7887             =head2 min
7888              
7889             $x->min(BigNum) # => BigNum
7890              
7891             Returns C if C is lower than C. Returns C otherwise.
7892              
7893             =cut
7894              
7895             Class::Multimethods::multimethod min => qw(Math::BigNum Math::BigNum) => sub {
7896             my ($x, $y) = @_;
7897             Math::GMPq::Rmpq_cmp($$x, $$y) < 0 ? $x : $y;
7898             };
7899              
7900             Class::Multimethods::multimethod min => qw(Math::BigNum *) => sub {
7901             $_[0]->min(Math::BigNum->new($_[1]));
7902             };
7903              
7904             Class::Multimethods::multimethod min => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->is_pos ? $_[0] : $_[1] };
7905             Class::Multimethods::multimethod min => qw(Math::BigNum Math::BigNum::Nan) => sub { $_[1] };
7906              
7907             =head2 max
7908              
7909             $x->max(BigNum) # => BigNum
7910              
7911             Returns C if C is greater than C. Returns C otherwise.
7912              
7913             =cut
7914              
7915             Class::Multimethods::multimethod max => qw(Math::BigNum Math::BigNum) => sub {
7916             my ($x, $y) = @_;
7917             Math::GMPq::Rmpq_cmp($$x, $$y) > 0 ? $x : $y;
7918             };
7919              
7920             Class::Multimethods::multimethod max => qw(Math::BigNum *) => sub {
7921             $_[0]->max(Math::BigNum->new($_[1]));
7922             };
7923              
7924             Class::Multimethods::multimethod max => qw(Math::BigNum Math::BigNum::Inf) => sub { $_[1]->is_pos ? $_[1] : $_[0] };
7925             Class::Multimethods::multimethod max => qw(Math::BigNum Math::BigNum::Nan) => sub { $_[1] };
7926              
7927             =head1 AUTHOR
7928              
7929             Daniel Șuteu, C<< >>
7930              
7931             =head1 BUGS
7932              
7933             Please report any bugs or feature requests to C, or through
7934             the web interface at L. I will be notified, and then you'll
7935             automatically be notified of progress on your bug as I make changes.
7936              
7937             =head1 SUPPORT
7938              
7939             You can find documentation for this module with the perldoc command.
7940              
7941             perldoc Math::BigNum
7942              
7943              
7944             You can also look for information at:
7945              
7946             =over 4
7947              
7948             =item * RT: CPAN's request tracker (report bugs here)
7949              
7950             L
7951              
7952             =item * AnnoCPAN: Annotated CPAN documentation
7953              
7954             L
7955              
7956             =item * CPAN Ratings
7957              
7958             L
7959              
7960             =item * Search CPAN
7961              
7962             L
7963              
7964             =item * GitHub
7965              
7966             L
7967              
7968             =back
7969              
7970             =head1 ACKNOWLEDGEMENTS
7971              
7972             =over 4
7973              
7974             =item * Rounding
7975              
7976             L
7977              
7978             =item * Special cases and NaN
7979              
7980             L
7981              
7982             =item * What Every Computer Scientist Should Know About FloatingPoint Arithmetic
7983              
7984             L
7985              
7986             =item * Wolfram|Alpha
7987              
7988             L
7989              
7990             =back
7991              
7992             =head1 SEE ALSO
7993              
7994             =over 4
7995              
7996             =item * Fast math libraries
7997              
7998             L - High speed arbitrary size integer math.
7999              
8000             L - perl interface to the GMP library's integer (mpz) functions.
8001              
8002             L - perl interface to the GMP library's rational (mpq) functions.
8003              
8004             L - perl interface to the MPFR (floating point) library.
8005              
8006             =item * Portable math libraries
8007              
8008             L - Arbitrary size integer/float math package.
8009              
8010             L - Arbitrary size floating point math package.
8011              
8012             L - Arbitrary big rational numbers.
8013              
8014             =item * Math utilities
8015              
8016             L - Utilities related to prime numbers, including fast sieves and factoring.
8017              
8018             =back
8019              
8020             =head1 LICENSE AND COPYRIGHT
8021              
8022             Copyright 2016-2017 Daniel Șuteu.
8023              
8024             This program is free software; you can redistribute it and/or modify it
8025             under the terms of the the Artistic License (2.0). You may obtain a
8026             copy of the full license at:
8027              
8028             L
8029              
8030             Any use, modification, and distribution of the Standard or Modified
8031             Versions is governed by this Artistic License. By using, modifying or
8032             distributing the Package, you accept this license. Do not use, modify,
8033             or distribute the Package, if you do not accept this license.
8034              
8035             If your Modified Version has been derived from a Modified Version made
8036             by someone other than you, you are nevertheless required to ensure that
8037             your Modified Version complies with the requirements of this license.
8038              
8039             This license does not grant you the right to use any trademark, service
8040             mark, tradename, or logo of the Copyright Holder.
8041              
8042             This license includes the non-exclusive, worldwide, free-of-charge
8043             patent license to make, have made, use, offer to sell, sell, import and
8044             otherwise transfer the Package with respect to any patent claims
8045             licensable by the Copyright Holder that are necessarily infringed by the
8046             Package. If you institute patent litigation (including a cross-claim or
8047             counterclaim) against any party alleging that the Package constitutes
8048             direct or contributory patent infringement, then this Artistic License
8049             to you shall terminate on the date that such litigation is filed.
8050              
8051             Disclaimer of Warranty: THE PACKAGE IS PROVIDED BY THE COPYRIGHT HOLDER
8052             AND CONTRIBUTORS "AS IS' AND WITHOUT ANY EXPRESS OR IMPLIED WARRANTIES.
8053             THE IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
8054             PURPOSE, OR NON-INFRINGEMENT ARE DISCLAIMED TO THE EXTENT PERMITTED BY
8055             YOUR LOCAL LAW. UNLESS REQUIRED BY LAW, NO COPYRIGHT HOLDER OR
8056             CONTRIBUTOR WILL BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, OR
8057             CONSEQUENTIAL DAMAGES ARISING IN ANY WAY OUT OF THE USE OF THE PACKAGE,
8058             EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
8059              
8060              
8061             =cut
8062              
8063             1; # End of Math::BigNum