! E02GBF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
Module e02gbfe_mod
! E02GBF 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 :: monit
! .. Parameters ..
Integer, Parameter, Public :: n = 4, nin = 5, nout = 6
Contains
Subroutine monit(n,x,niter,k,el1n)
! .. Scalar Arguments ..
Real (Kind=nag_wp), Intent (In) :: el1n
Integer, Intent (In) :: k, n, niter
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (In) :: x(n)
! .. Executable Statements ..
Write (nout,*)
Write (nout,99999) 'Results at iteration ', niter
Write (nout,*) 'X-values'
Write (nout,99998) x
Write (nout,99997) 'Norm of residuals =', el1n
Return
99999 Format (1X,A,I5)
99998 Format (1X,4F15.4)
99997 Format (1X,A,E12.5)
End Subroutine monit
End Module e02gbfe_mod
Program e02gbfe
! E02GBF Example Main Program
! .. Use Statements ..
Use e02gbfe_mod, Only: monit, n, nin, nout
Use nag_library, Only: e02gbf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Real (Kind=nag_wp) :: el1n, t
Integer :: i, ifail, iprint, iw, k, l, lde, m, &
mpl, mxs
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: e(:,:), f(:), w(:), x(:)
Integer, Allocatable :: indx(:)
! .. Executable Statements ..
Write (nout,*) 'E02GBF Example Program Results'
! Skip heading in data file
Read (nin,*)
Read (nin,*) m
lde = n
l = m
mpl = m + l
iw = 3*mpl + 5*n + n**2 + (n+1)*(n+2)/2
Allocate (e(lde,mpl),f(mpl),x(n),indx(mpl),w(iw))
Do i = 1, m
Read (nin,*) t, f(i)
e(1:4,i) = (/1.0_nag_wp,t,t*t,t*t*t/)
e(1:4,m+i) = (/0.0_nag_wp,1.0_nag_wp,2.0_nag_wp*t,3.0_nag_wp*t*t/)
f(m+i) = 0.0_nag_wp
End Do
x(1:n) = 0.0_nag_wp
mxs = 50
! * Set IPRINT=1 to obtain output from MONIT at each iteration *
iprint = 0
ifail = -1
Call e02gbf(m,n,m+l,e,lde,f,x,mxs,monit,iprint,k,el1n,indx,w,iw,ifail)
End Program e02gbfe