! D02KAF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
Module d02kafe_mod
! Data for D02KAF example program
! .. Use Statements ..
Use nag_library, Only: nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Accessibility Statements ..
Private
Public :: coeffn, monit
! .. Parameters ..
Real (Kind=nag_wp), Parameter, Public :: one = 1.0_nag_wp
Real (Kind=nag_wp), Parameter, Public :: zero = 0.0_nag_wp
Real (Kind=nag_wp), Parameter :: two = 2.0_nag_wp
Integer, Parameter, Public :: nin = 5, nout = 6, qq = 5
Contains
Subroutine coeffn(p,q,dqdl,x,elam,jint)
! .. Scalar Arguments ..
Real (Kind=nag_wp), Intent (Out) :: dqdl, p, q
Real (Kind=nag_wp), Intent (In) :: elam, x
Integer, Intent (In) :: jint
! .. Intrinsic Procedures ..
Intrinsic :: cos, real
! .. Executable Statements ..
p = one
dqdl = one
q = elam - two*real(qq,kind=nag_wp)*cos(two*x)
Return
End Subroutine coeffn
Subroutine monit(nit,iflag,elam,finfo)
! .. Scalar Arguments ..
Real (Kind=nag_wp), Intent (In) :: elam
Integer, Intent (In) :: iflag, nit
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (In) :: finfo(15)
! .. Executable Statements ..
If (nit==14) Then
Write (nout,*)
Write (nout,*) 'Output from MONIT'
End If
Write (nout,99999) nit, iflag, elam, finfo(1:4)
Return
99999 Format (1X,2I4,F10.3,2E12.2,2F8.1)
End Subroutine monit
End Module d02kafe_mod
Program d02kafe
! D02KAF Example Main Program
! .. Use Statements ..
Use d02kafe_mod, Only: coeffn, monit, nin, nout, one, qq, zero
Use nag_library, Only: d02kaf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Real (Kind=nag_wp) :: delam, delam1, elam, elam1, tol, xl, &
xr
Integer :: i, ifail, k
! .. Local Arrays ..
Real (Kind=nag_wp) :: bcond(3,2)
! .. Executable Statements ..
Write (nout,*) 'D02KAF Example Program Results'
! Skip heading in data file
Read (nin,*)
! xl: left-hand end point, xr: right-hand end point,
! k: index of the required eigenvalue
! elam1: initial estimate of the eigenvalue
! delam1: initial search step
Read (nin,*) xl, xr
Read (nin,*) k
Read (nin,*) elam1, delam1
bcond(1,1:2) = one
bcond(2,1:2) = zero
Do i = 5, 6
tol = 10.0_nag_wp**(-i)
elam = elam1
delam = delam1
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 0
Call d02kaf(xl,xr,coeffn,bcond,k,tol,elam,delam,monit,ifail)
Write (nout,*)
Write (nout,99999) 'Calculation with TOL =', tol
Write (nout,*)
Write (nout,*) ' Final results'
Write (nout,*)
Write (nout,99998) k, qq, elam, delam
Write (nout,99997) bcond(3,1), bcond(3,2)
Write (nout,*)
End Do
99999 Format (1X,A,E16.4)
99998 Format (1X,' K =',I3,' QQ =',I3,' ELAM =',F12.3,' DELAM =',E12.2)
99997 Format (1X,' BCOND(3,1) =',E12.4,' BCOND(3,2) =',E12.4)
End Program d02kafe