! C05ADF Example Program Text ! Mark 23 Release. NAG Copyright 2011. MODULE c05adfe_mod ! C05ADF Example Program Module: ! Parameters and User-defined Routines ! .. Use Statements .. USE nag_library, ONLY : nag_wp ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nout = 6 CONTAINS FUNCTION f(x) ! .. Implicit None Statement .. IMPLICIT NONE ! .. Function Return Value .. REAL (KIND=nag_wp) :: f ! .. Scalar Arguments .. REAL (KIND=nag_wp), INTENT (IN) :: x ! .. Intrinsic Functions .. INTRINSIC exp ! .. Executable Statements .. f = exp(-x) - x RETURN END FUNCTION f END MODULE c05adfe_mod PROGRAM c05adfe ! C05ADF Example Main Program ! .. Use Statements .. USE nag_library, ONLY : c05adf, nag_wp USE c05adfe_mod, ONLY : f, nout ! .. Implicit None Statement .. IMPLICIT NONE ! .. Local Scalars .. REAL (KIND=nag_wp) :: a, b, eps, eta, x INTEGER :: ifail ! .. Executable Statements .. WRITE (nout,*) 'C05ADF Example Program Results' a = 0.0E0_nag_wp b = 1.0E0_nag_wp eps = 1.0E-5_nag_wp eta = 0.0E0_nag_wp ifail = -1 CALL c05adf(a,b,eps,eta,f,x,ifail) WRITE (nout,*) SELECT CASE (ifail) CASE (0) WRITE (nout,99999) 'Zero at X =', x CASE (2,3) WRITE (nout,99999) 'Final point = ', x END SELECT 99999 FORMAT (1X,A,F12.5) END PROGRAM c05adfe