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