! E04GBF Example Program Text
! Mark 30.2 Release. NAG Copyright 2024.
Module e04gbfe_mod
! E04GBF 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 :: lsqfun, lsqgrd, lsqmon
! .. Parameters ..
Real (Kind=nag_wp), Parameter :: one = 1.0_nag_wp
Real (Kind=nag_wp), Parameter :: two = 2.0_nag_wp
Real (Kind=nag_wp), Parameter :: zero = 0.0_nag_wp
Integer, Parameter :: inc1 = 1
Integer, Parameter, Public :: liw = 1, m = 15, n = 3, nin = 5, &
nout = 6, nt = 3
Integer, Parameter, Public :: ldfjac = m
Integer, Parameter, Public :: ldv = n
Integer, Parameter, Public :: lw = 7*n + m*n + 2*m + n*n
Character (1), Parameter :: trans = 'T'
! .. Local Arrays ..
Real (Kind=nag_wp), Public, Save :: t(m,nt), y(m)
Contains
Subroutine lsqgrd(m,n,fvec,fjac,ldfjac,g)
! Routine to evaluate gradient of the sum of squares
! .. Use Statements ..
Use nag_library, Only: dgemv
! .. Scalar Arguments ..
Integer, Intent (In) :: ldfjac, m, n
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (In) :: fjac(ldfjac,n), fvec(m)
Real (Kind=nag_wp), Intent (Out) :: g(n)
! .. Executable Statements ..
! The NAG name equivalent of dgemv is f06paf
Call dgemv(trans,m,n,one,fjac,ldfjac,fvec,inc1,zero,g,inc1)
g(1:n) = two*g(1:n)
Return
End Subroutine lsqgrd
Subroutine lsqfun(iflag,m,n,xc,fvec,fjac,ldfjac,iw,liw,w,lw)
! Routine to evaluate the residuals and their 1st derivatives.
! This routine is also suitable for use when E04FCV is used as
! LSQLIN, since it can deal with IFLAG = 0 as well as IFLAG = 2.
! .. Scalar Arguments ..
Integer, Intent (Inout) :: iflag
Integer, Intent (In) :: ldfjac, liw, lw, m, n
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (Inout) :: fjac(ldfjac,n), w(lw)
Real (Kind=nag_wp), Intent (Out) :: fvec(m)
Real (Kind=nag_wp), Intent (In) :: xc(n)
Integer, Intent (Inout) :: iw(liw)
! .. Local Scalars ..
Real (Kind=nag_wp) :: denom, dummy
Integer :: i
! .. Executable Statements ..
Do i = 1, m
denom = xc(2)*t(i,2) + xc(3)*t(i,3)
fvec(i) = xc(1) + t(i,1)/denom - y(i)
If (iflag/=0) Then
fjac(i,1) = one
dummy = -one/(denom*denom)
fjac(i,2) = t(i,1)*t(i,2)*dummy
fjac(i,3) = t(i,1)*t(i,3)*dummy
End If
End Do
Return
End Subroutine lsqfun
Subroutine lsqmon(m,n,xc,fvec,fjac,ldfjac,s,igrade,niter,nf,iw,liw,w,lw)
! Monitoring routine
! .. Use Statements ..
Use nag_library, Only: ddot
! .. Parameters ..
Integer, Parameter :: ndec = 3
! .. Scalar Arguments ..
Integer, Intent (In) :: igrade, ldfjac, liw, lw, m, n, nf, &
niter
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (In) :: fjac(ldfjac,n), fvec(m), s(n), &
xc(n)
Real (Kind=nag_wp), Intent (Inout) :: w(lw)
Integer, Intent (Inout) :: iw(liw)
! .. Local Scalars ..
Real (Kind=nag_wp) :: fsumsq, gtg
Integer :: j
! .. Local Arrays ..
Real (Kind=nag_wp) :: g(ndec)
! .. Executable Statements ..
! The NAG name equivalent of ddot is f06eaf
fsumsq = ddot(m,fvec,inc1,fvec,inc1)
Call lsqgrd(m,n,fvec,fjac,ldfjac,g)
gtg = ddot(n,g,inc1,g,inc1)
Write (nout,*)
Write (nout,*) &
' Itn F evals SUMSQ GTG Grade'
Write (nout,99999) niter, nf, fsumsq, gtg, igrade
Write (nout,*)
Write (nout,*) &
' X G Singular values'
Write (nout,99998)(xc(j),g(j),s(j),j=1,n)
Return
99999 Format (1X,I4,6X,I5,6X,1P,E13.5,6X,1P,E9.1,6X,I3)
99998 Format (1X,1P,E13.5,10X,1P,E9.1,10X,1P,E9.1)
End Subroutine lsqmon
End Module e04gbfe_mod
Program e04gbfe
! E04GBF Example Main Program
! .. Use Statements ..
Use e04gbfe_mod, Only: ldfjac, ldv, liw, lsqfun, lsqgrd, lsqmon, lw, m, &
n, nin, nout, nt, t, y
Use nag_library, Only: e04gbf, e04hev, e04yaf, nag_wp, x02ajf
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Real (Kind=nag_wp) :: eta, fsumsq, stepmx, xtol
Integer :: i, ifail, iprint, maxcal, nf, niter
! .. Local Arrays ..
Real (Kind=nag_wp) :: fjac(ldfjac,n), fvec(m), g(n), s(n), &
v(ldv,n), w(lw), x(n)
Integer :: iw(liw)
! .. Intrinsic Procedures ..
Intrinsic :: sqrt
! .. Executable Statements ..
Write (nout,*) 'E04GBF Example Program Results'
! Skip heading in data file
Read (nin,*)
! Observations of TJ (J = 1, 2, ..., nt) are held in T(I, J)
! (I = 1, 2, . . . , m)
Do i = 1, m
Read (nin,*) y(i), t(i,1:nt)
End Do
! Check LSQFUN by calling E04YAF at an arbitrary point
x(1:nt) = (/0.19_nag_wp,-1.34_nag_wp,0.88_nag_wp/)
ifail = 0
Call e04yaf(m,n,lsqfun,x,fvec,fjac,ldfjac,iw,liw,w,lw,ifail)
! Continue setting parameters for E04GBF
! Set IPRINT to 1 to obtain output from LSQMON at each iteration
iprint = -1
maxcal = 50*n
! Since E04HEV is being used as LSQLIN, we set ETA to 0.9
eta = 0.9_nag_wp
xtol = 10.0_nag_wp*sqrt(x02ajf())
! We estimate that the minimum will be within 10 units of the
! starting point
stepmx = 10.0_nag_wp
! Set up the starting point
x(1:nt) = (/0.5_nag_wp,1.0_nag_wp,1.5_nag_wp/)
ifail = -1
Call e04gbf(m,n,e04hev,lsqfun,lsqmon,iprint,maxcal,eta,xtol,stepmx,x, &
fsumsq,fvec,fjac,ldfjac,s,v,ldv,niter,nf,iw,liw,w,lw,ifail)
Select Case (ifail)
Case (0,2:)
Write (nout,*)
Write (nout,99999) 'On exit, the sum of squares is', fsumsq
Write (nout,99999) 'at the point', x(1:n)
Call lsqgrd(m,n,fvec,fjac,ldfjac,g)
Write (nout,99998) 'The corresponding gradient is', g(1:n)
Write (nout,*) ' (machine dependent)'
Write (nout,*) 'and the residuals are'
Write (nout,99997) fvec(1:m)
End Select
99999 Format (1X,A,3F12.4)
99998 Format (1X,A,1P,3E12.3)
99997 Format (1X,1P,E9.1)
End Program e04gbfe