nonlin 1.5.2
A library that provides routines to compute the solutions to systems of nonlinear equations.
Loading...
Searching...
No Matches
nonlin_polynomials Module Reference

polynomials More...

Data Types

interface  assignment(=)
 Defines polynomial assignment. More...
 
interface  operator(*)
 Defines polynomial multiplication. More...
 
interface  operator(+)
 Defines polynomial addition. More...
 
interface  operator(-)
 Defines polynomial subtraction. More...
 
type  polynomial
 Defines a polynomial, and associated routines for performing polynomial operations. More...
 

Functions/Subroutines

subroutine init_poly (this, order, err)
 Initializes the polynomial instance, and sets all coefficients to zero.
 
subroutine init_poly_coeffs (this, c, err)
 Initializes the polynomial instance.
 
pure integer(int32) function get_poly_order (this)
 Returns the order of the polynomial object.
 
subroutine poly_fit (this, x, y, order, err)
 Fits a polynomial of the specified order to a data set.
 
subroutine poly_fit_thru_zero (this, x, y, order, err)
 Fits a polynomial of the specified order that passes through zero to a data set.
 
elemental real(real64) function poly_eval_double (this, x)
 Evaluates a polynomial at the specified points.
 
elemental complex(real64) function poly_eval_complex (this, x)
 Evaluates a polynomial at the specified points.
 
pure real(real64) function, dimension(this%order(), this%order()) poly_companion_mtx (this)
 Returns the companion matrix for the polynomial.
 
complex(real64) function, dimension(this%order()) poly_roots (this, err)
 Computes all the roots of a polynomial by computing the eigenvalues of the polynomial companion matrix.
 
real(real64) function get_poly_coefficient (this, ind, err)
 Gets the requested polynomial coefficient by index. The coefficient index is established as follows: c(1) + c(2) * x + c(3) * x**2 + ... c(n) * x**n-1.
 
pure real(real64) function, dimension(this%order()+1) get_poly_coefficients (this)
 Gets an array containing all the coefficients of the polynomial. The coefficient index is established as follows: c(1) + c(2) * x + c(3) * x**2 + ... c(n) * x**n-1.
 
subroutine set_poly_coefficient (this, ind, c, err)
 Sets the requested polynomial coefficient by index. The coefficient index is established as follows: c(1) + c(2) * x + c(3) * x**2 + ... c(n) * x**n-1.
 
subroutine poly_equals (x, y)
 Assigns the contents of one polynomial to another.
 
subroutine poly_dbl_equals (x, y)
 Assigns a number to each coefficient of the polynomial.
 
subroutine poly_equals_array (x, y)
 Assigns the contents of an array as polynomial coefficients.
 
type(polynomial) function poly_poly_add (x, y)
 Adds two polynomials.
 
type(polynomial) function poly_poly_subtract (x, y)
 Subtracts two polynomials.
 
type(polynomial) function poly_poly_mult (x, y)
 Multiplies two polynomials.
 
type(polynomial) function poly_dbl_mult (x, y)
 Multiplies a polynomial by a scalar value.
 
type(polynomial) function dbl_poly_mult (x, y)
 Multiplies a polynomial by a scalar value.
 

Detailed Description

polynomials

Purpose
Provides a means of defining and operating on polynomials.

Function/Subroutine Documentation

◆ dbl_poly_mult()

type(polynomial) function nonlin_polynomials::dbl_poly_mult ( real(real64), intent(in) x,
class(polynomial), intent(in) y )
private

Multiplies a polynomial by a scalar value.

Parameters
[in]xThe scalar value.
[in]yThe polynomial.
Returns
The resulting polynomial.

Definition at line 988 of file nonlin_polynomials.f90.

◆ get_poly_coefficient()

real(real64) function nonlin_polynomials::get_poly_coefficient ( class(polynomial), intent(in) this,
integer(int32), intent(in) ind,
class(errors), intent(inout), optional, target err )
private

Gets the requested polynomial coefficient by index. The coefficient index is established as follows: c(1) + c(2) * x + c(3) * x**2 + ... c(n) * x**n-1.

Parameters
[in]thisThe polynomial.
[in]indThe polynomial coefficient index (0 < ind <= order + 1).
[out]errAn optional errors-based object that if provided can be used to retrieve information relating to any errors encountered during execution. If not provided, a default implementation of the errors class is used internally to provide error handling. Possible errors and warning messages that may be encountered are as follows.
  • NL_INVALID_INPUT_ERROR: Occurs if the requested index is less than or equal to zero, or if the requested index exceeds the number of polynomial coefficients.
Returns
The requested coefficient.

Definition at line 655 of file nonlin_polynomials.f90.

◆ get_poly_coefficients()

