! E04YBF Example Program Text
! Mark 28.6 Release. NAG Copyright 2022.
Module e04ybfe_mod
! E04YBF 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, lsqhes
! .. Parameters ..
Integer, Parameter, Public :: liw = 1, mdec = 15, ndec = 3, &
nin = 5, nout = 6
Integer, Parameter, Public :: lb = ndec*(ndec+1)/2
Integer, Parameter, Public :: ldfjac = mdec
Integer, Parameter, Public :: lw = 5*ndec + mdec + mdec*ndec + &
ndec*(ndec-1)/2
! .. Local Arrays ..
Real (Kind=nag_wp), Public, Save :: t(mdec,ndec), y(mdec)
Contains
Subroutine lsqfun(iflag,m,n,xc,fvec,fjac,ldfjac,iw,liw,w,lw)
! Routine to evaluate the residuals and their 1st derivatives
! .. 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)
fjac(i,1) = 1.0E0_nag_wp
dummy = -1.0E0_nag_wp/(denom*denom)
fjac(i,2) = t(i,1)*t(i,2)*dummy
fjac(i,3) = t(i,1)*t(i,3)*dummy
End Do
Return
End Subroutine lsqfun
Subroutine lsqhes(iflag,m,n,fvec,xc,b,lb,iw,liw,w,lw)
! Routine to compute the lower triangle of the matrix B
! (stored by rows in the array B)
! .. Scalar Arguments ..
Integer, Intent (Inout) :: iflag
Integer, Intent (In) :: lb, liw, lw, m, n
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (Out) :: b(lb)
Real (Kind=nag_wp), Intent (In) :: fvec(m), xc(n)
Real (Kind=nag_wp), Intent (Inout) :: w(lw)
Integer, Intent (Inout) :: iw(liw)
! .. Local Scalars ..
Real (Kind=nag_wp) :: dummy, sum22, sum32, sum33
Integer :: i
! .. Executable Statements ..
b(1) = 0.0E0_nag_wp
b(2) = 0.0E0_nag_wp
sum22 = 0.0E0_nag_wp
sum32 = 0.0E0_nag_wp
sum33 = 0.0E0_nag_wp
Do i = 1, m
dummy = 2.0E0_nag_wp*t(i,1)/(xc(2)*t(i,2)+xc(3)*t(i,3))**3
sum22 = sum22 + fvec(i)*dummy*t(i,2)**2
sum32 = sum32 + fvec(i)*dummy*t(i,2)*t(i,3)
sum33 = sum33 + fvec(i)*dummy*t(i,3)**2
End Do
b(3) = sum22
b(4) = 0.0E0_nag_wp
b(5) = sum32
b(6) = sum33
Return
End Subroutine lsqhes
End Module e04ybfe_mod
Program e04ybfe
! E04YBF Example Main Program
! .. Use Statements ..
Use e04ybfe_mod, Only: lb, ldfjac, liw, lsqfun, lsqhes, lw, mdec, ndec, &
nin, nout, t, y
Use nag_library, Only: e04yaf, e04ybf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Integer :: i, ifail, k, m, n
! .. Local Arrays ..
Real (Kind=nag_wp) :: b(lb), fjac(ldfjac,ndec), &
fvec(mdec), w(lw), x(ndec)
Integer :: iw(liw)
! .. Executable Statements ..
Write (nout,*) 'E04YBF Example Program Results'
! Skip heading in data file
Read (nin,*)
m = mdec
n = ndec
! Observations of TJ (J = 1, 2, ..., n) are held in T(I, J)
! (I = 1, 2, ..., m)
Do i = 1, m
Read (nin,*) y(i), t(i,1:n)
End Do
! Set up an arbitrary point at which to check the derivatives
x(1:n) = (/0.19E0_nag_wp,-1.34E0_nag_wp,0.88E0_nag_wp/)
! Check the 1st derivatives
ifail = 0
Call e04yaf(m,n,lsqfun,x,fvec,fjac,ldfjac,iw,liw,w,lw,ifail)
Write (nout,*)
Write (nout,*) 'The test point is'
Write (nout,99999) x(1:n)
! Check the evaluation of B
ifail = -1
Call e04ybf(m,n,lsqfun,lsqhes,x,fvec,fjac,ldfjac,b,lb,iw,liw,w,lw,ifail)
If (ifail>=0 .And. ifail/=1) Then
Select Case (ifail)
Case (0)
Write (nout,*)
Write (nout,*) 'The matrix B is consistent with 1st derivatives'
Case (2)
Write (nout,*)
Write (nout,*) 'Probable error in calculation of the matrix B'
End Select
Write (nout,*)
Write (nout,*) 'At the test point, LSQFUN gives'
Write (nout,*)
Write (nout,*) ' Residuals 1st derivatives'
Write (nout,99998)(fvec(i),fjac(i,1:n),i=1,m)
Write (nout,*)
Write (nout,*) 'and LSQHES gives the lower triangle of the matrix B'
Write (nout,*)
k = 1
Do i = 1, n
Write (nout,99998) b(k:(k+i-1))
k = k + i
End Do
End If
99999 Format (1X,4F10.5)
99998 Format (1X,1P,4E15.3)
End Program e04ybfe