! E04HCF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
Module e04hcfe_mod
! E04HCF 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 :: funct
! .. Parameters ..
Integer, Parameter, Public :: liw = 1, n = 4, nout = 6
Integer, Parameter, Public :: lw = 3*n
Contains
Subroutine funct(iflag,n,xc,fc,gc,iw,liw,w,lw)
! Routine to evaluate objective function and its 1st derivatives.
! .. Scalar Arguments ..
Real (Kind=nag_wp), Intent (Out) :: fc
Integer, Intent (Inout) :: iflag
Integer, Intent (In) :: liw, lw, n
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (Out) :: gc(n)
Real (Kind=nag_wp), Intent (Inout) :: w(lw)
Real (Kind=nag_wp), Intent (In) :: xc(n)
Integer, Intent (Inout) :: iw(liw)
! .. Executable Statements ..
fc = (xc(1)+10.0_nag_wp*xc(2))**2 + 5.0_nag_wp*(xc(3)-xc(4))**2 + &
(xc(2)-2.0_nag_wp*xc(3))**4 + 10.0_nag_wp*(xc(1)-xc(4))**4
gc(1) = 2.0_nag_wp*(xc(1)+10.0_nag_wp*xc(2)) + &
40.0_nag_wp*(xc(1)-xc(4))**3
gc(2) = 20.0_nag_wp*(xc(1)+10.0_nag_wp*xc(2)) + &
4.0_nag_wp*(xc(2)-2.0_nag_wp*xc(3))**3
gc(3) = 10.0_nag_wp*(xc(3)-xc(4)) - 8.0_nag_wp*(xc(2)-2.0_nag_wp*xc(3) &
)**3
gc(4) = 10.0_nag_wp*(xc(4)-xc(3)) - 40.0_nag_wp*(xc(1)-xc(4))**3
Return
End Subroutine funct
End Module e04hcfe_mod
Program e04hcfe
! E04HCF Example Main Program
! .. Use Statements ..
Use e04hcfe_mod, Only: funct, liw, lw, n, nout
Use nag_library, Only: e04hcf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Real (Kind=nag_wp) :: f
Integer :: ifail
! .. Local Arrays ..
Real (Kind=nag_wp) :: g(n), w(lw), x(n)
Integer :: iw(liw)
! .. Executable Statements ..
Write (nout,*) 'E04HCF Example Program Results'
! Set up an arbitrary point at which to check the 1st derivatives
x(1:n) = (/1.46_nag_wp,-0.82_nag_wp,0.57_nag_wp,1.21_nag_wp/)
Write (nout,*)
Write (nout,*) 'The test point is'
Write (nout,99999) x(1:n)
ifail = -1
Call e04hcf(n,funct,x,f,g,iw,liw,w,lw,ifail)
If (ifail>=0) Then
Write (nout,*)
If (ifail==0) Then
Write (nout,*) '1st derivatives are consistent with function values'
Else
Write (nout,*) 'Probable error in calculation of 1st derivatives'
End If
Write (nout,*)
Write (nout,99998) 'At the test point, FUNCT gives the function value' &
, f
Write (nout,*) 'and the 1st derivatives'
Write (nout,99997) g(1:n)
End If
99999 Format (1X,4F10.4)
99998 Format (1X,A,1P,E12.4)
99997 Format (1X,1P,4E12.3)
End Program e04hcfe