!   E04CBF Example Program Text
!   Mark 23 Release. NAG Copyright 2011.
    MODULE e04cbfe_mod

!      E04CBF Example Program Module:
!             Parameters and User-defined Routines

!      .. Use Statements ..
       USE nag_library, ONLY : nag_wp
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       INTEGER, PARAMETER                  :: nout = 6
    CONTAINS
       SUBROUTINE funct(n,xc,fc,iuser,ruser)

!         .. Implicit None Statement ..
          IMPLICIT NONE
!         .. Scalar Arguments ..
          REAL (KIND=nag_wp), INTENT (OUT)    :: fc
          INTEGER, INTENT (IN)                :: n
!         .. Array Arguments ..
          REAL (KIND=nag_wp), INTENT (INOUT)  :: ruser(*)
          REAL (KIND=nag_wp), INTENT (IN)     :: xc(n)
          INTEGER, INTENT (INOUT)             :: iuser(*)
!         .. Intrinsic Functions ..
          INTRINSIC                              exp
!         .. Executable Statements ..
          fc = exp(xc(1))*(4.0_nag_wp*xc(1)*(xc(1)+xc(2))+2.0_nag_wp*xc(2)*(xc &
             (2)+1.0_nag_wp)+1.0_nag_wp)

          RETURN

       END SUBROUTINE funct
       SUBROUTINE monit(fmin,fmax,sim,n,ncall,serror,vratio,iuser,ruser)

!         .. Implicit None Statement ..
          IMPLICIT NONE
!         .. Scalar Arguments ..
          REAL (KIND=nag_wp), INTENT (IN)     :: fmax, fmin, serror, vratio
          INTEGER, INTENT (IN)                :: n, ncall
!         .. Array Arguments ..
          REAL (KIND=nag_wp), INTENT (INOUT)  :: ruser(*)
          REAL (KIND=nag_wp), INTENT (IN)     :: sim(n+1,n)
          INTEGER, INTENT (INOUT)             :: iuser(*)
!         .. Executable Statements ..
          WRITE (nout,*)
          WRITE (nout,99999) ncall
          WRITE (nout,99998) fmin
          WRITE (nout,99997)
          WRITE (nout,99996) sim(1:(n+1),1:n)
          WRITE (nout,99995) serror
          WRITE (nout,99994) vratio

          RETURN

99999     FORMAT (1X,'There have been',I5,' function calls')
99998     FORMAT (1X,'The smallest function value is',F10.4)
99997     FORMAT (1X,'The simplex is')
99996     FORMAT (1X,2F10.4)
99995     FORMAT (1X,'The standard deviation in function values at the ', &
             'vertices of the simplex is',F10.4)
99994     FORMAT (1X,'The linearized volume ratio of the current simplex', &
             ' to the starting one is',F10.4)
       END SUBROUTINE monit
    END MODULE e04cbfe_mod
    PROGRAM e04cbfe

!      E04CBF Example Main Program

!      .. Use Statements ..
       USE nag_library, ONLY : e04cbf, e04cbk, nag_wp, x02ajf
       USE e04cbfe_mod, ONLY : funct, monit, nout
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       INTEGER, PARAMETER                  :: n = 2
!      .. Local Scalars ..
       REAL (KIND=nag_wp)                  :: f, tolf, tolx
       INTEGER                             :: ifail, maxcal
       LOGICAL                             :: monitoring
!      .. Local Arrays ..
       REAL (KIND=nag_wp)                  :: ruser(1), x(n)
       INTEGER                             :: iuser(1)
!      .. Intrinsic Functions ..
       INTRINSIC                              sqrt
!      .. Executable Statements ..
       WRITE (nout,*) 'E04CBF Example Program Results'

!      Set MONITORING to .TRUE. to obtain monitoring information

       monitoring = .FALSE.

       x(1:n) = (/ -1.0_nag_wp, 1.0_nag_wp/)
       tolf = sqrt(x02ajf())
       tolx = sqrt(tolf)
       maxcal = 100

       ifail = 0

       IF ( .NOT. monitoring) THEN

          CALL e04cbf(n,x,f,tolf,tolx,funct,e04cbk,maxcal,iuser,ruser,ifail)

       ELSE

          CALL e04cbf(n,x,f,tolf,tolx,funct,monit,maxcal,iuser,ruser,ifail)

       END IF

       WRITE (nout,*)
       WRITE (nout,99999) f
       WRITE (nout,99998) x(1:n)

99999  FORMAT (1X,'The final function value is',F12.4)
99998  FORMAT (1X,'at the point',2F12.4)
    END PROGRAM e04cbfe