! D02BGF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
Module d02bgfe_mod
! D02BGF 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 :: fcn
! .. Parameters ..
Integer, Parameter, Public :: n = 3, nin = 5, nout = 6
! n: number of differential equations
Contains
Subroutine fcn(x,y,f)
! .. Scalar Arguments ..
Real (Kind=nag_wp), Intent (In) :: x
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (Out) :: f(*)
Real (Kind=nag_wp), Intent (In) :: y(*)
! .. Intrinsic Procedures ..
Intrinsic :: cos, tan
! .. Executable Statements ..
f(1) = tan(y(3))
f(2) = -0.032E0_nag_wp*tan(y(3))/y(2) - 0.02E0_nag_wp*y(2)/cos(y(3))
f(3) = -0.032E0_nag_wp/y(2)**2
Return
End Subroutine fcn
End Module d02bgfe_mod
Program d02bgfe
! D02BGF Example Main Program
! .. Use Statements ..
Use d02bgfe_mod, Only: fcn, n, nin, nout
Use nag_library, Only: d02bgf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Real (Kind=nag_wp) :: alpha, hmax, tol, val, x, xend, &
xinit
Integer :: i, ifail, m
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: w(:,:), y(:), yinit(:)
! .. Executable Statements ..
Write (nout,*) 'D02BGF Example Program Results'
! Skip heading in data file
Read (nin,*)
! m: index of mode of solution to attain value alpha
Read (nin,*) m
Allocate (w(n,10),y(n),yinit(n))
! xinit: initial x value, xend : final x value.
! alpha: attain y(m) = alpha, yinit: initial solution values.
Read (nin,*) alpha
Read (nin,*) xinit
Read (nin,*) xend
Read (nin,*) yinit(1:n)
hmax = 0.0E0_nag_wp
val = alpha
Do i = 4, 5
tol = 10.0E0_nag_wp**(-i)
x = xinit
y(1:n) = yinit(1:n)
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 0
Call d02bgf(x,xend,n,y,tol,hmax,m,val,fcn,w,ifail)
Write (nout,*)
Write (nout,99999) 'Calculation with TOL =', tol
Write (nout,99998) ' Y(M) changes sign at X = ', x
If (tol<0.0E0_nag_wp) Then
Write (nout,*) ' Over one-third steps controlled by HMAX'
End If
End Do
99999 Format (1X,A,E8.1)
99998 Format (1X,A,F7.4)
End Program d02bgfe