! C05AZF Example Program Text
! Mark 26.2 Release. NAG Copyright 2017.
Module c05azfe_mod
! C05AZF Example Program Module:
! Parameters and User-defined Routines
! .. Use Statements ..
Use nag_library, Only: nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Accessibility Statements ..
Private
Public :: f
! .. Parameters ..
Real (Kind=nag_wp), Parameter, Public :: tolx = 1.0E-5_nag_wp
Integer, Parameter, Public :: ir = 0, nout = 6
Contains
Function f(x)
! .. Function Return Value ..
Real (Kind=nag_wp) :: f
! .. Scalar Arguments ..
Real (Kind=nag_wp), Intent (In) :: x
! .. Intrinsic Procedures ..
Intrinsic :: exp
! .. Executable Statements ..
f = exp(-x) - x
Return
End Function f
End Module c05azfe_mod
Program c05azfe
! C05AZF Example Main Program
! .. Use Statements ..
Use c05azfe_mod, Only: f, ir, nout, tolx
Use nag_library, Only: c05azf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Real (Kind=nag_wp) :: fx, x, y
Integer :: ifail, ind
! .. Local Arrays ..
Real (Kind=nag_wp) :: c(17)
! .. Executable Statements ..
Write (nout,*) 'C05AZF Example Program Results'
Write (nout,*)
Write (nout,*) ' Iterations'
Write (nout,*)
! Initial values, root in [0,1].
x = 0.0_nag_wp
y = 1.0_nag_wp
ind = 1
ifail = -1
! Reverse communication loop
revcom: Do
Call c05azf(x,y,fx,tolx,ir,c,ind,ifail)
If (ind==0) Then
Exit revcom
End If
fx = f(x)
Write (nout,99999) ' X =', x, ' FX =', fx, ' IND =', ind
End Do revcom
! Results
Select Case (ifail)
Case (0)
Write (nout,*)
Write (nout,*) ' Solution'
Write (nout,*)
Write (nout,99998) ' X =', x, ' Y =', y
Case (4,5)
Write (nout,99998) 'X =', x, ' Y =', y
End Select
99999 Format (1X,A,F8.5,A,E12.4,A,I2)
99998 Format (1X,2(A,F8.5))
End Program c05azfe