pure real(real64) function, dimension(this%order() + 1) nonlin_polynomials::get_poly_coefficients ( class(polynomial), intent(in) this)
private

Gets an array containing all the coefficients of the polynomial. The coefficient index is established as follows: c(1) + c(2) * x + c(3) * x**2 + ... c(n) * x**n-1.

Parameters
[in]thisThe polynomial object.
Returns
The array of coefficients.

Definition at line 698 of file nonlin_polynomials.f90.

◆ get_poly_order()

pure integer(int32) function nonlin_polynomials::get_poly_order ( class(polynomial), intent(in) this)
private

Returns the order of the polynomial object.

Parameters
[in]thisThe polynomial object.
Returns
The order of the polynomial. Returns -1 in the event no polynomial coefficients have been defined.

Definition at line 203 of file nonlin_polynomials.f90.

◆ init_poly()

subroutine nonlin_polynomials::init_poly ( class(polynomial), intent(inout) this,
integer(int32), intent(in) order,
class(errors), intent(inout), optional, target err )

Initializes the polynomial instance, and sets all coefficients to zero.

Parameters
[in,out]thisThe polynomial object.
[in]orderThe order of the polynomial (must be >= 0).
[out]errAn optional errors-based object that if provided can be used to retrieve information relating to any errors encountered during execution. If not provided, a default implementation of the errors class is used internally to provide error handling. Possible errors and warning messages that may be encountered are as follows.
  • NL_INVALID_INPUT_ERROR: Occurs if a zero or negative polynomial order was specified.
  • NL_OUT_OF_MEMORY_ERROR: Occurs if insufficient memory is available.

Definition at line 110 of file nonlin_polynomials.f90.

◆ init_poly_coeffs()

subroutine nonlin_polynomials::init_poly_coeffs ( class(polynomial), intent(inout) this,
real(real64), dimension(:), intent(in) c,
class(errors), intent(inout), optional, target err )
private

Initializes the polynomial instance.

Parameters
[in,out]thisThe polynomial object.
[in]cThe array of polynomial coefficients. The coefficients are established as follows: c(1) + c(2) * x + c(3) * x**2 + ... c(n) * x**n-1.
[out]errAn optional errors-based object that if provided can be used to retrieve information relating to any errors encountered during execution. If not provided, a default implementation of the errors class is used internally to provide error handling. Possible errors and warning messages that may be encountered are as follows.
  • NL_INVALID_INPUT_ERROR: Occurs if a zero or negative polynomial order was specified.
  • NL_OUT_OF_MEMORY_ERROR: Occurs if insufficient memory is available.

Definition at line 167 of file nonlin_polynomials.f90.

◆ poly_companion_mtx()

pure real(real64) function, dimension(this%order(), this%order()) nonlin_polynomials::poly_companion_mtx ( class(polynomial), intent(in) this)
private

Returns the companion matrix for the polynomial.

Parameters
[in]thisThe polynomial object.
Returns
The companion matrix.
See Also

Definition at line 529 of file nonlin_polynomials.f90.

◆ poly_dbl_equals()

subroutine nonlin_polynomials::poly_dbl_equals ( class(polynomial), intent(inout) x,
real(real64), intent(in) y )
private

Assigns a number to each coefficient of the polynomial.

Parameters
[in,out]xThe assignee.
[in]yThe value to assign.

Definition at line 786 of file nonlin_polynomials.f90.

◆ poly_dbl_mult()

type(polynomial) function nonlin_polynomials::poly_dbl_mult ( class(polynomial), intent(in) x,
real(real64), intent(in) y )
private

Multiplies a polynomial by a scalar value.

Parameters
[in]xThe polynomial.
[in]yThe scalar value.
Returns
The resulting polynomial.

Definition at line 964 of file nonlin_polynomials.f90.

◆ poly_equals()

subroutine nonlin_polynomials::poly_equals ( class(polynomial), intent(inout) x,
class(polynomial), intent(in) y )
private

Assigns the contents of one polynomial to another.

Parameters
[in,out]xThe assignee.
[in]yThe polynomial to copy

Definition at line 765 of file nonlin_polynomials.f90.

◆ poly_equals_array()

subroutine nonlin_polynomials::poly_equals_array ( class(polynomial), intent(inout) x,
real(real64), dimension(:), intent(in) y )
private

Assigns the contents of an array as polynomial coefficients.

Parameters
[in,out]xThe assignee.
[in]yThe coefficient array.

Definition at line 806 of file nonlin_polynomials.f90.

◆ poly_eval_complex()

elemental complex(real64) function nonlin_polynomials::poly_eval_complex ( class(polynomial), intent(in) this,
complex(real64), intent(in) x )
private

Evaluates a polynomial at the specified points.

