nonlin 1.5.2
A library that provides routines to compute the solutions to systems of nonlinear equations.
Loading...
Searching...
No Matches
nonlin_core::vecfcn_helper Type Reference

Defines a type capable of encapsulating a system of nonlinear equations of the form: F(X) = 0. This type is used to establish the system of equations to solve, and provides a means for computing the Jacobian matrix for the system of equations, and any other ancillary operations that may be needed by the solver. More...

Public Member Functions

procedure, public set_fcn vfh_set_fcn
 Establishes a pointer to the routine containing the system of equations to solve.
 
procedure, public set_jacobian vfh_set_jac
 Establishes a pointer to the routine for computing the Jacobian matrix of the system of equations. If no routine is defined, the Jacobian matrix will be computed numerically (this is the default state).
 
procedure, public is_fcn_defined vfh_is_fcn_defined
 Tests if the pointer to the subroutine containing the system of equations to solve has been assigned.
 
procedure, public is_jacobian_defined vfh_is_jac_defined
 Tests if the pointer to the subroutine containing the system of equations to solve has been assigned.
 
procedure, public fcn vfh_fcn
 Executes the routine containing the system of equations to solve. No action is taken if the pointer to the subroutine has not been defined.
 
procedure, public jacobian vfh_jac_fcn
 Executes the routine containing the Jacobian matrix if supplied. If not supplied, the Jacobian is computed via finite differences.
 
procedure, public get_equation_count vfh_get_nfcn
 Gets the number of equations in this system.
 
procedure, public get_variable_count vfh_get_nvar
 Gets the number of variables in this system.
 

Public Attributes

integer(int32) m_nfcn = 0
 The number of functions in m_fcn.
 
integer(int32) m_nvar = 0
 The number of variables in m_fcn.
 

Static Public Attributes

procedure(jacobianfcn), pointer, nopass m_jac => null()
 A pointer to the jacobian routine - null if no routine is supplied.
 

Static Private Attributes

procedure(vecfcn), pointer, nopass m_fcn => null()
 A pointer to the target vecfcn routine.
 

Detailed Description

Defines a type capable of encapsulating a system of nonlinear equations of the form: F(X) = 0. This type is used to establish the system of equations to solve, and provides a means for computing the Jacobian matrix for the system of equations, and any other ancillary operations that may be needed by the solver.

Example
The following example illustrates the most basic use of this type to solve a system of 2 equations and 2 unknowns using Newton's method.
program example
use iso_fortran_env
implicit none
! Local Variables
type(vecfcn_helper) :: obj
procedure(vecfcn), pointer :: fcn
type(newton_solver) :: solver
real(real64) :: x(2), f(2)
! Assign a pointer to the subroutine containing the equations to solve
fcn => fcns
call obj%set_fcn(fcn, 2, 2) ! There are 2 equations with 2 unknowns
! Define an initial guess
x = 1.0d0 ! Equivalent to x = [1.0d0, 1.0d0]
! Solve the system of equations
call solver%solve(obj, x, f)
! Display the output
print '(AF7.5AF7.5A)', "Solution: (", x(1), ", ", x(2), ")"
print '(AE9.3AE9.3A)', "Residual: (", f(1), ", ", f(2), ")"
contains
! Define the routine containing the equations to solve. The equations are:
! x**2 + y**2 = 34
! x**2 - 2 * y**2 = 7
subroutine fcns(x, f)
real(real64), intent(in), dimension(:) :: x
real(real64), intent(out), dimension(:) :: f
f(1) = x(1)**2 + x(2)**2 - 34.0d0
f(2) = x(1)**2 - 2.0d0 * x(2)**2 - 7.0d0
end subroutine
end program
nonlin_core
nonlin_solve
The above program produces the following output.
Solution: (5.00000, 3.00000)
Residual: (0.000E+00, 0.000E+00)

Definition at line 339 of file nonlin_core.f90.

Member Function/Subroutine Documentation

◆ fcn()

procedure, public nonlin_core::vecfcn_helper::fcn

Executes the routine containing the system of equations to solve. No action is taken if the pointer to the subroutine has not been defined.

Syntax
subroutine fcn(class(vecfcn_helper) this, real(real64) x(:), real(real64) f(:))
Parameters
[in]thisThe vecfcn_helper object.
[in]xAn N-element array containing the independent variables.
[out]fAn M-element array that, on output, contains the values of the M functions.

