Program c05mdfe
! C05MDF Example Program Text
! Mark 30.1 Release. NAG Copyright 2024.
! .. Use Statements ..
Use nag_library, Only: c05mdf, dnrm2, nag_wp, x02ajf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: imax = 50, n = 4, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: atol, cndtol, fnorm, rtol
Integer :: astart, i, icount, ifail, irevcm, m
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: fvec(:), rwsav(:), x(:)
Integer, Allocatable :: iwsav(:)
! .. Intrinsic Procedures ..
Intrinsic :: cos, max, min, sin, sqrt
! .. Executable Statements ..
Write (nout,*) 'C05MDF Example Program Results'
m = 2
Allocate (fvec(n),iwsav(14+m),x(n),rwsav(2*m*n+m*m+m+2*n+1+min(m, &
1)*max(n,3*m)))
! The following starting values provide a rough solution.
x(1) = 2.0E0_nag_wp
x(2) = 0.5E0_nag_wp
x(3) = 2.0E0_nag_wp
x(4) = 0.5E0_nag_wp
atol = sqrt(x02ajf())
rtol = sqrt(x02ajf())
cndtol = 0.0_nag_wp
astart = 0
icount = 0
irevcm = 0
ifail = -1
revcomm: Do
Call c05mdf(irevcm,n,x,fvec,atol,rtol,m,cndtol,astart,iwsav,rwsav, &
ifail)
Select Case (irevcm)
Case (1)
If (icount==imax) Then
Write (nout,*) 'Exiting after the maximum number of iterations'
Exit revcomm
End If
icount = icount + 1
! Insert print statements here to monitor progress if desired.
Cycle revcomm
Case (2)
! Evaluate functions at given point
fvec(1) = cos(x(3)) - x(1)
fvec(2) = sqrt(1.0_nag_wp-x(4)**2) - x(2)
fvec(3) = sin(x(1)) - x(3)
fvec(4) = x(2)**2 - x(4)
Cycle revcomm
Case Default
Exit revcomm
End Select
End Do revcomm
If (ifail==0 .Or. icount==imax) Then
! The NAG name equivalent of dnrm2 is f06ejf
fnorm = dnrm2(n,fvec,1)
Write (nout,*)
Write (nout,99999) 'Final 2-norm of the residuals after', icount, &
' iterations is ', fnorm
Write (nout,*)
Write (nout,*) 'Final approximate solution'
Write (nout,*)
Write (nout,99998)(x(i),i=1,n)
End If
99999 Format (1X,A,I4,A,E12.4)
99998 Format (1X,4F12.4)
End Program c05mdfe