Parameters
[in]thisThe polynomial object.
[in]xThe value(s) at which to evaluate the polynomial.
Returns
The value(s) of the polynomial at x.

Definition at line 489 of file nonlin_polynomials.f90.

◆ poly_eval_double()

elemental real(real64) function nonlin_polynomials::poly_eval_double ( class(polynomial), intent(in) this,
real(real64), intent(in) x )
private

Evaluates a polynomial at the specified points.

Parameters
[in]thisThe polynomial object.
[in]xThe value(s) at which to evaluate the polynomial.
Returns
The value(s) of the polynomial at x.

Definition at line 452 of file nonlin_polynomials.f90.

◆ poly_fit()

subroutine nonlin_polynomials::poly_fit ( class(polynomial), intent(inout) this,
real(real64), dimension(:), intent(in) x,
real(real64), dimension(:), intent(inout) y,
integer(int32), intent(in) order,
class(errors), intent(inout), optional, target err )
private

Fits a polynomial of the specified order to a data set.

Parameters
[in,out]thisThe polynomial object.
[in]xAn N-element array containing the independent variable data points. Notice, must be N > order.
[in,out]yOn input, an N-element array containing the dependent variable data points. On output, the contents are overwritten.
[in]orderThe order of the polynomial (must be >= 1).
[out]errAn optional errors-based object that if provided can be used to retrieve information relating to any errors encountered during execution. If not provided, a default implementation of the errors class is used internally to provide error handling. Possible errors and warning messages that may be encountered are as follows.
  • NL_INVALID_INPUT_ERROR: Occurs if a zero or negative polynomial order was specified, or if order is too large for the data set.
  • NL_OUT_OF_MEMORY_ERROR: Occurs if insufficient memory is available.
  • NL_ARRAY_SIZE_ERROR: Occurs if x and y are different sizes.
Usage
The following code provides an example of how to fit a polynomial to a set of data.
program example
use linalg_constants, only : dp, i32
! Local Variables
real(real64), dimension(21) :: xp, yp, yf, yc, err
real(real64) :: res
type(polynomial) :: p
! Data to fit
xp = [0.0d0, 0.1d0, 0.2d0, 0.3d0, 0.4d0, 0.5d0, 0.6d0, 0.7d0, 0.8d0, &
0.9d0, 1.0d0, 1.1d0, 1.2d0, 1.3d0, 1.4d0, 1.5d0, 1.6d0, 1.7d0, &
1.8d0, 1.9d0, 2.0d0]
yp = [1.216737514d0, 1.250032542d0, 1.305579195d0, 1.040182335d0, &
1.751867738d0, 1.109716707d0, 2.018141531d0, 1.992418729d0, &
1.807916923d0, 2.078806005d0, 2.698801324d0, 2.644662712d0, &
3.412756702d0, 4.406137221d0, 4.567156645d0, 4.999550779d0, &
5.652854194d0, 6.784320119d0, 8.307936836d0, 8.395126494d0, &
10.30252404d0]
! Create a copy of yp as it will be overwritten in the fit command
yc = yp
! Fit the polynomial
call p%fit(xp, yp, 3)
! Evaluate the polynomial at xp, and then determine the residual
yf = p%evaluate(xp)
err = abs(yf - yc)
res = maxval(err)
! Print out the coefficients
print '(A)', "Polynomial Coefficients (c0 + c1*x + c2*x**2 + c3*x**3):"
do i = 1, 4
print '(AI0AF12.9)', "c", i - 1, " = ", p%get(i)
end do
print '(AE9.4)', "Residual: ", res
end program
The above program returns the following results.
Polynomial Coefficients (c0 + c1*x + c2*x**2 + c3*x**3):
c0 = 1.186614186
c1 = 0.446613631
c2 = -0.122320499
c3 = 1.064762822
Residual: .5064E+00

Definition at line 284 of file nonlin_polynomials.f90.

◆ poly_fit_thru_zero()

subroutine nonlin_polynomials::poly_fit_thru_zero ( class(polynomial), intent(inout) this,
real(real64), dimension(:), intent(in) x,
real(real64), dimension(:), intent(inout) y,
integer(int32), intent(in) order,
class(errors), intent(inout), optional, target err )
private

Fits a polynomial of the specified order that passes through zero to a data set.

Parameters
[in,out]thisThe polynomial object.
[in]xAn N-element array containing the independent variable data points. Notice, must be N > order.
[in,out]yOn input, an N-element array containing the dependent variable data points. On output, the contents are overwritten.
[in]orderThe order of the polynomial (must be >= 1).
[out]errAn optional errors-based object that if provided can be used to retrieve information relating to any errors encountered during execution. If not provided, a default implementation of the errors class is used internally to provide error handling. Possible errors and warning messages that may be encountered are as follows.
  • NL_INVALID_INPUT_ERROR: Occurs if a zero or negative polynomial order was specified, or if order is too large for the data set.
  • NL_OUT_OF_MEMORY_ERROR: Occurs if insufficient memory is available.
  • NL_ARRAY_SIZE_ERROR: Occurs if x and y are different sizes.