Definition at line 522 of file nonlin_core.f90.

◆ get_equation_count()

procedure, public nonlin_core::vecfcn_helper::get_equation_count

Gets the number of equations in this system.

Syntax
integer(int32) get_equation_count(class(vecfcn_helper) this)
Parameters
[in]thisThe vecfcn_helper object.
Returns
The function count.

Definition at line 567 of file nonlin_core.f90.

◆ get_variable_count()

procedure, public nonlin_core::vecfcn_helper::get_variable_count

Gets the number of variables in this system.

Syntax
integer(int32) get_variable_count(class(vecfcn_helper) this)
Parameters
[in]thisThe vecfcn_helper object.
Returns
The number of variables.

Definition at line 577 of file nonlin_core.f90.

◆ is_fcn_defined()

procedure, public nonlin_core::vecfcn_helper::is_fcn_defined

Tests if the pointer to the subroutine containing the system of equations to solve has been assigned.

Syntax
logical function is_fcn_defined(class(vecfcn_helper) this)
Parameters
[in]thisThe vecfcn_helper object.
Returns
Returns true if the pointer has been assigned; else, false.

Definition at line 497 of file nonlin_core.f90.

◆ is_jacobian_defined()

procedure, public nonlin_core::vecfcn_helper::is_jacobian_defined

Tests if the pointer to the subroutine containing the system of equations to solve has been assigned.

Syntax
logical function is_jacobian_defined(class(vecfcn_helper) this)
Parameters
[in]thisThe vecfcn_helper object.
Returns
Returns true if the pointer has been assigned; else, false.

Definition at line 508 of file nonlin_core.f90.

◆ jacobian()

procedure, public nonlin_core::vecfcn_helper::jacobian

Executes the routine containing the Jacobian matrix if supplied. If not supplied, the Jacobian is computed via finite differences.

Syntax
subroutine jacobian(class(vecfcn_helper) this real(real64) x(:), &
real(real64) jac(:), optional real(real64) fv(:), &
optional real(real64) work(:), optional integer(int32) lwork, &
optional integer(int32) err)
Parameters
[in]thisThe vecfcn_helper object.
[in]xAn N-element array containing the independent variabls defining the point about which the derivatives will be calculated.
[out]jacAn M-by-N matrix where, on output, the Jacobian will be written.
[in]fvAn optional M-element array containing the function values at x. If not supplied, the function values are computed at x.
[out]workAn optional input, that if provided, prevents any local memory allocation. If not provided, the memory required is allocated within. If provided, the length of the array must be at least olwork. Notice, a workspace array is only utilized if the user does not provide a routine for computing the Jacobian.
[out]olworkAn optional output used to determine workspace size. If supplied, the routine determines the optimal size for work, and returns without performing any actual calculations.
[out]errAn optional integer output that can be used to determine error status. If not used, and an error is encountered, the routine simply returns silently. If used, the following error codes identify error status:
  • 0: No error has occurred.
  • n: A positive integer denoting the index of an invalid input.
  • -1: Indicates internal memory allocation failed.

Definition at line 557 of file nonlin_core.f90.

◆ set_fcn()

procedure, public nonlin_core::vecfcn_helper::set_fcn

Establishes a pointer to the routine containing the system of equations to solve.

Syntax
subroutine set_fcn(class(vecfcn_helper) this, procedure(vecfcn) pointer fcn, integer(int32) nfcn, integer(int32) nvar)
Parameters
[in,out]thisThe vecfcn_helper object.
[in]fcnThe function pointer.
[in]nfcnThe number of functions.
[in]nvarThe number of variables.
Example
The following example illustrates how to define the function to solve. Newton's method is being utilized via the newton_solver type.
program example
use iso_fortran_env
implicit none
! Local Variables
type(vecfcn_helper) :: obj
procedure(vecfcn), pointer :: fcn
type(newton_solver) :: solver
real(real64) :: x(2), f(2)
! Assign a pointer to the subroutine containing the equations to solve
fcn => fcns
call obj%set_fcn(fcn, 2, 2) ! There are 2 equations with 2 unknowns
! Define an initial guess
x = 1.0d0 ! Equivalent to x = [1.0d0, 1.0d0]
! Solve the system of equations
call solver%solve(obj, x, f)
! Display the output
print '(AF7.5AF7.5A)', "Solution: (", x(1), ", ", x(2), ")"
print '(AE9.3AE9.3A)', "Residual: (", f(1), ", ", f(2), ")"
contains
! Define the routine containing the equations to solve. The equations are:
! x**2 + y**2 = 34
! x**2 - 2 * y**2 = 7
subroutine fcns(x, f)
real(real64), intent(in), dimension(:) :: x
real(real64), intent(out), dimension(:) :: f
f(1) = x(1)**2 + x(2)**2 - 34.0d0
f(2) = x(1)**2 - 2.0d0 * x(2)**2 - 7.0d0
end subroutine
end program
The above program produces the following output.
Solution: (5.00000, 3.00000)
Residual: (0.000E+00, 0.000E+00)

