PROGRAM s21bhfe ! S21BHF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : nag_wp, s21bhf ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nout = 6 ! .. Local Scalars .. REAL (KIND=nag_wp) :: dm, f INTEGER :: ifail, ix ! .. Intrinsic Functions .. INTRINSIC real ! .. Executable Statements .. WRITE (nout,*) 'S21BHF Example Program Results' WRITE (nout,*) WRITE (nout,*) ' DM S21BHF' WRITE (nout,*) DATA: DO ix = 1, 3 dm = real(ix,kind=nag_wp)*0.25E0_nag_wp ifail = -1 f = s21bhf(dm,ifail) IF (ifail<0) THEN EXIT DATA END IF WRITE (nout,99999) dm, f END DO DATA 99999 FORMAT (1X,F7.2,F12.4) END PROGRAM s21bhfe