Definition at line 375 of file nonlin_polynomials.f90.

◆ poly_poly_add()

type(polynomial) function nonlin_polynomials::poly_poly_add ( class(polynomial), intent(in) x,
class(polynomial), intent(in) y )
private

Adds two polynomials.

Parameters
[in]xThe left-hand-side argument.
[in]yThe right-hand-side argument.
Returns
The resulting polynomial.

Definition at line 820 of file nonlin_polynomials.f90.

◆ poly_poly_mult()

type(polynomial) function nonlin_polynomials::poly_poly_mult ( class(polynomial), intent(in) x,
class(polynomial), intent(in) y )
private

Multiplies two polynomials.

Parameters
[in]xThe left-hand-side argument.
[in]yThe right-hand-side argument.
Returns
The resulting polynomial.

Definition at line 934 of file nonlin_polynomials.f90.

◆ poly_poly_subtract()

type(polynomial) function nonlin_polynomials::poly_poly_subtract ( class(polynomial), intent(in) x,
class(polynomial), intent(in) y )
private

Subtracts two polynomials.

Parameters
[in]xThe left-hand-side argument.
[in]yThe right-hand-side argument.
Returns
The resulting polynomial.

Definition at line 877 of file nonlin_polynomials.f90.

◆ poly_roots()

complex(real64) function, dimension(this%order()) nonlin_polynomials::poly_roots ( class(polynomial), intent(in) this,
class(errors), intent(inout), optional, target err )
private

Computes all the roots of a polynomial by computing the eigenvalues of the polynomial companion matrix.

Parameters
[in]thisThe polynomial object.
[out]errAn optional errors-based object that if provided can be used to retrieve information relating to any errors encountered during execution. If not provided, a default implementation of the errors class is used internally to provide error handling. Possible errors and warning messages that may be encountered are as follows.
  • NL_OUT_OF_MEMORY_ERROR: Occurs if local memory must be allocated, and there is insufficient memory available.
  • NL_CONVERGENCE_ERROR: Occurs if the algorithm failed to converge.
Usage
The following code provides an example of how to compute the roots of a polynomial. This examples uses a tenth order polynomial; however, this process is applicable to any order.
program example
use linalg_constants, only : dp, i32
! Parameters
integer(int32), parameter :: order = 10
! Local Variables
integer(int32) :: i
type(polynomial) :: p
real(real64), dimension(order+1) :: coeff
complex(real64), allocatable, dimension(:) :: rts, sol
! Define the polynomial
call random_number(coeff)
call p%initialize(order)
do i = 1, size(coeff)
call p%set(i, coeff(i))
end do
! Compute the roots via the polynomial routine
rts = p%roots()
! Compute the value of the polynomial at each root and ensure it
! is sufficiently close to zero.
sol = p%evaluate(rts)
do i = 1, size(sol)
print '(AE9.3AE9.3A)', "(", real(sol(i)), ", ", aimag(sol(i)), ")"
end do
end program
The above program returns the following results.
(-.466E-14, -.161E-14)
(-.466E-14, 0.161E-14)
(-.999E-15, 0.211E-14)
(-.999E-15, -.211E-14)
(0.444E-15, 0.108E-14)
(0.444E-15, -.108E-14)
(-.144E-14, -.433E-14)
(-.144E-14, 0.433E-14)
(0.644E-14, -.100E-13)
(0.644E-14, 0.100E-13)

Definition at line 614 of file nonlin_polynomials.f90.

◆ set_poly_coefficient()

subroutine nonlin_polynomials::set_poly_coefficient ( class(polynomial), intent(inout) this,
integer(int32), intent(in) ind,
real(real64), intent(in) c,
class(errors), intent(inout), optional, target err )
private

Sets the requested polynomial coefficient by index. The coefficient index is established as follows: c(1) + c(2) * x + c(3) * x**2 + ... c(n) * x**n-1.

Parameters
[in,out]thisThe polynomial.
[in]indThe polynomial coefficient index (0 < ind <= order + 1).
[in]cThe polynomial coefficient.
[out]errAn optional errors-based object that if provided can be used to retrieve information relating to any errors encountered during execution. If not provided, a default implementation of the errors class is used internally to provide error handling. Possible errors and warning messages that may be encountered are as follows.
  • NL_INVALID_INPUT_ERROR: Occurs if the requested index is less than or equal to zero, or if the requested index exceeds the number of polynomial coefficients.

Definition at line 724 of file nonlin_polynomials.f90.