dynamics_system_id Module


Uses


Contents


Interfaces

interface

  • public subroutine constraint_equations(xg, fg, xc, p, fc, args)

    An interface to a set of routines for defining constraint equations to the fitting process.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=real64), intent(in), dimension(:) :: xg

    An N-element array containing the N independent variable values for the N differential equation solution points.

    real(kind=real64), intent(in), dimension(:) :: fg

    An N-element array containing the N differential equation solution points.

    real(kind=real64), intent(in), dimension(:) :: xc

    An M-element array containing the M independent variable values for the M constraint equations.

    real(kind=real64), intent(in), dimension(:) :: p

    An array containing the model parameters.

    real(kind=real64), intent(out), dimension(:) :: fc

    An M-element array where the values of the constraint equations should be written.

    class(*), intent(inout), optional :: args

    An optional argument that can be used to pass data in/out of this routine.

public interface siso_model_fit_least_squares

  • private subroutine siso_model_fit_least_squares_1(fcn, x, ic, p, integrator, ind, maxp, minp, stats, alpha, controls, settings, info, status, cov, xc, yc, constraints, weights, args, err)

    Attempts to fit a model of a single-intput, single-output (SISO) dynamic system by means of an iterative least-squares solver. The algorithm computes the solution to the differential equations numerically, and compares the output to the known solution via a Levenberg-Marquardt least-squares solver.

    Arguments

    Type IntentOptional Attributes Name
    procedure(ode), intent(in), pointer :: fcn

    The routine containing the ODE's being fit. To communicate model parameters and other relevant information, an instance of the [[model_information]] type is passed to the optional argument of this routine. Use the "select type" construct to access this information.

    class(dynamic_system_measurement), intent(in), dimension(:) :: x

    An M-element array of arrays with each array containing the measured input and output of the system being identified.

    real(kind=real64), intent(in), dimension(:) :: ic

    The initial condition vector for the equations in fcn.

    real(kind=real64), intent(inout), dimension(:) :: p

    An N-element array containing an initial guess at the parameters.
    On output, the computed model parameters.

    class(ode_integrator), intent(inout), optional, target :: integrator

    The integrator to use when solving the system equations. If not supplied, the default integrator will be used. The default integrator is a Runge-Kutta integrator (Dormand-Prince).

    integer(kind=int32), intent(in), optional :: ind

    The index of the ODE in fcn providing the output to fit. If no value is supplied, a value of 1 will be utilized.

    real(kind=real64), intent(in), optional, dimension(:) :: maxp

    An optional N-element array that can be used as upper limits on the parameter values. If no upper limit is requested for a particular parameter, utilize a very large value. The internal default is to utilize huge() as a value.

    real(kind=real64), intent(in), optional, dimension(:) :: minp

    An optional N-element array that can be used as lower limits on the parameter values. If no lower limit is requested for a particalar parameter, utilize a very large magnitude, but negative, value. The internal default is to utilize -huge() as a value.

    type(regression_statistics), intent(out), optional, dimension(:) :: stats

    An optional N-element array that, if supplied, will be used to return statistics about the fit for each parameter.

    real(kind=real64), intent(in), optional :: alpha

    The significance level at which to evaluate the confidence intervals. The default value is 0.05 such that a 95% confidence interval is calculated.

    type(iteration_controls), intent(in), optional :: controls

    An optional input providing custom iteration controls.

    type(lm_solver_options), intent(in), optional :: settings

    An optional input providing custom settings for the solver.

    type(convergence_info), intent(out), optional :: info

    An optional output that can be used to gain information about the iterative solution and the nature of the convergence.

    procedure(iteration_update), intent(in), optional, pointer :: status

    An optional pointer to a routine that can be used to extract iteration information.

    real(kind=real64), intent(out), optional, dimension(:,:) :: cov

    An optional N-by-N matrix that, if supplied, will be used to return the covariance matrix.

    real(kind=real64), intent(in), optional, dimension(:) :: xc

    An optional NC-element array containing the values of the independent variable at which the constraint equations are defined.

    real(kind=real64), intent(in), optional, dimension(:) :: yc

    An optional NC-element array containing the constraint function values at xc.

    procedure(constraint_equations), optional, pointer :: constraints

    An optional input, that must be utilized with the xc and yc inputs, but allows for the implementation of additional constraints on the solution outside of the differential equations being fitted. An example usage would be an additional set of quasi-static tests that could help identify a stiffness term, for instance. Other uses of course can be imagined.

    real(kind=real64), intent(in), optional, dimension(:) :: weights

    An optional array containing weighting factors for every equation.

    class(*), intent(inout), optional, target :: args

    User-defined information to pass along to fcn. These arguments, if supplied, will be passed through to fcn by means of the [[model_information]] type.

    class(errors), intent(inout), optional, target :: err

    An error handling object.

  • private subroutine siso_model_fit_least_squares_2(fcn, x, ic, p, integrator, ind, maxp, minp, stats, alpha, controls, settings, info, status, cov, xc, yc, constraints, weights, args, err)

    Attempts to fit a model of a single-intput, single-output (SISO) dynamic system by means of an iterative least-squares solver. The algorithm computes the solution to the differential equations numerically, and compares the output to the known solution via a Levenberg-Marquardt least-squares solver.

    Arguments

    Type IntentOptional Attributes Name
    procedure(ode), intent(in), pointer :: fcn

    The routine containing the ODE's being fit. To communicate model parameters and other relevant information, an instance of the [[model_information]] type is passed to the optional argument of this routine. Use the "select type" construct to access this information.

    class(dynamic_system_measurement), intent(in), dimension(:) :: x

    An M-element array of arrays with each array containing the measured input and output of the system being identified.

    real(kind=real64), intent(in), dimension(:,:) :: ic

    An M-by-NEQN matrix of initial condition vectors for the NEQN equations in fcn, one set for each of the M sets of data in x.

    real(kind=real64), intent(inout), dimension(:) :: p

    An N-element array containing an initial guess at the parameters.
    On output, the computed model parameters.

    class(ode_integrator), intent(inout), optional, target :: integrator

    The integrator to use when solving the system equations. If not supplied, the default integrator will be used. The default integrator is a Runge-Kutta integrator (Dormand-Prince).

    integer(kind=int32), intent(in), optional :: ind

    The index of the ODE in fcn providing the output to fit. If no value is supplied, a value of 1 will be utilized.

    real(kind=real64), intent(in), optional, dimension(:) :: maxp

    An optional N-element array that can be used as upper limits on the parameter values. If no upper limit is requested for a particular parameter, utilize a very large value. The internal default is to utilize huge() as a value.

    real(kind=real64), intent(in), optional, dimension(:) :: minp

    An optional N-element array that can be used as lower limits on the parameter values. If no lower limit is requested for a particalar parameter, utilize a very large magnitude, but negative, value. The internal default is to utilize -huge() as a value.

    type(regression_statistics), intent(out), optional, dimension(:) :: stats

    An optional N-element array that, if supplied, will be used to return statistics about the fit for each parameter.

    real(kind=real64), intent(in), optional :: alpha

    The significance level at which to evaluate the confidence intervals. The default value is 0.05 such that a 95% confidence interval is calculated.

    type(iteration_controls), intent(in), optional :: controls

    An optional input providing custom iteration controls.

    type(lm_solver_options), intent(in), optional :: settings

    An optional input providing custom settings for the solver.

    type(convergence_info), intent(out), optional :: info

    An optional output that can be used to gain information about the iterative solution and the nature of the convergence.

    procedure(iteration_update), intent(in), optional, pointer :: status

    An optional pointer to a routine that can be used to extract iteration information.

    real(kind=real64), intent(out), optional, dimension(:,:) :: cov

    An optional N-by-N matrix that, if supplied, will be used to return the covariance matrix.

    real(kind=real64), intent(in), optional, dimension(:) :: xc

    An optional NC-element array containing the values of the independent variable at which the constraint equations are defined.

    real(kind=real64), intent(in), optional, dimension(:) :: yc

    An optional NC-element array containing the constraint function values at xc.

    procedure(constraint_equations), optional, pointer :: constraints

    An optional input, that must be utilized with the xc and yc inputs, but allows for the implementation of additional constraints on the solution outside of the differential equations being fitted. An example usage would be an additional set of quasi-static tests that could help identify a stiffness term, for instance. Other uses of course can be imagined.

    real(kind=real64), intent(in), optional, dimension(:) :: weights

    An optional array containing weighting factors for every equation.

    class(*), intent(inout), optional, target :: args

    User-defined information to pass along to fcn. These arguments, if supplied, will be passed through to fcn by means of the [[model_information]] type.

    class(errors), intent(inout), optional, target :: err

    An error handling object.


Derived Types

type, public ::  dynamic_system_measurement

A container of a single measurement data set.

Components

Type Visibility Attributes Name Initial
real(kind=real64), public, allocatable, dimension(:) :: input

The input data.

real(kind=real64), public, allocatable, dimension(:) :: output

The output data.

real(kind=real64), public, allocatable, dimension(:) :: t

The time points at which the measurements were taken.

type, public ::  model_information

A container for model information.

Components

Type Visibility Attributes Name Initial
class(base_interpolator), public, pointer :: excitation

An interpolation object allowing sampling of the excitation function.

real(kind=real64), public, allocatable, dimension(:) :: model

An array containing the model parameters.

class(*), public, pointer :: user_info

Information the user has passed along.