simple_step Subroutine

private subroutine simple_step(me, xold, p, x, f, fvec, fjac, fjac_sparse)

Take a simple step in the search direction of p * alpha.

Arguments

Type IntentOptional Attributes Name
class(nlesolver_type), intent(inout) :: me
real(kind=wp), intent(in), dimension(me%n) :: xold

previous value of x

real(kind=wp), intent(in), dimension(me%n) :: p

search direction

real(kind=wp), intent(out), dimension(me%n) :: x

new x

real(kind=wp), intent(inout) :: f

magnitude of fvec

real(kind=wp), intent(inout), dimension(me%m) :: fvec

function vector

real(kind=wp), intent(in), optional, dimension(:,:) :: fjac

jacobian matrix [dense]

real(kind=wp), intent(in), optional, dimension(:) :: fjac_sparse

jacobian matrix [sparse]


Calls

proc~~simple_step~~CallsGraph proc~simple_step simple_step proc~adjust_search_direction nlesolver_type%adjust_search_direction proc~simple_step->proc~adjust_search_direction proc~compute_next_step nlesolver_type%compute_next_step proc~simple_step->proc~compute_next_step proc~int2str int2str proc~adjust_search_direction->proc~int2str proc~set_status nlesolver_type%set_status proc~adjust_search_direction->proc~set_status proc~set_status->proc~int2str proc~real2str real2str proc~set_status->proc~real2str

Source Code

    subroutine simple_step(me,xold,p,x,f,fvec,fjac,fjac_sparse)

    implicit none

    class(nlesolver_type),intent(inout) :: me
    real(wp),dimension(me%n),intent(in) :: xold      !! previous value of `x`
    real(wp),dimension(me%n),intent(in) :: p         !! search direction
    real(wp),dimension(me%n),intent(out) :: x        !! new `x`
    real(wp),intent(inout) :: f                      !! magnitude of `fvec`
    real(wp),dimension(me%m),intent(inout) :: fvec   !! function vector
    real(wp),dimension(:,:),intent(in),optional :: fjac !! jacobian matrix [dense]
    real(wp),dimension(:),intent(in),optional :: fjac_sparse !! jacobian matrix [sparse]

    real(wp),dimension(:),allocatable :: search_direction
    logical,dimension(:),allocatable :: modified  !! indicates the elements of p that were modified

    allocate(search_direction(me%n))
    allocate(modified(me%n))

    call me%adjust_search_direction(xold,p,search_direction,modified)
    call me%compute_next_step(xold, search_direction, me%alpha, modified, x)

    !evaluate the function at the new point:
    call me%func(x,fvec)
    f = me%norm(fvec)

    end subroutine simple_step