NAG Library Manual, Mark 29.3
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
!   E04USF Example Program Text
!   Mark 29.3 Release. NAG Copyright 2023.

    Module e04usfe_mod

!     E04USF 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                           :: confun, objfun
!     .. Parameters ..
      Integer, Parameter, Public       :: nin = 5, nout = 6
    Contains
      Subroutine objfun(mode,m,n,ldfj,needfi,x,f,fjac,nstate,iuser,ruser)
!       Routine to evaluate the subfunctions and their 1st derivatives.

!       .. Parameters ..
        Real (Kind=nag_wp), Parameter  :: a(44) = (/8.0E0_nag_wp,8.0E0_nag_wp, &
                                          10.0E0_nag_wp,10.0E0_nag_wp,         &
                                          10.0E0_nag_wp,10.0E0_nag_wp,         &
                                          12.0E0_nag_wp,12.0E0_nag_wp,         &
                                          12.0E0_nag_wp,12.0E0_nag_wp,         &
                                          14.0E0_nag_wp,14.0E0_nag_wp,         &
                                          14.0E0_nag_wp,16.0E0_nag_wp,         &
                                          16.0E0_nag_wp,16.0E0_nag_wp,         &
                                          18.0E0_nag_wp,18.0E0_nag_wp,         &
                                          20.0E0_nag_wp,20.0E0_nag_wp,         &
                                          20.0E0_nag_wp,22.0E0_nag_wp,         &
                                          22.0E0_nag_wp,22.0E0_nag_wp,         &
                                          24.0E0_nag_wp,24.0E0_nag_wp,         &
                                          24.0E0_nag_wp,26.0E0_nag_wp,         &
                                          26.0E0_nag_wp,26.0E0_nag_wp,         &
                                          28.0E0_nag_wp,28.0E0_nag_wp,         &
                                          30.0E0_nag_wp,30.0E0_nag_wp,         &
                                          30.0E0_nag_wp,32.0E0_nag_wp,         &
                                          32.0E0_nag_wp,34.0E0_nag_wp,         &
                                          36.0E0_nag_wp,36.0E0_nag_wp,         &
                                          38.0E0_nag_wp,38.0E0_nag_wp,         &
                                          40.0E0_nag_wp,42.0E0_nag_wp/)
!       .. Scalar Arguments ..
        Integer, Intent (In)           :: ldfj, m, n, needfi, nstate
        Integer, Intent (Inout)        :: mode
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: f(m)
        Real (Kind=nag_wp), Intent (Inout) :: fjac(ldfj,n), ruser(*)
        Real (Kind=nag_wp), Intent (In) :: x(n)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Local Scalars ..
        Real (Kind=nag_wp)             :: ai, temp, x1, x2
        Integer                        :: i
        Logical                        :: mode02, mode12
!       .. Intrinsic Procedures ..
        Intrinsic                      :: exp
!       .. Executable Statements ..
        x1 = x(1)
        x2 = x(2)

        If (mode==0 .And. needfi>0) Then
          f(needfi) = x1 + (0.49E0_nag_wp-x1)*exp(-x2*(a(needfi)-8.0E0_nag_wp) &
            )
        Else

          mode02 = (mode==0 .Or. mode==2)
          mode12 = (mode==1 .Or. mode==2)

          Do i = 1, m

            ai = a(i)
            temp = exp(-x2*(ai-8.0E0_nag_wp))

            If (mode02) Then
              f(i) = x1 + (0.49E0_nag_wp-x1)*temp
            End If

            If (mode12) Then
              fjac(i,1) = 1.0E0_nag_wp - temp
              fjac(i,2) = -(0.49E0_nag_wp-x1)*(ai-8.0E0_nag_wp)*temp
            End If

          End Do
        End If

        Return

      End Subroutine objfun
      Subroutine confun(mode,ncnln,n,ldcj,needc,x,c,cjac,nstate,iuser,ruser)
!       Routine to evaluate the nonlinear constraint and its 1st
!       derivatives.