Definition at line 410 of file nonlin_core.f90.

◆ set_jacobian()

procedure, public nonlin_core::vecfcn_helper::set_jacobian

Establishes a pointer to the routine for computing the Jacobian matrix of the system of equations. If no routine is defined, the Jacobian matrix will be computed numerically (this is the default state).

Syntax
subroutine set_jacobian(class(vecfcn_helper) this, procedure(jacobianfcn) pointer jac)
Parameters
[in,out]thisThe vecfcn_helper object.
[in]jacThe function pointer.
Example
The following example utilizes Newton's method to solve a system of 2 equations and 2 unknowns with a user-defined Jacobian.
program example
use iso_fortran_env
implicit none
! Local Variables
type(vecfcn_helper) :: obj
procedure(vecfcn), pointer :: fcn
procedure(jacobianfcn), pointer :: jac
type(newton_solver) :: solver
real(real64) :: x(2), f(2)
! Assign the function and Jacobian routines
fcn => fcns
jac => fcnjac
call obj%set_fcn(fcn, 2, 2)
call obj%set_jacobian(jac)
! Define an initial guess
x = 1.0d0 ! Equivalent to x = [1.0d0, 1.0d0]
! Solve the system of equations
call solver%solve(obj, x, f)
! Display the output
print '(AF7.5AF7.5A)', "Solution: (", x(1), ", ", x(2), ")"
print '(AE9.3AE9.3A)', "Residual: (", f(1), ", ", f(2), ")"
contains
! The system of equations (source: https://www.mathworks.com/help/optim/ug/fsolve.html)
! 2 * x1 - x2 = exp(-x1)
! -x1 + 2 * x2 = exp(-x2)
subroutine fcns(x, f)
real(real64), intent(in), dimension(:) :: x
real(real64), intent(out), dimension(:) :: f
f(1) = 2.0d0 * x(1) - x(2) - exp(-x(1))
f(2) = -x(1) + 2.0d0 * x(2) - exp(-x(2))
end subroutine
! The Jacobian matrix:
! | exp(-x1) + 2 -1 |
! J = | |
! | -1 exp(-x2) + 2 |
subroutine fcnjac(x, jac)
real(real64), intent(in), dimension(:) :: x
real(real64), intent(out), dimension(:,:) :: jac
jac(1,1) = exp(-x(1)) + 2.0d0
jac(2,1) = -1.0d0
jac(1,2) = -1.0d0
jac(2,2) = exp(-x(2)) + 2.0d0
end subroutine
end program
The above program produces the following output.
Solution: (0.56714, 0.56714)
Residual: (-.693E-08, -.683E-08)

Definition at line 486 of file nonlin_core.f90.

Member Data Documentation

◆ m_fcn

procedure(vecfcn), pointer, nopass nonlin_core::vecfcn_helper::m_fcn => null()
staticprivate

A pointer to the target vecfcn routine.

Definition at line 342 of file nonlin_core.f90.

◆ m_jac

procedure(jacobianfcn), pointer, nopass nonlin_core::vecfcn_helper::m_jac => null()
static

A pointer to the jacobian routine - null if no routine is supplied.

Definition at line 344 of file nonlin_core.f90.

◆ m_nfcn

integer(int32) nonlin_core::vecfcn_helper::m_nfcn = 0

The number of functions in m_fcn.

Definition at line 346 of file nonlin_core.f90.

◆ m_nvar

integer(int32) nonlin_core::vecfcn_helper::m_nvar = 0

The number of variables in m_fcn.

Definition at line 348 of file nonlin_core.f90.


The documentation for this type was generated from the following file: