Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(RootFinderDataType), | intent(inout) | :: | RootFinderData | |||
real(kind=r64), | intent(in) | :: | X | |||
real(kind=r64), | intent(in) | :: | Y | |||
logical, | intent(out), | optional | :: | IsDoneFlag |
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE IterateRootFinder( RootFinderData, X, Y, IsDoneFlag )
! SUBROUTINE INFORMATION:
! AUTHOR Dimitri Curtil (LBNL)
! DATE WRITTEN March 2006
! MODIFIED
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine is the workhorse of the root finder framework.
! It should be invoked with every new candidate (X,Y) until
! convergence is achieved or abnormal termination is detected.
!
! The subroutine performs the following tasks:
! - it checks for convergence
! - it updates the internal data with the current iterate (X,Y)
! - it computes a new root candidate if not converged yet.
!
! Sets IsDoneFlag to FALSE when iteration should continue with the new candidate value.
! Sets IsDoneFlag to TRUE when iteration should be stopped because convergence has been achieved
! or because of a fatal error.
!
! Note that only upon normal termination (iStatusOK<...> codes)
! will the XCandidate value contain the root.
! If the root has not been located yet the XCandidate value contains
! the next candidate root to try.
!
! Status IsDoneFlag XCandidate
! ========================================================================
! iStatusErrorRange TRUE na
! iStatusErrorSingular TRUE na
! iStatusErrorSlope TRUE na
! iStatusErrorBracket TRUE na
! ------------------------------------------------------------------------
! iStatusOKMin TRUE MinPoint%X
! iStatusOKMax TRUE MaxPoint%X
! iStatusOK TRUE X
! iStatusOKRoundOff TRUE X
! ------------------------------------------------------------------------
! iStatusNone FALSE AdvanceRootFinder()
! iStatusWarningNonMonotonic FALSE AdvanceRootFinder()
! iStatusWarningSingular FALSE AdvanceRootFinder()
!
! METHODOLOGY EMPLOYED:
! The methodology reflects the same approach implemented in the subroutine CalcSimpleController()
! whereby the iteration was exited by checking the following conditions in this specified
! sequence:
! 1. Check for singular function so that YMin /= YMax
! 2. Check for slope condition for the residual function
! - increasing: YMin < YMax
! - decreasing: YMin > YMax
! 3. Check for min constraint
! - increasing: YMin <= 0
! - decreasing: YMin >= 0
! 4. Check for max constraint
! - increasing: YMax > 0
! - decreasing: YMax < 0
! 5. Check unconstrained convergence
!
! Note that the slope condition was not explicitly checked in the original implementation
! in CalcSimpleController().
!
! Finally, we also check the X increments between successive iterations to detect possible
! cases whereby the allowed precision in the X space limits the precision attainable in
! the Y space. This check is implemented in:
! - CheckIncrementRoundOff()
! - CheckBracketRoundOff()
!
! REFERENCES:
! na
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
TYPE(RootFinderDataType), INTENT(INOUT) :: RootFinderData ! Data used by root finding algorithm
REAL(r64), INTENT(IN) :: X ! X value of current iterate
REAL(r64), INTENT(IN) :: Y ! Y value of current iterate
LOGICAL, INTENT(OUT), OPTIONAL :: IsDoneFlag ! If TRUE indicates that the iteration should be stopped
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
! na
! FLOW:
! Reset status flag
RootFinderData%StatusFlag = iStatusNone
! Check that MinPoint%X <= X <= MaxPoint%X
IF ( .NOT.CheckMinMaxRange( RootFinderData, X ) ) THEN
RootFinderData%StatusFlag = iStatusErrorRange
! Fatal error: No need to continue iterating
IsDoneFlag = .TRUE.
RETURN
END IF
! Update min/max support points with current iterate
CALL UpdateMinMax( RootFinderData, X, Y )
!----------------------------------------------------------------------------
! Check "global" singularity and bad slope conditions between min and
! max points
!----------------------------------------------------------------------------
! NOTE: Performed before checking min and max constraints to mimic original implementation
! in ManagerControllers()
IF ( RootFinderData%MinPoint%DefinedFlag .AND. RootFinderData%MaxPoint%DefinedFlag ) THEN
! Check that min and max points are distinct
IF (RootFinderData%MinPoint%X == RootFinderData%MaxPoint%X) THEN
RootFinderData%StatusFlag = iStatusOKMin
RootFinderData%XCandidate = RootFinderData%MinPoint%X
! Solution found: No need to continue iterating
IsDoneFlag = .TRUE.
RETURN
END IF
IF ( RootFinderData%MinPoint%DefinedFlag ) THEN
IF ( CheckMinConstraint( RootFinderData ) ) THEN
RootFinderData%StatusFlag = iStatusOKMin
RootFinderData%XCandidate = RootFinderData%MinPoint%X
! Solution found: No need to continue iterating
IsDoneFlag = .TRUE.
RETURN
END IF
END IF
! Check singularity condition between min and max points
IF ( .NOT.CheckNonSingularity(RootFinderData) ) THEN
RootFinderData%StatusFlag = iStatusErrorSingular
! Fatal error: No need to continue iterating
IsDoneFlag = .TRUE.
RETURN
END IF
! Check slope condition between min and max points
IF ( .NOT.CheckSlope(RootFinderData) ) THEN
RootFinderData%StatusFlag = iStatusErrorSlope
! Fatal error: No need to continue iterating
IsDoneFlag = .TRUE.
RETURN
END IF
END IF
!----------------------------------------------------------------------------
! Check that F(X) is not min or max constrained
!----------------------------------------------------------------------------
! Check min constraint before max constraint to mimic original implementation
! in ManagerControllers()
IF ( RootFinderData%MinPoint%DefinedFlag ) THEN
IF ( CheckMinConstraint( RootFinderData ) ) THEN
RootFinderData%StatusFlag = iStatusOKMin
RootFinderData%XCandidate = RootFinderData%MinPoint%X
! Solution found: No need to continue iterating
IsDoneFlag = .TRUE.
RETURN
END IF
END IF
! Min point should always be evaluated first to ensure that we return with the min
! consrained solution even in cases where the residual function has inconsistent slope.
!
! TODO: Force to evaluate min point before exiting with max constrained solution
! in order to be able to detect singularity and bad slope conditions.
IF ( RootFinderData%MaxPoint%DefinedFlag ) THEN
IF ( CheckMaxConstraint( RootFinderData ) ) THEN
RootFinderData%StatusFlag = iStatusOKMax
RootFinderData%XCandidate = RootFinderData%MaxPoint%X
! Solution found: No need to continue iterating
IsDoneFlag = .TRUE.
RETURN
END IF
END IF
!----------------------------------------------------------------------------
! Check convergence of current iterate
!----------------------------------------------------------------------------
! Check unconstrained convergence after we are sure that the candidate X value lies
! within the allowed min/max range
IF ( CheckRootFinderConvergence( RootFinderData, Y ) ) THEN
RootFinderData%StatusFlag = iStatusOK
RootFinderData%XCandidate = X
! Update root finder internal data with current iterate (X,Y)
CALL UpdateRootFinder( RootFinderData, X, Y )
! Solution found: No need to continue iterating
IsDoneFlag = .TRUE.
RETURN
END IF
! Check last as this was not done in the original implementation
!
! Essentially we stop the iteration if:
! - the increment beween successive iterates is smaller than the user-specified
! tolerance for the X variables.
! - the distance between the lower and upper bounds is smaller than the user-specified
! tolerance for the X variables. (USING brackets from previous iteration)
!
! BUG: Relaxed check to avoid detecting round-off in case 2 successive iterates are the same!
!
!IF ( CheckIncrementRoundOff( RootFinderData, X ) ) THEN
! RootFinderData%StatusFlag = iStatusOKRoundOff
! RETURN
!END IF
IF ( CheckBracketRoundOff( RootFinderData ) ) THEN
RootFinderData%StatusFlag = iStatusOKRoundOff
RootFinderData%XCandidate = X
! Update root finder internal data with current iterate (X,Y)
CALL UpdateRootFinder( RootFinderData, X, Y )
! Solution found: No need to continue iterating
IsDoneFlag = .TRUE.
RETURN
END IF
!----------------------------------------------------------------------------
! If the current iterate lies within the current lower and upper brackets,
! proceed with normal processing to identify the next root candidate:
! - update lower/upper bracket with current iterate
! - update history
! - update increments across successive iterations
! - update current point
! - compute next candidate (see AdvanceRootFinder() ).
!----------------------------------------------------------------------------
! Check that current iterate is within the current lower and upper points
IF ( .NOT.CheckLowerUpperBracket( RootFinderData, X ) ) THEN
RootFinderData%StatusFlag = iStatusErrorBracket
! Fatal error: No need to continue iterating
IsDoneFlag = .TRUE.
RETURN
END IF
! Update root finder internal data with current iterate (X,Y)
CALL UpdateRootFinder( RootFinderData, X, Y )
! Compute new root candidate and store value in in RootFinderData%XCandidate
! - First attempt to bracket root within lower and upper points
! - Then use whatever requested solution method in SetupRootFinder() to
! compute the next candidate.
CALL AdvanceRootFinder( RootFinderData )
! Indicates that we should continue iterating with new candidate
IsDoneFlag = .FALSE.
RETURN
END SUBROUTINE IterateRootFinder