!       .. Scalar Arguments ..
        Integer, Intent (In)           :: ldcj, n, ncnln, nstate
        Integer, Intent (Inout)        :: mode
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: c(ncnln)
        Real (Kind=nag_wp), Intent (Inout) :: cjac(ldcj,n), ruser(*)
        Real (Kind=nag_wp), Intent (In) :: x(n)
        Integer, Intent (Inout)        :: iuser(*)
        Integer, Intent (In)           :: needc(ncnln)
!       .. Executable Statements ..
        If (nstate==1) Then

!         First call to CONFUN.  Set all Jacobian elements to zero.
!         Note that this will only work when 'Derivative Level = 3'
!         (the default; see Section 11.2).

          cjac(1:ncnln,1:n) = 0.0E0_nag_wp
        End If

        If (needc(1)>0) Then

          If (mode==0 .Or. mode==2) Then
            c(1) = -x(1)*x(2) + 0.49E0_nag_wp*x(2)
          End If

          If (mode==1 .Or. mode==2) Then
            cjac(1,1) = -x(2)
            cjac(1,2) = -x(1) + 0.49E0_nag_wp
          End If

        End If

        Return

      End Subroutine confun
    End Module e04usfe_mod
    Program e04usfe

!     E04USF Example Main Program

!     .. Use Statements ..
      Use e04usfe_mod, Only: confun, nin, nout, objfun
      Use nag_library, Only: e04usf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: objf
      Integer                          :: i, ifail, iter, lda, ldcj, ldfj,     &
                                          ldr, liwork, lwork, m, n, nclin,     &
                                          ncnln, sda, sdcjac
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: a(:,:), bl(:), bu(:), c(:),          &
                                          cjac(:,:), clamda(:), f(:),          &
                                          fjac(:,:), r(:,:), work(:), x(:),    &
                                          y(:)
      Real (Kind=nag_wp)               :: user(1)
      Integer, Allocatable             :: istate(:), iwork(:)
      Integer                          :: iuser(1)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: max
!     .. Executable Statements ..
      Write (nout,*) 'E04USF Example Program Results'
      Flush (nout)

!     Skip heading in data file
      Read (nin,*)

      Read (nin,*) m, n
      Read (nin,*) nclin, ncnln
      liwork = 3*n + nclin + 2*ncnln
      lda = max(1,nclin)

      If (nclin>0) Then
        sda = n
      Else
        sda = 1
      End If

      ldcj = max(1,ncnln)

      If (ncnln>0) Then
        sdcjac = n
      Else
        sdcjac = 1
      End If

      ldfj = m
      ldr = n

      If (ncnln==0 .And. nclin>0) Then
        lwork = 2*n**2 + 20*n + 11*nclin + m*(n+3)
      Else If (ncnln>0 .And. nclin>=0) Then
        lwork = 2*n**2 + n*nclin + 2*n*ncnln + 20*n + 11*nclin + 21*ncnln +    &
          m*(n+3)
      Else
        lwork = 20*n + m*(n+3)
      End If

      Allocate (istate(n+nclin+ncnln),iwork(liwork),a(lda,sda),                &
        bl(n+nclin+ncnln),bu(n+nclin+ncnln),y(m),c(max(1,                      &
        ncnln)),cjac(ldcj,sdcjac),f(m),fjac(ldfj,n),clamda(n+nclin+ncnln),     &
        r(ldr,n),x(n),work(lwork))

      If (nclin>0) Then
        Read (nin,*)(a(i,1:sda),i=1,nclin)
      End If

      Read (nin,*) y(1:m)
      Read (nin,*) bl(1:(n+nclin+ncnln))
      Read (nin,*) bu(1:(n+nclin+ncnln))
      Read (nin,*) x(1:n)

!     Solve the problem

      ifail = 0
      Call e04usf(m,n,nclin,ncnln,lda,ldcj,ldfj,ldr,a,bl,bu,y,confun,objfun,   &
        iter,istate,c,cjac,f,fjac,clamda,objf,r,x,iwork,liwork,work,lwork,     &
        iuser,user,ifail)

    End Program e04usfe