File Coverage

blib/lib/Math/Polynomial/Solve.pm
Criterion Covered Total %
statement 484 517 93.6
branch 157 200 78.5
condition 18 27 66.6
subroutine 36 38 94.7
pod 25 27 92.5
total 720 809 89.0


line stmt bran cond sub pod time code
1             package Math::Polynomial::Solve;
2              
3             require 5.010001;
4 17     17   1216629 use strict;
  17         185  
  17         468  
5 17     17   91 use warnings;
  17         34  
  17         467  
6 17     17   9047 use utf8;
  17         222  
  17         79  
7 17     17   480 use Carp;
  17         34  
  17         878  
8              
9 17     17   3081 use Math::Complex;
  17         67894  
  17         2551  
10 17     17   7489 use Math::Utils qw(:polynomial :utility);
  17         52036  
  17         3674  
11 17     17   127 use Exporter;
  17         39  
  17         4630  
12              
13             our $VERSION = '2.85';
14             our @ISA = qw(Exporter);
15              
16             #
17             # Three # for "I am here" messages.
18             # Four # for variable dumps.
19             # Five # for a dump of the companion matrix.
20             # Six # for sturm structs (sign chain, etc).
21             #
22             #use Smart::Comments q(######);
23              
24             #
25             # Export only on request.
26             #
27             our %EXPORT_TAGS = (
28             'classical' => [ qw(
29             linear_roots
30             quadratic_roots
31             cubic_roots
32             quartic_roots
33             coefficients
34             ) ],
35             'numeric' => [ qw(poly_roots
36             poly_option
37             build_companion
38             balance_matrix
39             hqr_eigen_hessenberg
40             coefficients
41             ) ],
42             'sturm' => [ qw(
43             poly_real_root_count
44             poly_sturm_chain
45             sturm_real_root_range_count
46             sturm_bisection
47             sturm_bisection_roots
48             sturm_sign_count
49             sturm_sign_chain
50             sturm_sign_minus_inf
51             sturm_sign_plus_inf
52             coefficients
53             ) ],
54             'utility' => [ qw(
55             epsilon
56             laguerre
57             newtonraphson
58             poly_iteration
59             poly_nonzero_term_count
60             poly_tolerance
61             coefficients
62             ) ],
63             );
64              
65             our @EXPORT_OK = (
66             @{ $EXPORT_TAGS{'classical'} },
67             @{ $EXPORT_TAGS{'numeric'} },
68             @{ $EXPORT_TAGS{'sturm'} },
69             @{ $EXPORT_TAGS{'utility'} } );
70              
71             our @EXPORT = qw( coefficients ascending_order );
72              
73             #
74             # Add an :all tag automatically.
75             #
76             $EXPORT_TAGS{all} = [@EXPORT_OK, @EXPORT];
77              
78             #
79             # Options to set or unset to force poly_roots() to use different
80             # methods of solving.
81             #
82             # hessenberg (default 1): set to 1 to force poly_roots() to use the QR
83             # Hessenberg method regardless of the degree of the polynomial. Set to zero
84             # to force poly_roots() uses one of the specialized routines (linerar_roots(),
85             # quadratic_roots(), etc) if the degree of the polynomial is less than five.
86             #
87             # root_function (default 0): set to 1 to force poly_roots() to use
88             # Math::Complex's root(-c/a, n) function if the polynomial is of the form
89             # ax**n + c.
90             #
91             # varsubst (default 0): try to reduce the degree of the polynomial through
92             # variable substitution before solving.
93             #
94             my %option = (
95             hessenberg => 1,
96             root_function => 0,
97             varsubst => 0,
98             );
99              
100             #
101             # Iteration limits. The Hessenberg matrix method and the Laguerre method run
102             # continuously until they converge upon an answer. The iteration limits are
103             # there to prevent the loops from running forever if they fail to converge.
104             #
105             my %iteration = (
106             hessenberg => 60,
107             newtonraphson => 60,
108             laguerre => 60,
109             sturm_bisection => 100,
110             );
111              
112             #
113             # Some values here are placeholders only, and will get
114             # replaced in the BEGIN block.
115             #
116             my %tolerance = (
117             newtonraphson => 1e-14,
118             laguerre => 1e-14,
119             );
120              
121             #
122             # Set up the epsilon variable, the value that is, in the floating-point
123             # math of the computer, the smallest value a variable can have before
124             # it is indistinguishable from zero when adding it to one.
125             #
126             my $epsilon;
127              
128             BEGIN
129             {
130 17     17   59 $epsilon = 0.125;
131 17         45 my $epsilon2 = $epsilon/2.0;
132              
133 17         97 while (1.0 + $epsilon2 > 1.0)
134             {
135 833         1002 $epsilon = $epsilon2;
136 833         1330 $epsilon2 /= 2.0;
137             }
138              
139 17         95 $tolerance{laguerre} = 2 * $epsilon;
140 17         75022 $tolerance{newtonraphson} = 2 * $epsilon;
141             }
142              
143             #
144             # Flag to determine whether calling order is
145             # ($an_1, $an_2, $an_3, ...) or if it is
146             # ($a0, $a1, $a2, $a3, ...)
147             #
148             my $ascending_flag = 0; # default 0, in a later version it will be 1.
149              
150             #
151             # See the END block.
152             #
153             my $coeff_order_set = 0;
154              
155             =pod
156              
157             =encoding UTF-8
158              
159             =head1 NAME
160              
161             Math::Polynomial::Solve - Find the roots of polynomial equations.
162              
163             =head1 SYNOPSIS
164              
165             use Math::Complex; # The roots may be complex numbers.
166             use Math::Polynomial::Solve qw(poly_roots coefficients);
167             coefficients order => 'descending';
168              
169             my @x = poly_roots(1, 1, 4, 4);
170              
171             or
172              
173             use Math::Complex; # The roots may be complex numbers.
174             use Math::Polynomial::Solve qw(:numeric coefficients); # See the EXPORT section
175             coefficients order => 'descending';
176              
177             #
178             # Find roots using the matrix method.
179             #
180             my @x = poly_roots(5, 12, 17, 12, 5);
181              
182             #
183             # Alternatively, use the classical methods instead of the matrix
184             # method if the polynomial degree is less than five.
185             #
186             poly_option(hessenberg => 0);
187             @x = poly_roots(5, 12, 17, 12, 5);
188              
189             or
190              
191             use Math::Complex; # The roots may be complex numbers.
192             use Math::Polynomial::Solve qw(:classical coefficients); # See the EXPORT section
193             coefficients order => 'descending';
194              
195             #
196             # Find the polynomial roots using the classical methods.
197             #
198              
199             # Find the roots of ax + b
200             my @x1 = linear_roots($a, $b);
201              
202             # Find the roots of ax**2 + bx +c
203             my @x2 = quadratic_roots($a, $b, $c);
204              
205             # Find the roots of ax**3 + bx**2 +cx + d
206             my @x3 = cubic_roots($a, $b, $c, $d);
207              
208             # Find the roots of ax**4 + bx**3 +cx**2 + dx + e
209             my @x4 = quartic_roots($a, $b, $c, $d, $e);
210              
211             or
212              
213             use Math::Complex; # The roots may be complex numbers.
214             use Math::Polynomial;
215             use Math::Polynomial::Solve qw(:classical coefficients);
216              
217             #
218             # Change default coefficient order for M::P::S.
219             #
220             coefficients order => 'ascending';
221              
222             #
223             # Form 8*x**3 - 6*x - 1
224             #
225             my $p1 = Math::Polynomial->new(-1, -6, 0, 8);
226              
227             #
228             # Use Math::Polynomial's coefficient order.
229             # If the coefficient order had not been changed,
230             # the statement would be:
231             #
232             # my @roots = poly_roots(reverse $p1->coefficients);
233             #
234             my @roots = poly_roots($p1->coefficients);
235              
236             or
237              
238             use Math::Polynomial::Solve qw(:sturm coefficients);
239             coefficients order => 'descending';
240              
241             #
242             # Find the number of unique real roots of the polynomial.
243             #
244             my $no_of_unique_roots = poly_real_root_count(2, 7, 8, -8, -23, -11);
245              
246             =head1 DESCRIPTION
247              
248             This package supplies a set of functions that find the roots of
249             polynomials, along with some utility functions.
250              
251             Roots will be either real or of type L.
252              
253             Functions making use of the Sturm sequence are also available, letting you
254             find the number of real roots present in a range of X values.
255              
256             In addition to the root-finding functions, the internal functions have
257             also been exported for your use.
258              
259             =cut
260              
261             #
262             # $asending = ascending_order();
263             # $oldorder = ascending_order($neworder);
264             #
265             # Obsolete way of doing it, but preserve it in case
266             # someone was an early adopter.
267             #
268             sub ascending_order
269             {
270 0     0 0 0 my $ascend = $ascending_flag;
271              
272 0 0       0 if (scalar @_ > 0)
273             {
274 0 0       0 $ascending_flag = ($_[0] == 0)? 0: 1;
275 0         0 $coeff_order_set = 1;
276             }
277              
278 0         0 return $ascend;
279             }
280              
281             sub coefficients
282             {
283 17     17 1 1607 my %def = @_;
284 17 50       139 if (not exists $def{order})
    100          
    50          
285             {
286 0         0 carp "'coefficients' needs to know the order.";
287 0         0 $coeff_order_set = 0;
288             }
289             elsif ($def{order} =~ m/ascend/i)
290             {
291 15         37 $ascending_flag = 1;
292 15         46 $coeff_order_set = 1;
293             }
294             elsif ($def{order} =~ m/descend/i)
295             {
296 2         6 $ascending_flag = 0;
297 2         7 $coeff_order_set = 1;
298             }
299             else
300             {
301 0         0 carp "'coefficients' needs to know if the order is ascending or descending.";
302 0         0 $coeff_order_set = 0;
303             }
304             }
305              
306             #
307             # ($new_coefficients_ref, $varsubst) = poly_analysis(@coefficients);
308             #
309             # If the polynomial has evenly spaced gaps of zero coefficients, reduce
310             # the polynomial through variable substitution.
311             #
312             # For example, a degree-6 polynomial like 9x**6 + 128x**3 + 7
313             # can be reduced to a polynomial 9y**2 + 128y + 7, where y = x**3.
314             #
315             # After solving a quadratic instead of a sextic, the actual roots of
316             # the original equation are found by taking the cube roots of each
317             # root of the quadratic.
318             #
319             # Not exported. Coefficients are always in ascending order.
320             #
321             sub poly_analysis
322             {
323 44     44 0 87 my(@coefficients) = @_;
324 44         46 my @czp;
325 44         47 my $m = 1;
326              
327             #
328             # Is the count of coefficients a multiple of any of the primes?
329             #
330             # Realistically I don't expect any gaps that can't be handled by
331             # the first three prime numbers, but it's not much of a waste of
332             # space to check the first dozen.
333             #
334 44         168 @czp = grep(($#coefficients % $_) == 0,
335             (2, 3, 5, 7, 11, 13, 17, 19, 23, 29, 31, 37)
336             );
337              
338             #
339             # Any coefficients zero at the non-N degrees? (1==T,0==F).
340             #
341             #### @czp
342             #
343 44 100       78 if (@czp)
344             {
345 30         50 for my $j (1..$#coefficients - 1)
346             {
347 106 100       166 if (abs($coefficients[$j]) > $epsilon)
348             {
349 20         38 @czp = grep(($j % $_) == 0, @czp);
350             }
351             }
352              
353             #
354             # The remaining list of primes represent the gap size
355             # between non-zero coefficients.
356             #
357 30         50 map(($m *= $_), @czp);
358              
359             #### Substitution degree: $m
360             }
361              
362             #
363             # If there's a sequence of zero-filled gaps in the coefficients,
364             # reduce the polynomial by degree $m and check again for the
365             # next round of factors (e.g., X**8 + X**4 + 1 needs two rounds
366             # to get to a factor of 4).
367             #
368 44 100       71 if ($m > 1)
369             {
370 22         25 my @alt_coefs;
371 22         97 push @alt_coefs, $coefficients[$_*$m] for (0..$#coefficients/$m);
372 22         39 my($cf, $m1) = poly_analysis(@alt_coefs);
373 22         41 @coefficients = @$cf;
374 22         38 $m *= $m1;
375             }
376              
377 44         87 return \@coefficients, $m;
378             }
379              
380             =head1 EXPORT
381              
382             There is an B tag that exports everything.
383              
384             Currently there is one default export, L.
385              
386             If you want to have more fine-grained control you may
387             individually name the functions in an export list, or
388             use one four export tags:
389              
390             L,
391             L,
392             L,
393             L,
394              
395             =head2 EXPORTED BY DEFAULT
396              
397             =head3 coefficients
398              
399             Changes the default order of the coefficents to the functions.
400              
401             When Math::Polynomial::Solve was originally written, it followed the
402             calling convention of L, using the highest degree
403             coefficient, followed by the next highest degree coefficient, and so
404             on in descending order.
405              
406             Later Math::Polynomial was re-written, and the order of the coefficients were
407             put in ascending order, e.g.:
408              
409             use Math::Polynomial;
410              
411             #
412             # Create the polynomial 8*x**3 - 6*x - 1.
413             #
414             $fpx = Math::Polynomial->new(-1, -6, 0, 8);
415              
416             If you use Math::Polynomial with this module, it will probably be
417             more convenient to change the default parameter list of
418             Math::Polynomial::Solve's functions, using the coefficients() function:
419              
420             use Math::Polynomial;
421             use Math::Polynomial::Solve qw(:all);
422              
423             coefficients order => 'ascending';
424              
425             my $fp4 = Math::Polynomial->interpolate([1 .. 4], [14, 19, 25, 32]);
426              
427             #
428             # Find roots of $fp4.
429             #
430             my @fp4_roots = quartic_roots($fp4->coefficients);
431              
432             or
433              
434             my @fp4_roots = poly_roots($fp4->coefficients);
435              
436             If C 'ascending'> had not been called, the
437             previous line of code would have been written instead as
438              
439             my @fp4_roots = poly_roots(reverse $fp4->coefficients);
440              
441             The function is a way to help with the change in the API when version 3.00 of
442             this module is released. At that point coefficients will be in ascending
443             order by default, and you will need to use
444             C 'ascending'> to use the old (current) style.
445              
446             =head2 Numeric Functions
447              
448             These are the functions that calculate the polynomial's roots through numeric
449             algorithms. They are all exported under the tag "numeric".
450              
451             =head3 poly_roots()
452              
453             Returns the roots of a polynomial equation, regardless of degree.
454             Unlike the other root-finding functions, it will check for coefficients
455             of zero for the highest power, and 'step down' the degree of the
456             polynomial to the appropriate case. Additionally, it will check for
457             coefficients of zero for the lowest power terms, and add zeros to its
458             root list before calling one of the root-finding functions.
459              
460             By default, C will use the Hessenberg matrix method for solving
461             polynomials. This can be changed by calling L.
462              
463             The method of poly_roots() is almost equivalent to
464              
465             @x = hqr_eigen_hessenberg(
466             balance_matrix(build_companion(@coefficients))
467             );
468              
469             except this wouldn't check for leading and trailing zero coefficients, and it
470             ignores the settings of C.
471              
472             =cut
473              
474             sub poly_roots
475             {
476 135 50   135 1 433405 my(@coefficients) = ($ascending_flag == 0)? reverse @_: @_;
477 135         263 my(@x, @zero_x);
478 135         213 my $subst_degree = 1;
479              
480             #
481             #### @coefficients
482             #
483             # Check for zero coefficients in the higher-powered terms.
484             #
485 135   33     709 pop @coefficients while (scalar @coefficients and
486             abs($coefficients[$#coefficients]) < $epsilon);
487              
488 135 50       373 if (@coefficients == 0)
489             {
490 0         0 carp "All coefficients are zero\n";
491 0         0 return (0);
492             }
493              
494             #
495             # How about zero coefficients in the low terms?
496             #
497 135   66     544 while (scalar @coefficients and
498             abs($coefficients[0]) < $epsilon)
499             {
500 12         20 push @zero_x, 0;
501             shift @coefficients
502 12         37 }
503              
504             #
505             # If the polynomial is of the form c + ax**n, and if the
506             # root_function option is set, use the Math::Complex::root()
507             # function to return the roots.
508             #
509             ### %option
510             #
511 135 100 100     416 if ($option{root_function} and
512             poly_nonzero_term_count(@coefficients) == 2)
513             {
514 15         88 return @zero_x,
515             root(-$coefficients[0]/$coefficients[$#coefficients],
516             $#coefficients);
517             }
518              
519             #
520             # Next do some analysis of the coefficients.
521             # See if we can reduce the size of the polynomial by
522             # doing some variable substitution.
523             #
524 120 100 66     322 if ($option{varsubst} and $#coefficients > 1)
525             {
526 22         27 my $cf;
527 22         41 ($cf, $subst_degree) = poly_analysis(@coefficients);
528 22 50       54 @coefficients = @$cf if ($subst_degree > 1);
529             }
530              
531             #
532             # If the remaining polynomial is a quintic or higher, or
533             # if $option{hessenberg} is set, continue with the matrix
534             # calculation.
535             #
536             #### @coefficients
537             #### $subst_degree
538             #
539             #
540             # With the coefficents in ascending order,
541             # pretend it was always that way for the next
542             # function calls.
543             #
544 120         179 my $temp_ascending_flag = $ascending_flag;
545 120         185 $ascending_flag = 1;
546              
547 120 100 66     374 if ($option{hessenberg} or $#coefficients > 4)
    100          
    100          
    100          
    50          
548             {
549             #
550             # QR iterations from the matrix.
551             #
552 87         229 @x = hqr_eigen_hessenberg(
553             balance_matrix(build_companion(@coefficients))
554             );
555             }
556             elsif ($#coefficients == 4)
557             {
558 15         34 @x = quartic_roots(@coefficients);
559             }
560             elsif ($#coefficients == 3)
561             {
562 4         9 @x = cubic_roots(@coefficients);
563             }
564             elsif ($#coefficients == 2)
565             {
566 5         16 @x = quadratic_roots(@coefficients);
567             }
568             elsif ($#coefficients == 1)
569             {
570 9         24 @x = linear_roots(@coefficients);
571             }
572              
573 120         4619 $ascending_flag = $temp_ascending_flag;
574              
575 120 100       299 @x = map(root($_, $subst_degree), @x) if ($subst_degree > 1);
576              
577 120         6552 return @zero_x, @x;
578             }
579              
580              
581             =head3 poly_option()
582              
583             Set options that affect the behavior of the C function. All
584             options are set to either 1 ("on") or 0 ("off"). See also L
585             and L.
586              
587             Options may be set and saved:
588              
589             #
590             # Set a few options...
591             #
592             poly_option(hessenberg => 0, root_function => 1);
593              
594             #
595             # Get all of the current options and their values.
596             #
597             my %all_options = poly_option();
598              
599             #
600             # Set some options but save the former option values
601             # for later.
602             #
603             my %changed_options = poly_option(hessenberg => 1, varsubst => 1);
604              
605             The current options available are:
606              
607             =over 4
608              
609             =item 'hessenberg'
610              
611             Use the QR Hessenberg matrix method to solve the polynomial. By default, this
612             is set to 1. If set to 0, C uses one of the L
613             root-finding functions listed below, I the degree of the polynomial is four
614             or less.
615              
616             =item 'root_function'
617              
618             Use the L function from Math::Complex if the
619             polynomial is of the form C. This will take precedence over the other
620             solving methods.
621              
622             =item 'varsubst'
623              
624             Reduce polynomials to a lower degree through variable substitution, if possible.
625              
626             For example, with C set to one and the polynomial to solve being
627             C<9x**6 + 128x**3 + 21>, C will reduce the polynomial to
628             C<9y**2 + 128y + 21> (where C),
629             and solve the quadratic (either classically or numerically, depending
630             on the hessenberg option). Taking the cube root of each quadratic root
631             completes the operation.
632              
633             This has the benefit of having a simpler matrix to solve, or if the
634             C option is set to zero, has the effect of being able to use one of
635             the classical methods on a polynomial of high degree. In the above example, the
636             order-six polynomial gets solved with the quadratic_roots() function if the
637             hessenberg option is zero.
638              
639             Currently the variable substitution is fairly simple and will only look
640             for gaps of zeros in the coefficients that are multiples of the prime numbers
641             less than or equal to 37 (2, 3, 5, et cetera).
642              
643             =back
644              
645             =cut
646              
647             sub poly_option
648             {
649 22     22 1 33614 my %opts = @_;
650 22         32 my %old_opts;
651              
652 22 100       71 return %option if (scalar @_ == 0);
653              
654 15         47 for my $okey (keys %opts)
655             {
656             #
657             # If this is a real option, save its old value, then set it.
658             #
659 15 50       38 if (exists $option{$okey})
660             {
661 15         34 $old_opts{$okey} = $option{$okey};
662 15 100       65 $option{$okey} = ($opts{$okey})? 1: 0;
663             }
664             else
665             {
666 0         0 carp "poly_option(): unknown key $okey.";
667             }
668             }
669              
670 15         42 return %old_opts;
671             }
672              
673             =head3 build_companion
674              
675             Creates the initial companion matrix of the polynomial. Returns an array
676             of arrays (the internal representation of a matrix). This may be used as
677             an argument to the L contructor:
678              
679             my @cm = build_companion(@coef);
680              
681             my $m = Math::Matrix->new(@cm);
682             $m->print();
683              
684             The Wikipedia article at L has
685             more information on the subject.
686              
687             =cut
688              
689             #
690             # Perl code to find roots of a polynomial translated by Nick Ing-Simmons
691             # from FORTRAN code by Hiroshi Murakami.
692             #
693             # From the netlib archive: http://netlib.bell-labs.com/netlib/search.html
694             # In particular http://netlib.bell-labs.com/netlib/opt/companion.tgz
695             #
696             sub build_companion
697             {
698 87 50   87 1 247 my @coefficients = ($ascending_flag == 0)? reverse @_: @_;
699 87         190 my $n = $#coefficients - 1;
700 87         131 my @h;
701              
702             #
703             ### build_companion called with: @coefficients
704             #
705             # First step: Divide by the leading coefficient and negate.
706             #
707 87         159 my $cn = - (pop @coefficients);
708 87         305 map($_ /= $cn, @coefficients);
709              
710             #
711             # Next: set up the diagonal matrix.
712             #
713 87         202 for my $i (0 .. $n)
714             {
715 351         767 $h[$i][$n] = shift @coefficients;
716 351         1072 map($h[$i][$_] = 0.0, 0 .. $n - 1);
717             }
718              
719 87         265 map($h[$_][$_ - 1] = 1.0, 1 .. $n);
720              
721 87         285 return @h;
722             }
723              
724             =head3 balance_matrix
725              
726             Balances the matrix (makes the rows and columns have similar norms) created
727             by build_companion() by applying a matrix transformation with a diagonal
728             matrix of powers of two.
729              
730             This is used to help prevent any rounding errors that occur if the elements
731             of the matrix differ greatly in magnitude.
732              
733             =cut
734              
735             # BASE is the base of the floating point representation on the machine.
736             # It is 16 for base 16 float : for example, IBM system 360/370.
737             # It is 2 for base 2 float : for example, IEEE float.
738             sub BASE () { 2 }
739             sub BASESQR () { BASE * BASE }
740              
741             #
742             # @matrix = balance_matrix(@cm);
743             #
744             # Balance the companion matrix created by build_companion().
745             #
746             # Return an array of arrays representing the N by N matrix.
747             #
748             # In the :numeric export set.
749             #
750             sub balance_matrix
751             {
752 87     87 1 189 my @h = @_;
753 87         148 my $n = $#h;
754              
755             #
756             ### Balancing the unsymmetric matrix A.
757             #
758             ##### @h
759             #
760             # Perl code translated by Nick Ing-Simmons from FORTRAN code
761             # by Hiroshi Murakami.
762             #
763             # The Fortran code is based on the Algol code "balance" from paper:
764             # "Balancing a Matrix for Calculation of Eigenvalues and Eigenvectors"
765             # by B. N. Parlett and C. Reinsch, Numer. Math. 13, 293-304(1969).
766             #
767             # Note: The only non-zero elements of the companion matrix are touched.
768             #
769 87         146 my $noconv = 1;
770 87         195 while ($noconv)
771             {
772 156         221 $noconv = 0;
773 156         263 for my $i (0 .. $n)
774             {
775             #
776             # Touch only non-zero elements of companion.
777             #
778 681         883 my $c;
779 681 100       1122 if ($i != $n)
780             {
781 525         899 $c = abs($h[$i + 1][$i]);
782             }
783             else
784             {
785 156         212 $c = 0.0;
786 156         296 for my $j (0 .. $n - 1)
787             {
788 525         898 $c += abs($h[$j][$n]);
789             }
790             }
791              
792 681         862 my $r;
793 681 100       1283 if ($i == 0)
    100          
794             {
795 156         248 $r = abs($h[0][$n]);
796             }
797             elsif ($i != $n)
798             {
799 378         711 $r = abs($h[$i][$i - 1]) + abs($h[$i][$n]);
800             }
801             else
802             {
803 147         234 $r = abs($h[$i][$i - 1]);
804             }
805              
806 681 100 66     2009 next if ($c == 0.0 || $r == 0.0);
807              
808 672         1012 my $g = $r / BASE;
809 672         859 my $f = 1.0;
810 672         973 my $s = $c + $r;
811 672         1303 while ( $c < $g )
812             {
813 205         279 $f = $f * BASE;
814 205         350 $c = $c * BASESQR;
815             }
816              
817 672         917 $g = $r * BASE;
818 672         1188 while ($c >= $g)
819             {
820 113         167 $f = $f / BASE;
821 113         221 $c = $c / BASESQR;
822             }
823              
824 672 100       1563 if (($c + $r) < 0.95 * $s * $f)
825             {
826 173         247 $g = 1.0 / $f;
827 173         232 $noconv = 1;
828              
829             #C Generic code.
830             #C do $j=1,$n
831             #C $h($i,$j)=$h($i,$j)*$g
832             #C enddo
833             #C do $j=1,$n
834             #C $h($j,$i)=$h($j,$i)*$f
835             #C enddo
836             #C begin specific code. Touch only non-zero elements of companion.
837 173 100       300 if ($i == 0)
838             {
839 41         73 $h[0][$n] *= $g;
840             }
841             else
842             {
843 132         228 $h[$i][$i - 1] *= $g;
844 132         206 $h[$i][$n] *= $g;
845             }
846 173 100       288 if ($i != $n)
847             {
848 145         283 $h[$i + 1][$i] *= $f;
849             }
850             else
851             {
852 28         62 for my $j (0 .. $n)
853             {
854 142         239 $h[$j][$i] *= $f;
855             }
856             }
857             }
858             } # for $i
859             } # while $noconv
860              
861             #
862             ### Returning balanced matrix.
863             ##### @h
864             #
865 87         267 return @h;
866             }
867              
868              
869             =head3 hqr_eigen_hessenberg
870              
871             Returns the roots of the polynomial equation by solving the matrix created by
872             C and C. See L.
873              
874             =cut
875              
876             sub hqr_eigen_hessenberg
877             {
878 87     87 1 180 my @h = @_;
879 87         159 my $n = $#h;
880              
881             #
882             ### hqr_eigen_hessenberg()
883             #
884             # Eigenvalue Computation by the Householder QR method for the
885             # Real Hessenberg matrix.
886             #
887             # Perl code translated by Nick Ing-Simmons from FORTRAN code
888             # by Hiroshi Murakami.
889             #
890             # The Fortran code is based on the Algol code "hqr" from the paper:
891             # "The QR Algorithm for Real Hessenberg Matrices"
892             # by R. S. Martin, G. Peters and J. H. Wilkinson,
893             # Numer. Math. 14, 219-231(1970).
894             #
895 87         147 my($p, $q, $r);
896 87         123 my $t = 0.0;
897              
898 87         131 my @roots;
899              
900             ROOT:
901 87         185 while ($n >= 0)
902             {
903 207         336 my $its = 0;
904 207         312 my $na = $n - 1;
905              
906 207         456 while ($its < $iteration{hessenberg})
907             {
908 1298         2059 my($w, $x, $y);
909              
910             #
911             # Look for single small sub-diagonal element;
912             #
913 1298         1820 my $l = 0;
914 1298         2527 for my $d (reverse 1 .. $n)
915             {
916 4215 100       10783 if (abs( $h[$d][ $d - 1 ] ) <= $epsilon *
917             (abs( $h[ $d - 1 ][ $d - 1 ] ) +
918             abs( $h[$d][$d] ) ) )
919             {
920 157         236 $l = $d;
921 157         221 last;
922             }
923             }
924              
925 1298         2249 $x = $h[$n][$n];
926              
927 1298 100       2347 if ($l == $n)
928             {
929             #
930             # One (real) root found.
931             #
932 63         95 $n--;
933 63         123 push @roots, $x + $t;
934 63         176 next ROOT;
935             }
936              
937 1235         1732 $y = $h[$na][$na];
938 1235         1837 $w = $h[$n][$na] * $h[$na][$n];
939              
940 1235 100       2202 if ($l == $na)
941             {
942 144         245 $p = ( $y - $x ) / 2;
943 144         226 $q = $p * $p + $w;
944 144         378 $y = sqrt( abs($q) );
945 144         1061 $x += $t;
946              
947 144 100       304 if ($q > 0.0)
948             {
949             #
950             # Real pair.
951             #
952 17 100       55 $y = -$y if ( $p < 0.0 );
953 17         30 $y += $p;
954 17         42 push @roots, $x - $w / $y;
955 17         34 push @roots, $x + $y;
956             }
957             else
958             {
959             #
960             # Complex or twin pair.
961             #
962 127         338 push @roots, $x + $p - $y * i;
963 127         37165 push @roots, $x + $p + $y * i;
964             }
965              
966 144         33502 $n -= 2;
967 144         497 next ROOT;
968             }
969              
970 1091 50       2123 croak "Too many iterations ($its) at n=$n\n" if ($its >= $iteration{hessenberg});
971              
972 1091 100 100     3460 if ($its && $its % 10 == 0)
973             {
974             #
975             # Form exceptional shift.
976             #
977             ### Exceptional shift at: $its
978             #
979              
980 53         96 $t += $x;
981 53         104 for my $i (0 .. $n)
982             {
983 249         358 $h[$i][$i] -= $x;
984             }
985              
986 53         162 my $s = abs($h[$n][$na]) + abs($h[$na][$n - 2]);
987 53         85 $y = 0.75 * $s;
988 53         71 $x = $y;
989 53         96 $w = -0.4375 * $s * $s;
990             }
991              
992 1091         1515 $its++;
993              
994             #
995             ### Look for two consecutive small
996             ### sub-diagonal elements.
997             #
998 1091         1481 my $m = $l; # Set in case we fall through the loop.
999 1091         2137 for my $d (reverse $l .. $n - 2)
1000             {
1001 2809         4351 my $z = $h[$d][$d];
1002 2809         3998 my $s = $y - $z;
1003 2809         3632 $r = $x - $z;
1004 2809         5153 $p = ($r * $s - $w) / $h[$d + 1][$d] + $h[$d][$d + 1];
1005 2809         4467 $q = $h[$d + 1][$d + 1] - $z - $r - $s;
1006 2809         4167 $r = $h[$d + 2][$d + 1];
1007              
1008 2809         4389 $s = abs($p) + abs($q) + abs($r);
1009 2809         3728 $p /= $s;
1010 2809         3451 $q /= $s;
1011 2809         3441 $r /= $s;
1012              
1013             #
1014             # The sub-diagonal check doesn't get made for
1015             # the last iteration of the loop, and the only
1016             # reason we have the loop continue up to this
1017             # point is to set $p, $q, and $r.
1018             #
1019 2809 100       5119 last if ($d == $l);
1020              
1021 1726 100       5594 if (abs($h[$d][$d - 1]) * (abs($q) + abs($r)) <=
1022             $epsilon * abs($p) * (
1023             abs($h[$d - 1][$d - 1]) +
1024             abs($z) +
1025             abs($h[$d + 1][$d + 1])
1026             ))
1027             {
1028 8         20 $m = $d;
1029 8         20 last;
1030             }
1031             }
1032              
1033             #
1034             #### $n
1035             #### $l
1036             #### $m
1037             #
1038 1091         2273 for my $i (($m + 2) .. $n)
1039             {
1040 2809         4605 $h[$i][$i - 2] = 0.0;
1041             }
1042 1091         1868 for my $i (($m + 3) .. $n)
1043             {
1044 1718         2782 $h[$i][$i - 3] = 0.0;
1045             }
1046              
1047             #
1048             # Double QR step involving rows $l to $n and
1049             # columns $m to $n.
1050             #
1051 1091         1789 for my $k ($m .. $na)
1052             {
1053 3900         5146 my $z;
1054 3900         5903 my $notlast = ($k != $na);
1055 3900 100       7143 if ($k != $m)
1056             {
1057 2809         4356 $p = $h[$k][$k - 1];
1058 2809         4562 $q = $h[$k + 1][$k - 1];
1059 2809 100       5038 $r = ($notlast)? $h[$k + 2][$k - 1]: 0.0;
1060              
1061 2809         4683 $x = abs($p) + abs($q) + abs($r);
1062 2809 50       5063 next if ( $x == 0.0 );
1063              
1064 2809         3910 $p /= $x;
1065 2809         3482 $q /= $x;
1066 2809         3712 $r /= $x;
1067             }
1068              
1069 3900         10919 my $s = sqrt($p * $p + $q * $q + $r * $r);
1070 3900 100       29515 $s = -$s if ($p < 0.0);
1071              
1072 3900 100       7287 if ($k != $m)
    100          
1073             {
1074 2809         5067 $h[$k][$k - 1] = -$s * $x;
1075             }
1076             elsif ($l != $m)
1077             {
1078 8         22 $h[$k][$k - 1] *= -1;
1079             }
1080              
1081 3900         5257 $p += $s;
1082 3900         5299 $x = $p / $s;
1083 3900         4956 $y = $q / $s;
1084 3900         4987 $z = $r / $s;
1085 3900         4921 $q /= $p;
1086 3900         4825 $r /= $p;
1087              
1088             #
1089             # Row modification.
1090             #
1091 3900         6828 for my $j ($k .. $n)
1092             {
1093 14074         21504 $p = $h[$k][$j] + $q * $h[$k + 1][$j];
1094              
1095 14074 100       22821 if ($notlast)
1096             {
1097 11892         16736 $p += $r * $h[ $k + 2 ][$j];
1098 11892         17140 $h[ $k + 2 ][$j] -= $p * $z;
1099             }
1100              
1101 14074         19400 $h[ $k + 1 ][$j] -= $p * $y;
1102 14074         21802 $h[$k][$j] -= $p * $x;
1103             }
1104              
1105 3900         5646 my $j = $k + 3;
1106 3900 100       7192 $j = $n if ($j > $n);
1107              
1108             #
1109             # Column modification.
1110             #
1111 3900         6853 for my $i ($l .. $j)
1112             {
1113 18629         28239 $p = $x * $h[$i][$k] +
1114             $y * $h[$i][$k + 1];
1115              
1116 18629 100       29241 if ($notlast)
1117             {
1118 13624         18964 $p += $z * $h[$i][$k + 2];
1119 13624         19232 $h[$i][$k + 2] -= $p * $r;
1120             }
1121              
1122 18629         25307 $h[$i][$k + 1] -= $p * $q;
1123 18629         29197 $h[$i][$k] -= $p;
1124             }
1125             } # for $k
1126             } # while $its
1127             } # while $n
1128 87         312 return @roots;
1129             }
1130              
1131              
1132             =head2 Classical Functions
1133              
1134             These are the functions that solve polynomials via the classical methods.
1135             Quartic, cubic, quadratic, and even linear equations may be solved with
1136             these functions. They are all exported under the tag "classical".
1137              
1138             L will use these functions I the hessenberg option
1139             is set to 0, I the degree of the polynomial is four or less.
1140              
1141             The leading coefficient C<$a> must always be non-zero for the classical
1142             functions.
1143              
1144             =head3 linear_roots()
1145              
1146             Here for completeness's sake more than anything else. Returns the
1147             solution for
1148              
1149             ax + b = 0
1150              
1151             by returning C<-b/a>. This may be in either a scalar or an array context.
1152              
1153             =cut
1154              
1155             sub linear_roots
1156             {
1157 9 50   9 1 28 my($b, $a) = ($ascending_flag == 0)? reverse @_: @_;
1158              
1159 9 50       22 if (abs($a) < $epsilon)
1160             {
1161 0         0 carp "The coefficient of the highest power must not be zero!\n";
1162 0         0 return ();
1163             }
1164              
1165 9 50       25 return wantarray? (-$b/$a): -$b/$a;
1166             }
1167              
1168              
1169             =head3 quadratic_roots()
1170              
1171             Gives the roots of the quadratic equation
1172              
1173             ax**2 + bx + c = 0
1174              
1175             using the well-known quadratic formula. Returns a two-element list.
1176              
1177             =cut
1178              
1179             sub quadratic_roots
1180             {
1181 40 50   40 1 3130 my($c, $b, $a) = ($ascending_flag == 0)? reverse @_: @_;
1182              
1183 40 50       91 if (abs($a) < $epsilon)
1184             {
1185 0         0 carp "The coefficient of the highest power must not be zero!\n";
1186 0         0 return ();
1187             }
1188              
1189 40 100       81 return (0, -$b/$a) if (abs($c) < $epsilon);
1190              
1191 38         144 my $dis_sqrt = sqrt($b*$b - $a * 4 * $c);
1192              
1193 38 100       1444 $dis_sqrt = -$dis_sqrt if ($b < $epsilon); # Avoid catastrophic cancellation.
1194              
1195 38         784 my $xt = ($b + $dis_sqrt)/-2;
1196              
1197 38         2400 return ($xt/$a, $c/$xt);
1198             }
1199              
1200              
1201             =head3 cubic_roots()
1202              
1203             Gives the roots of the cubic equation
1204              
1205             ax**3 + bx**2 + cx + d = 0
1206              
1207             by the method described by R. W. D. Nickalls (see the L
1208             section below). Returns a three-element list. The first element will
1209             always be real. The next two values will either be both real or both
1210             complex numbers.
1211              
1212             =cut
1213              
1214             sub cubic_roots
1215             {
1216 23 50   23 1 10246 my($d, $c, $b, $a) = ($ascending_flag == 0)? reverse @_: @_;
1217 23         38 my @x;
1218              
1219 23 50       52 if (abs($a) < $epsilon)
1220             {
1221 0         0 carp "The coefficient of the highest power must not be zero!\n";
1222 0         0 return @x;
1223             }
1224              
1225             #
1226             # We're calling exported functions that also check
1227             # the $ascending_flag. To avoid reversing the reversed,
1228             # temporarily set the flag to zero and reset before returning.
1229             #
1230 23         27 my $temp_ascending_flag = $ascending_flag;
1231 23         28 $ascending_flag = 1;
1232              
1233 23 100       42 if (abs($d) < $epsilon)
1234             {
1235 2         6 @x = quadratic_roots($c, $b, $a);
1236 2         3 $ascending_flag = $temp_ascending_flag;
1237 2         7 return (0, @x);
1238             }
1239              
1240 21         42 my $xN = -$b/3/$a;
1241 21         39 my $yN = $d + $xN * ($c + $xN * ($b + $a * $xN));
1242              
1243 21         29 my $two_a = 2 * $a;
1244 21         53 my $delta_sq = ($b * $b - 3 * $a * $c)/(9 * $a * $a);
1245 21         64 my $h_sq = 4/9 * ($b * $b - 3 * $a * $c) * $delta_sq**2;
1246 21         30 my $dis = $yN * $yN - $h_sq;
1247 21         28 my $twothirds_pi = (2 * pi)/3;
1248              
1249             #
1250             ### cubic_roots() calculations...
1251             #### $two_a
1252             #### $delta_sq
1253             #### $h_sq
1254             #### $dis
1255             #
1256 21 100       54 if ($dis > $epsilon)
    100          
1257             {
1258             #
1259             ### Cubic branch 1, $dis is greater than 0...
1260             #
1261             # One real root, two complex roots.
1262             #
1263 10         27 my $dis_sqrt = sqrt($dis);
1264 10         67 my $r_p = $yN - $dis_sqrt;
1265 10         14 my $r_q = $yN + $dis_sqrt;
1266 10         24 my $p = cbrt( abs($r_p)/$two_a );
1267 10         72 my $q = cbrt( abs($r_q)/$two_a );
1268              
1269 10 100       56 $p = -$p if ($r_p > 0);
1270 10 100       32 $q = -$q if ($r_q > 0);
1271              
1272 10         19 $x[0] = $xN + $p + $q;
1273 10         27 $x[1] = $xN + $p * exp($twothirds_pi * i)
1274             + $q * exp(-$twothirds_pi * i);
1275 10         6434 $x[2] = ~$x[1];
1276             }
1277             elsif ($dis < -$epsilon)
1278             {
1279             #
1280             ### Cubic branch 2, $dis is less than 0...
1281             #
1282             # Three distinct real roots.
1283             #
1284 7         20 my $theta = acos(-$yN/sqrt($h_sq))/3;
1285 7         83 my $delta = sqrt($b * $b - 3 * $a * $c)/(3 * $a);
1286 7         38 my $two_d = 2 * $delta;
1287              
1288 7         26 @x = ($xN + $two_d * cos($theta),
1289             $xN + $two_d * cos($twothirds_pi - $theta),
1290             $xN + $two_d * cos($twothirds_pi + $theta));
1291             }
1292             else
1293             {
1294             #
1295             ### Cubic branch 3, $dis equals 0, within epsilon...
1296             #
1297             # abs($dis) <= $epsilon (effectively zero).
1298             #
1299             # Three real roots (two or three equal).
1300             #
1301 4         18 my $delta = cbrt($yN/$two_a);
1302              
1303 4         47 @x = ($xN + $delta, $xN + $delta, $xN - 2 * $delta);
1304             }
1305              
1306 21         438 $ascending_flag = $temp_ascending_flag;
1307 21         54 return @x;
1308             }
1309              
1310             =head3 quartic_roots()
1311              
1312             Gives the roots of the quartic equation
1313              
1314             ax**4 + bx**3 + cx**2 + dx + e = 0
1315              
1316             using Ferrari's method (see the L section below). Returns
1317             a four-element list. The first two elements will be either
1318             both real or both complex. The next two elements will also be alike in
1319             type.
1320              
1321             =cut
1322              
1323             sub quartic_roots
1324             {
1325 22 50   22 1 9198 my($e, $d, $c, $b, $a) = ($ascending_flag == 0)? reverse @_: @_;
1326 22         38 my @x = ();
1327              
1328 22 50       53 if (abs($a) < $epsilon)
1329             {
1330 0         0 carp "Coefficient of highest power must not be zero!\n";
1331 0         0 return @x;
1332             }
1333              
1334             #
1335             # We're calling exported functions that also check
1336             # the $ascending_flag. To avoid reversing the reversed,
1337             # temporarily set the flag to one and reset before returning.
1338             #
1339 22         30 my $temp_ascending_flag = $ascending_flag;
1340 22         31 $ascending_flag = 1;
1341              
1342 22 50       46 if (abs($e) < $epsilon)
1343             {
1344 0         0 @x = cubic_roots($d, $c, $b, $a);
1345 0         0 $ascending_flag = $temp_ascending_flag;
1346 0         0 return (0, @x);
1347             }
1348              
1349             #
1350             # First step: Divide by the leading coefficient.
1351             #
1352 22         35 $b /= $a;
1353 22         30 $c /= $a;
1354 22         31 $d /= $a;
1355 22         30 $e /= $a;
1356              
1357             #
1358             # Second step: simplify the equation to the
1359             # "resolvent cubic" y**4 + fy**2 + gy + h.
1360             #
1361             # (This is done by setting x = y - b/4).
1362             #
1363 22         34 my $b4 = $b/4;
1364              
1365             #
1366             # The f, g, and h values are:
1367             #
1368 22         49 my $f = $c -
1369             6 * $b4 * $b4;
1370 22         50 my $g = $d +
1371             2 * $b4 * (-$c + 4 * $b4 * $b4);
1372 22         55 my $h = $e +
1373             $b4 * (-$d + $b4 * ($c - 3 * $b4 * $b4));
1374              
1375             #
1376             ### quartic_roots calculations
1377             #### $b4
1378             #### $f
1379             #### $g
1380             #### $h
1381             #
1382 22 100       62 if (abs($h) < $epsilon)
    100          
1383             {
1384             #
1385             ### Quartic branch 1, $h equals 0, within epsilon...
1386             #
1387             # Special case: h == 0. We have a cubic times y.
1388             #
1389 2         7 @x = (0, cubic_roots($g, $f, 0, 1));
1390             }
1391             elsif (abs($g * $g) < $epsilon)
1392             {
1393             #
1394             ### Quartic branch 2, $g equals 0, within epsilon...
1395             #
1396             # Another special case: g == 0. We have a quadratic
1397             # with y-squared.
1398             #
1399             # (We check $g**2 because that's what the constant
1400             # value actually is in Ferrari's method, and it is
1401             # possible for $g to be outside of epsilon while
1402             # $g**2 is inside, i.e., "zero").
1403             #
1404 16         37 my($p, $q) = quadratic_roots($h, $f, 1);
1405 16         1066 $p = sqrt($p);
1406 16         765 $q = sqrt($q);
1407 16         886 @x = ($p, -$p, $q, -$q);
1408             }
1409             else
1410             {
1411             #
1412             ### Quartic branch 3, Ferrari's method...
1413             #
1414             # Special cases don't apply, so continue on with Ferrari's
1415             # method. This involves setting up the resolvent cubic
1416             # as the product of two quadratics.
1417             #
1418             # After setting up conditions that guarantee that the
1419             # coefficients come out right (including the zero value
1420             # for the third-power term), we wind up with a 6th
1421             # degree polynomial with, fortunately, only even-powered
1422             # terms. In other words, a cubic with z = y**2.
1423             #
1424             # Take a root of that equation, and get the
1425             # quadratics from it.
1426             #
1427 4         18 my $z;
1428 4         15 ($z, undef, undef) = cubic_roots(-$g*$g, $f*$f - 4*$h, 2*$f, 1);
1429              
1430             #### $z
1431              
1432 4         16 my $alpha = sqrt($z);
1433 4         72 my $rho = $g/$alpha;
1434 4         55 my $beta = ($f + $z - $rho)/2;
1435 4         136 my $gamma = ($f + $z + $rho)/2;
1436              
1437 4         130 @x = quadratic_roots($beta, $alpha, 1);
1438 4         176 push @x, quadratic_roots($gamma, -$alpha, 1);
1439             }
1440              
1441 22         1228 $ascending_flag = $temp_ascending_flag;
1442 22         65 return ($x[0] - $b4, $x[1] - $b4, $x[2] - $b4, $x[3] - $b4);
1443             }
1444              
1445             =head2 Sturm Functions
1446              
1447             These are the functions that create and make use of the Sturm sequence.
1448             They are all exported under the tag "sturm".
1449              
1450             =head3 poly_real_root_count()
1451              
1452             Return the number of I, I roots of the polynomial.
1453              
1454             $unique_roots = poly_real_root_count(@coefficients);
1455              
1456             For example, the equation C<(x + 3)**3> forms the polynomial
1457             C, but since all three of its roots are identical,
1458             C will return 1.
1459              
1460             Likewise, C will return 0 because the two roots
1461             of C are both complex.
1462              
1463             This function is the all-in-one function to use instead of
1464              
1465             my @chain = poly_sturm_chain(@coefficients);
1466              
1467             return sturm_sign_count(sturm_sign_minus_inf(\@chain)) -
1468             sturm_sign_count(sturm_sign_plus_inf(\@chain));
1469              
1470             if you don't intend to use the Sturm chain for anything else.
1471              
1472             =cut
1473              
1474             sub poly_real_root_count
1475             {
1476 17     17 1 5244 my @coefficients = @_;
1477              
1478 17         32 my @chain = poly_sturm_chain(@coefficients);
1479              
1480 17         30 return sturm_sign_count(sturm_sign_minus_inf(\@chain)) -
1481             sturm_sign_count(sturm_sign_plus_inf(\@chain));
1482             }
1483              
1484             =head3 sturm_real_root_range_count()
1485              
1486             Return the number of I, I roots of the polynomial between two X values.
1487              
1488             my($x0, $x1) = (0, 1000);
1489              
1490             my @chain = poly_sturm_chain(@coefficients);
1491             $root_count = sturm_real_root_range_count(\@chain, $x0, $x1);
1492              
1493             This is equivalent to:
1494              
1495             my($x0, $x1) = (0, 1000);
1496              
1497             my @chain = poly_sturm_chain(@coefficients);
1498             my @signs = sturm_sign_chain(\@chain, [$x0, $x1]);
1499             $root_count = sturm_sign_count(@{$signs[0]}) - sturm_sign_count(@{$signs[1]});
1500              
1501             =cut
1502              
1503             sub sturm_real_root_range_count
1504             {
1505 156     156 1 264 my($chain_ref, $x0, $x1) = @_;
1506              
1507 156         293 my @signs = sturm_sign_chain($chain_ref, [$x0, $x1]);
1508              
1509 156         207 my $count0 = sturm_sign_count(@{$signs[0]});
  156         243  
1510 156         167 my $count1 = sturm_sign_count(@{$signs[1]});
  156         212  
1511              
1512             #
1513             ###### (from, to): join(", ", ($x0, $x1))
1514             ###### sign count from: $count0
1515             ###### sign count to: $count1
1516             #
1517 156         281 return $count0 - $count1;
1518             }
1519              
1520              
1521             =head3 sturm_bisection()
1522              
1523             Finds the boundaries around the roots of a polynomial function,
1524             using the root count method of Sturm.
1525              
1526             @boundaries = sturm_bisection(\@chain, $from, $to);
1527              
1528             The elements of @boundaries will be a list of two-element arrays, each
1529             one bracketing a root.
1530              
1531             It will not bracket complex roots.
1532              
1533             This allows you to use a different root-finding function than laguerre(),
1534             which is the default function used by sturm_bisection_roots().
1535              
1536             =cut
1537              
1538             sub sturm_bisection
1539             {
1540 21     21 1 29 my($chain_ref, $from, $to) = @_;
1541 21         20 my(@coefficients) = @{${$chain_ref}[0]};
  21         20  
  21         33  
1542 21         21 my @boundaries;
1543              
1544             #
1545             #### @coefficients
1546             #
1547             #
1548             # If we have a linear equation, just solve the thing. We're not
1549             # going to find a useful second derivative, after all. (Which
1550             # would raise the question of why we're here without a useful
1551             # Sturm chain, but never mind...)
1552             #
1553 21 50       34 if ($#coefficients == 1)
1554             {
1555 0         0 my $root = linear_roots(@coefficients);
1556              
1557             #
1558             # But make sure the root is within the
1559             # asked-for range.
1560             #
1561 0 0 0     0 return () if ($root < $from or $root > $to);
1562 0         0 return ([$root, $root]);
1563             }
1564              
1565             #
1566             # Do Sturm bisection here.
1567             #
1568 21         31 my $range_count = sturm_real_root_range_count($chain_ref, $from, $to);
1569              
1570             #
1571             # If we're down to one root in this range, use Laguerre's method
1572             # to hunt it down.
1573             #
1574 21 50       40 return () if ($range_count == 0);
1575 21 100       50 return ([$from, $to]) if ($range_count == 1);
1576              
1577             #
1578             # More than one root in this range, so subdivide
1579             # until each root has its own range.
1580             #
1581 8         10 my $its = 0;
1582              
1583             ROOT:
1584 8         9 for (;;)
1585             {
1586 59         73 my $mid = ($to + $from)/2.0;
1587 59         78 my $frommid_count = sturm_real_root_range_count($chain_ref, $from, $mid);
1588 59         74 my $midto_count = sturm_real_root_range_count($chain_ref, $mid, $to);
1589              
1590             #
1591             #### $its
1592             #### $from
1593             #### $mid
1594             #### $to
1595             #### $frommid_count
1596             #### $midto_count
1597             #
1598              
1599             #
1600             # Bisect again if we only narrowed down to a range
1601             # containing all the roots.
1602             #
1603 59 100       84 if ($frommid_count == 0)
    100          
1604             {
1605 39         40 $from = $mid;
1606             }
1607             elsif ($midto_count == 0)
1608             {
1609 12         14 $to = $mid;
1610             }
1611             else
1612             {
1613             #
1614             # We've divided the roots between two ranges. Do it
1615             # again until each range has a single root in it.
1616             #
1617 8         21 push @boundaries, sturm_bisection($chain_ref, $from, $mid);
1618 8         15 push @boundaries, sturm_bisection($chain_ref, $mid, $to);
1619 8         13 last ROOT;
1620             }
1621 51 50       87 croak "Too many iterations ($its) at mid=$mid\n" if ($its >= $iteration{sturm_bisection});
1622 51         55 $its++;
1623             }
1624 8         17 return @boundaries;
1625             }
1626              
1627              
1628             =head3 sturm_bisection_roots()
1629              
1630             Return the I roots counted by L.
1631             Uses L to bracket the roots of the polynomial,
1632             then uses L to close in on each root.
1633              
1634             my($from, $to) = (-1000, 0);
1635             my @chain = poly_sturm_chain(@coefficients);
1636             my @roots = sturm_bisection_roots(\@chain, $from, $to);
1637              
1638             As it is using the Sturm functions, it will find only the real roots.
1639              
1640             =cut
1641              
1642             sub sturm_bisection_roots
1643             {
1644 5     5 1 15 my($chain_ref, $from, $to) = @_;
1645 5         6 my $cref0 = ${$chain_ref}[0];
  5         7  
1646 5         7 my @boundaries = sturm_bisection($chain_ref, $from, $to);
1647 5         7 my @roots;
1648              
1649 5         6 my $temp_ascending_flag = $ascending_flag;
1650 5         6 $ascending_flag = 1;
1651              
1652             #
1653             #### sturm_bisection() returns: @boundaries
1654             #
1655 5         15 for my $bracket (@boundaries)
1656             {
1657 13         19 my ($left, $right) = @$bracket;
1658 13         25 push @roots, laguerre($cref0, ($left + $right)/2.0);
1659             }
1660              
1661 5         12 $ascending_flag = $temp_ascending_flag;
1662              
1663 5         17 return @roots;
1664             }
1665              
1666              
1667             =head3 poly_sturm_chain()
1668              
1669             Returns the chain of Sturm functions used to evaluate the number of roots of a
1670             polynomial in a range of X values. The chain is a list of coefficient
1671             references, the coefficients being stored in ascending order.
1672              
1673             If you feed in a sequence of X values to the Sturm functions, you can tell where
1674             the (real, not complex) roots of the polynomial are by counting the number of
1675             times the Y values change sign.
1676              
1677             See L above for an example of its use.
1678              
1679             =cut
1680              
1681             sub poly_sturm_chain
1682             {
1683 55     55 1 13148 my @coefficients = @_;
1684 55         89 my $degree = $#coefficients;
1685 55         148 my (@chain, @remd);
1686 55         0 my ($f1, $f2);
1687              
1688 55 100       110 @coefficients = reverse @coefficients unless ($ascending_flag);
1689              
1690 55         110 $f1 = [@coefficients];
1691 55         148 $f2 = pl_derivative(\@coefficients);
1692              
1693             #
1694             # The first link of the chain.
1695             #
1696 55         659 push @chain, $f1;
1697 55 100       117 push @chain, $f2 if ($degree > 0);
1698              
1699 55 100       102 if ($degree > 1)
1700             {
1701             #
1702             ###### poly_sturm_chain chain before do loop:
1703             ###### @chain
1704             #
1705             do
1706 49         70 {
1707 77         169 my ($q, $r) = pl_div($f1, $f2);
1708              
1709             #
1710             # Remove any leading zeros in the remainder.
1711             #
1712 77         2341 @remd = @{$r};
  77         133  
1713 77   100     354 pop @remd while (@remd and abs($remd[$#remd]) < $epsilon);
1714              
1715 77         120 $f1 = $f2;
1716 77 100       151 $f2 = (@remd)? [map {$_ * -1} @remd]: [0];
  103         208  
1717 77         229 push @chain, $f2;
1718             }
1719             while ($#remd > 0);
1720             }
1721              
1722             #
1723             ###### poly_sturm_chain:
1724             ###### @chain
1725             #
1726 55         152 return @chain;
1727             }
1728              
1729             =head3 sturm_sign_count()
1730              
1731             Counts and returns the number of sign changes in a sequence of signs,
1732             such as those returned by the L
1733              
1734             See L and L for
1735             examples of its use.
1736              
1737             =cut
1738              
1739             sub sturm_sign_count
1740             {
1741 346     346 1 453 my @sign_seq = @_;
1742 346         372 my $scnt = 0;
1743              
1744 346         359 my $s1 = shift @sign_seq;
1745 346         423 for my $s2 (@sign_seq)
1746             {
1747 1060 100       1399 $scnt++ if ($s1 != $s2);
1748 1060         1198 $s1 = $s2;
1749             }
1750              
1751 346         551 return $scnt;
1752             }
1753              
1754              
1755             =head3 Sturm Sign Sequence Functions
1756              
1757             =head4 sturm_sign_chain()
1758              
1759             =head4 sturm_sign_minus_inf()
1760              
1761             =head4 sturm_sign_plus_inf()
1762              
1763             These functions return the array of signs that are used by the functions
1764             L and L to find
1765             the number of real roots in a polynomial.
1766              
1767             In normal use you will probably never need to use them, unless you want
1768             to examine the internals of the Sturm functions:
1769              
1770             #
1771             # Examine the sign changes that occur at each endpoint of
1772             # the x range.
1773             #
1774             my(@coefficients) = (1, 4, 7, 23);
1775             my(@xvals) = (-12, 12);
1776              
1777             my @chain = poly_sturm_chain( @coefficients);
1778             my @signs = sturm_sign_chain(\@chain, \@xvals); # An array of arrays.
1779              
1780             print "\nPolynomial: [", join(", ", @coefficients), "]\n";
1781              
1782             for my $j (0..$#signs)
1783             {
1784             my @s = @{$signs[$j]};
1785             print $xval[$j], "\n",
1786             "\t", join(", ", @s), "], sign count = ",
1787             sturm_sign_count(@s), "\n\n";
1788             }
1789              
1790             Similar examinations can be made at plus and minus infinity:
1791              
1792             #
1793             # Examine the sign changes that occur between plus and minus
1794             # infinity.
1795             #
1796             my @coefficients = (1, 4, 7, 23);
1797              
1798             my @chain = poly_sturm_chain( @coefficients);
1799             my @smi = sturm_sign_minus_inf(\@chain);
1800             my @spi = sturm_sign_plus_inf(\@chain);
1801              
1802             print "\nPolynomial: [", join(", ", @coefficients), "]\n";
1803              
1804             print "Minus Inf:\n",
1805             "\t", join(", ", @smi), "], sign count = ",
1806             sturm_sign_count(@smi), "\n\n";
1807              
1808             print "Plus Inf:\n",
1809             "\t", join(", ", @spi), "], sign count = ",
1810             sturm_sign_count(@spi), "\n\n";
1811              
1812             =cut
1813              
1814             #
1815             # @signs = sturm_minus_inf(\@chain);
1816             #
1817             # Return an array of signs from the chain at minus infinity.
1818             #
1819             # In the :sturm export set.
1820             #
1821             sub sturm_sign_minus_inf
1822             {
1823 17     17 1 21 my($chain_ref) = @_;
1824 17         18 my @signs;
1825              
1826 17         26 for my $c (@$chain_ref)
1827             {
1828 56         160 my @coefficients = @$c;
1829 56 100       83 push @signs, sign($coefficients[$#coefficients]) *
1830             ((($#coefficients & 1) == 1)? -1: 1);
1831             }
1832              
1833 17         67 return @signs;
1834             }
1835              
1836             #
1837             # @signs = sturm_plus_inf(\@chain);
1838             #
1839             # Return an array of signs from the chain at infinity.
1840             #
1841             # In the :sturm export set.
1842             #
1843             sub sturm_sign_plus_inf
1844             {
1845 17     17 1 22 my($chain_ref) = @_;
1846 17         23 my @signs;
1847              
1848 17         26 for my $c (@$chain_ref)
1849             {
1850 56         187 my @coefficients = @$c;
1851 56         76 push @signs, sign($coefficients[$#coefficients]);
1852             }
1853              
1854 17         76 return @signs;
1855             }
1856              
1857             #
1858             # @sign_chains = sturm_sign_chain(\@chain, \@xvals);
1859             #
1860             # Return an array of signs for each x-value passed in each function in
1861             # the Sturm chain.
1862             #
1863             # In the :sturm export set.
1864             #
1865             sub sturm_sign_chain
1866             {
1867 156     156 1 197 my($chain_ref, $xvals_ref) = @_;
1868 156         184 my $fn_count = $#$chain_ref;
1869 156         187 my $x_count = $#$xvals_ref;
1870 156         169 my @sign_chain;
1871              
1872 156         337 push @sign_chain, [] for (0..$x_count);
1873              
1874 156         200 for my $p_ref (@$chain_ref)
1875             {
1876 647         991 my @ysigns = sign(pl_evaluate($p_ref, $xvals_ref));
1877              
1878             #
1879             # We just retrieved the signs of a single function across
1880             # our x-vals. We want it the other way around; signs listed
1881             # by x-val across functions.
1882             #
1883             # (list of lists)
1884             # |
1885             # v
1886             # f0 f1 f2 f3 f4 ...
1887             # x0 - - + - + (list 0)
1888             #
1889             # x1 + - - + + (list 1)
1890             #
1891             # x2 + - + + + (list 2)
1892             #
1893             # ...
1894             #
1895 647         12948 for my $j (0..$x_count)
1896             {
1897 1294         1324 push @{$sign_chain[$j]}, shift @ysigns;
  1294         1882  
1898             }
1899             }
1900              
1901             #
1902             ###### sturm_sign_chain() returns
1903             ###### @sign_chain: @sign_chain
1904             #
1905 156         236 return @sign_chain;
1906             }
1907              
1908              
1909             =head2 Utility Functions
1910              
1911             These are internal functions used by the other functions listed above
1912             that may also be useful to the user, or which affect the behavior of
1913             other functions. They are all exported under the tag "utility".
1914              
1915             =head3 epsilon()
1916              
1917             Returns the machine epsilon value that was calculated when this module was
1918             loaded.
1919              
1920             The value may be changed, although this in general is not recommended.
1921              
1922             my $old_epsilon = epsilon($new_epsilon);
1923              
1924             The previous value of epsilon may be saved to be restored later.
1925              
1926             The Wikipedia article at L has
1927             more information on the subject.
1928              
1929             =cut
1930              
1931             sub epsilon
1932             {
1933 0     0 1 0 my $eps = $epsilon;
1934 0 0       0 $epsilon = $_[0] if (scalar @_ > 0);
1935 0         0 return $eps;
1936             }
1937              
1938             =head3 laguerre()
1939              
1940             A numerical method for finding a root of an equation, especially made
1941             for polynomials.
1942              
1943             @roots = laguerre(\@coefficients, \@xvalues);
1944             push @roots, laguerre(\@coefficients, $another_xvalue);
1945              
1946             For each x value the function will attempt to find a root closest to it.
1947             The function will return real roots only.
1948              
1949             This is the function used by L after using
1950             L to narrow its search to a range containing a single
1951             root.
1952              
1953             =cut
1954              
1955             sub laguerre
1956             {
1957 17     17   164 no Math::Complex;
  17         46  
  17         5522  
1958 16     16 1 3479 my($p_ref, $xval_ref) = @_;
1959 16         23 my $n = $#$p_ref;
1960 16         22 my @xvalues;
1961             my @roots;
1962              
1963 16 50       28 $p_ref = [reverse @$p_ref] unless ($ascending_flag);
1964              
1965             #
1966             # Allow some flexibility in sending the x-values.
1967             #
1968 16 100       31 if (ref $xval_ref eq "ARRAY")
1969             {
1970 3         10 @xvalues = @$xval_ref;
1971             }
1972             else
1973             {
1974             #
1975             # It could happen. Someone might type \$x instead of $x.
1976             #
1977 13 50       19 @xvalues = ((ref $xval_ref eq "SCALAR")? $$xval_ref: $xval_ref);
1978             }
1979              
1980 16         32 for my $x (@xvalues)
1981             {
1982             #
1983             #### laguerre looking near: $x
1984             #### Coefficient: @$p_ref
1985             #### Degree: $n
1986             #
1987 21         28 my $its = 0;
1988              
1989             ROOT:
1990 21         25 for (;;)
1991             {
1992             #
1993             # Get the values of the function and its first and
1994             # second derivatives at X.
1995             #
1996 95         174 my($y, $dy, $d2y) = pl_dxevaluate($p_ref, $x);
1997              
1998 95 100       14858 if (abs($y) <= $tolerance{laguerre})
1999             {
2000 20         85 push @roots, $x;
2001 20         53 last ROOT;
2002             }
2003              
2004             #
2005             #### At Iteration: $its
2006             #### x: $x
2007             #### f(x): $y
2008             #### f'(x): $dy
2009             #### f''(x): $d2y
2010             #
2011 75         253 my $g = $dy/$y;
2012 75         616 my $h = $g * $g - $d2y/$y;
2013 75         1773 my $f = sqrt(($n - 1) * ($n * $h - $g*$g));
2014 75 100       3143 $f = - $f if (abs($g - $f) > abs($g + $f));
2015              
2016             #
2017             #### g: $g
2018             #### h: $h
2019             #### f: $f
2020             #
2021             # Divide by the largest value of $g plus
2022             # $f, bearing in mind that $f is the result
2023             # of a square root function and may be positive
2024             # or negative.
2025             #
2026             # Use the abs() function to determine size
2027             # since $g or $f may be complex numbers.
2028             #
2029 75         2388 my $dx = $n/($g + $f);
2030              
2031 75         1319 $x -= $dx;
2032 75 100       515 if (abs($dx) <= $tolerance{laguerre})
2033             {
2034 1         2 push @roots, $x;
2035 1         2 last ROOT;
2036             }
2037              
2038 74 50       303 croak "Too many iterations ($its) at dx=$dx\n" if ($its >= $iteration{laguerre});
2039 74         137 $its++;
2040             }
2041              
2042             ### root found at iteration $its
2043             #### $x
2044             }
2045              
2046 16         39 return @roots;
2047             }
2048              
2049              
2050             =head3 newtonraphson()
2051              
2052             Like L, a numerical method for finding a root of an equation.
2053              
2054             @roots = newtonraphson(\@coefficients, \@xvalues);
2055             push @roots, newtonraphson(\@coefficients, $another_xvalue);
2056              
2057             For each x value the function will attempt to find a root closest to it.
2058             The function will return real roots only.
2059              
2060             This function is provided as an alternative to laguerre(). It is not
2061             used internally by any other functions.
2062              
2063             =cut
2064              
2065             sub newtonraphson
2066             {
2067 17     17   123 no Math::Complex;
  17         34  
  17         10982  
2068 2     2 1 1293 my($p_ref, $xval_ref) = @_;
2069 2         3 my $n = $#$p_ref;
2070 2         5 my @xvalues;
2071             my @roots;
2072              
2073 2 50       4 $p_ref = [reverse @$p_ref] unless ($ascending_flag);
2074              
2075             #
2076             # Allow some flexibility in sending the x-values.
2077             #
2078 2 50       5 if (ref $xval_ref eq "ARRAY")
2079             {
2080 2         3 @xvalues = @$xval_ref;
2081             }
2082             else
2083             {
2084             #
2085             # It could happen. Someone might type \$x instead of $x.
2086             #
2087 0 0       0 @xvalues = ((ref $xval_ref eq "SCALAR")? $$xval_ref: $xval_ref);
2088             }
2089              
2090             #
2091             ### newtonraphson()
2092             #### @xvalues
2093             #
2094 2         4 for my $x (@xvalues)
2095             {
2096 6         6 my $its = 0;
2097              
2098             ROOT:
2099 6         6 for (;;)
2100             {
2101             #
2102             # Get the values of the function and its
2103             # first derivative at X.
2104             #
2105 40         49 my($y, $dy, undef) = pl_dxevaluate($p_ref, $x);
2106 40         639 my $dx = $y/$dy;
2107 40         41 $x -= $dx;
2108              
2109 40 100       59 if (abs($dx) <= $tolerance{newtonraphson})
2110             {
2111 6         7 push @roots, $x;
2112 6         10 last ROOT;
2113             }
2114              
2115             #
2116             #### At Iteration: $its
2117             #### x: $x
2118             #### f(x): $y
2119             #### f'(x): $dy
2120             #
2121 34 50       39 croak "Too many iterations ($its) at dx=$dx\n" if ($its >= $iteration{newtonraphson});
2122 34         33 $its++;
2123             }
2124              
2125             ### root found at iteration $its
2126             #### $x
2127             }
2128              
2129 2         6 return @roots;
2130             }
2131              
2132             =head3 poly_iteration()
2133              
2134             Sets the limit to the number of iterations that a solving method may go
2135             through before giving up trying to find a root. Each method of root-finding
2136             used by L, L, and L
2137             has its own iteration limit, which may be found, like L,
2138             simply by looking at the return value of poly_iteration().
2139              
2140             #
2141             # Get all of the current iteration limits.
2142             #
2143             my %its_limits = poly_iteration();
2144              
2145             #
2146             # Double the limit for the hessenberg method, but set the limit
2147             # for Laguerre's method to 20.
2148             #
2149             my %old_limits = poly_iteration(hessenberg => $its_limits{hessenberg} * 2,
2150             laguerre => 20);
2151              
2152             #
2153             # Reset the limits with the former values, but save the values we had
2154             # for later.
2155             #
2156             my %hl_limits = poly_iteration(%old_limits);
2157              
2158             There are iteration limit values for:
2159              
2160             =over 4
2161              
2162             =item 'hessenberg'
2163              
2164             The numeric method used by poly_roots(), if the hessenberg option is set.
2165             Its default value is 60.
2166              
2167             =item 'laguerre'
2168              
2169             The numeric method used by L. Laguerre's method is used within
2170             sturm_bisection_roots() once it has narrowed its search in on an individual
2171             root, and of course laguerre() may be called independently. Its default value
2172             is 60.
2173              
2174             =item 'newtonraphson'
2175              
2176             The numeric method used by newtonraphson(). The Newton-Raphson method is offered
2177             as an alternative to Laguerre's method. Its default value is 60.
2178              
2179             =item 'sturm_bisection'
2180              
2181             The bisection method used to find roots within a range. Its default value
2182             is 100.
2183              
2184             =back
2185              
2186             =cut
2187              
2188             sub poly_iteration
2189             {
2190 13     13 1 2169 my %limits = @_;
2191 13         24 my %old_limits;
2192              
2193 13 100       60 return %iteration if (scalar @_ == 0);
2194              
2195 6         19 for my $k (keys %limits)
2196             {
2197             #
2198             # If this is a real iteration limit, save its old
2199             # value, then set it.
2200             #
2201 6 50       20 if (exists $iteration{$k})
2202             {
2203 6         15 my $val = abs(int($limits{$k}));
2204            
2205 6 50       14 carp "poly_iteration(): Unreasonably small value for $k => $val\n" if ($val < 10);
2206              
2207 6         14 $old_limits{$k} = $iteration{$k};
2208 6         13 $iteration{$k} = $val;
2209             }
2210             else
2211             {
2212 0         0 croak "poly_iteration(): unknown key $k.";
2213             }
2214             }
2215              
2216 6         20 return %old_limits;
2217             }
2218              
2219             =head3 poly_tolerance()
2220              
2221             Set the degree of accuracy needed for comparisons to be equal or roots
2222             to be found. Amongst the root finding functions this currently only
2223             affects laguerre() and newtonraphson(), as the Hessenberg matrix method
2224             determines how close it needs to get using a complicated formula based
2225             on L.
2226              
2227             #
2228             # Print the tolerances.
2229             #
2230             my %tolerances = poly_tolerance();
2231             print "Default tolerances:\n";
2232             for my $k (keys %tolerances)
2233             {
2234             print "$k => ", $tolerances{$k}, "\n";
2235             }
2236              
2237             #
2238             # Quadruple the tolerance for Laguerre's method.
2239             #
2240             poly_tolerance(laguerre => 4 * $tolerances{laguerre});
2241              
2242             Tolerances may be set for:
2243              
2244             =over 4
2245              
2246             =item 'laguerre'
2247              
2248             The numeric method used by laguerre(). Laguerre's method is used within
2249             sturm_bisection_roots() once an individual root has been found within a
2250             range, and of course it may be called independently.
2251              
2252             =item 'newtonraphson'
2253              
2254             The numeric method used by newtonraphson(). Newton-Raphson is, like
2255             Laguerre's method, a method for finding a root near the starting X value.
2256              
2257             =back
2258              
2259             =cut
2260              
2261             sub poly_tolerance
2262             {
2263 5     5 1 964 my %tols = @_;
2264 5         9 my %old_tols;
2265              
2266 5 100       25 return %tolerance if (scalar @_ == 0);
2267              
2268 2         8 for my $k (keys %tols)
2269             {
2270             #
2271             # If this is a real tolerance limit, save its old
2272             # value, then set it.
2273             #
2274 2 50       7 if (exists $tolerance{$k})
2275             {
2276 2         8 my $val = abs($tols{$k});
2277              
2278 2         5 $old_tols{$k} = $tolerance{$k};
2279 2         5 $tolerance{$k} = $val;
2280             }
2281             else
2282             {
2283 0         0 croak "poly_tolerance(): unknown key $k.";
2284             }
2285             }
2286              
2287 2         7 return %old_tols;
2288             }
2289              
2290             =head3 poly_nonzero_term_count()
2291              
2292             Returns a simple count of the number of coefficients that aren't zero
2293             (zero meaning between -epsilon and epsilon).
2294              
2295             =cut
2296              
2297             sub poly_nonzero_term_count
2298             {
2299 39     39 1 102078 my(@coefficients) = @_;
2300 39         64 my $nzc = 0;
2301              
2302 39         102 for my $j (0..$#coefficients)
2303             {
2304 227 100       428 $nzc++ if (abs($coefficients[$j]) > $epsilon);
2305             }
2306 39         123 return $nzc;
2307             }
2308              
2309             END {
2310 17 50   17   40819 unless ($coeff_order_set)
2311             {
2312 0         0 warn "Your coefficient order is in a default state, which will change by version 3.00.\n\n",
2313             "Please put\n",
2314             " coefficients order => 'descending';\n",
2315             sprintf("at the beginning of file %s to make\n", (caller())[1]),
2316             "sure your function parameters will be in the correct order when the\n",
2317             "default order changes.\n\n",
2318             "See the README file and the Math::Polynomial::Solve documentation for\n",
2319             "more information.\n",
2320             }
2321             }
2322              
2323             1;
2324             __END__