! E04UGA Example Program Text
! Mark 29.3 Release. NAG Copyright 2023.
Module e04ugae_mod
! E04UGA 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 :: lcwsav = 1, liwsav = 550, &
llwsav = 20, lrwsav = 550, nin = 5, &
nout = 6
Contains
Subroutine confun(mode,ncnln,njnln,nnzjac,x,f,fjac,nstate,iuser,ruser)
! Computes the nonlinear constraint functions and their Jacobian.
! .. Scalar Arguments ..
Integer, Intent (Inout) :: mode
Integer, Intent (In) :: ncnln, njnln, nnzjac, nstate
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (Out) :: f(ncnln)
Real (Kind=nag_wp), Intent (Inout) :: fjac(nnzjac), ruser(*)
Real (Kind=nag_wp), Intent (In) :: x(njnln)
Integer, Intent (Inout) :: iuser(*)
! .. Intrinsic Procedures ..
Intrinsic :: cos, sin
! .. Executable Statements ..
If (mode==0 .Or. mode==2) Then
f(1) = 1000.0E+0_nag_wp*sin(-x(1)-0.25E+0_nag_wp) + &
1000.0E+0_nag_wp*sin(-x(2)-0.25E+0_nag_wp)
f(2) = 1000.0E+0_nag_wp*sin(x(1)-0.25E+0_nag_wp) + &
1000.0E+0_nag_wp*sin(x(1)-x(2)-0.25E+0_nag_wp)
f(3) = 1000.0E+0_nag_wp*sin(x(2)-x(1)-0.25E+0_nag_wp) + &
1000.0E+0_nag_wp*sin(x(2)-0.25E+0_nag_wp)
End If
If (mode==1 .Or. mode==2) Then
! Nonlinear Jacobian elements for column 1.
fjac(1) = -1000.0E+0_nag_wp*cos(-x(1)-0.25E+0_nag_wp)
fjac(2) = 1000.0E+0_nag_wp*cos(x(1)-0.25E+0_nag_wp) + &
1000.0E+0_nag_wp*cos(x(1)-x(2)-0.25E+0_nag_wp)
fjac(3) = -1000.0E+0_nag_wp*cos(x(2)-x(1)-0.25E+0_nag_wp)
! Nonlinear Jacobian elements for column 2.
fjac(4) = -1000.0E+0_nag_wp*cos(-x(2)-0.25E+0_nag_wp)
fjac(5) = -1000.0E+0_nag_wp*cos(x(1)-x(2)-0.25E+0_nag_wp)
fjac(6) = 1000.0E+0_nag_wp*cos(x(2)-x(1)-0.25E+0_nag_wp) + &
1000.0E+0_nag_wp*cos(x(2)-0.25E+0_nag_wp)
End If
Return
End Subroutine confun
Subroutine objfun(mode,nonln,x,objf,objgrd,nstate,iuser,ruser)
! Computes the nonlinear part of the objective function and its
! gradient
! .. Scalar Arguments ..
Real (Kind=nag_wp), Intent (Out) :: objf
Integer, Intent (Inout) :: mode
Integer, Intent (In) :: nonln, nstate
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (Inout) :: objgrd(nonln), ruser(*)
Real (Kind=nag_wp), Intent (In) :: x(nonln)
Integer, Intent (Inout) :: iuser(*)
! .. Executable Statements ..
If (mode==0 .Or. mode==2) Then
objf = 1.0E-6_nag_wp*x(3)**3 + 2.0E-6_nag_wp*x(4)**3/3.0E+0_nag_wp
End If
If (mode==1 .Or. mode==2) Then
objgrd(1) = 0.0E+0_nag_wp
objgrd(2) = 0.0E+0_nag_wp
objgrd(3) = 3.0E-6_nag_wp*x(3)**2
objgrd(4) = 2.0E-6_nag_wp*x(4)**2
End If
Return
End Subroutine objfun
End Module e04ugae_mod
Program e04ugae
! E04UGA Example Main Program
! .. Use Statements ..
Use e04ugae_mod, Only: confun, lcwsav, liwsav, llwsav, lrwsav, nin, &
nout, objfun
Use nag_library, Only: e04uga, e04wbf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Real (Kind=nag_wp) :: obj, sinf
Integer :: i, icol, ifail, iobj, j, jcol, &
leniz, lenz, m, miniz, minz, n, &
ncnln, ninf, njnln, nname, nnz, &
nonln, ns
Character (1) :: start
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:), bl(:), bu(:), clamda(:), &
xs(:), z(:)
Real (Kind=nag_wp) :: rwsav(lrwsav), user(1)
Integer, Allocatable :: ha(:), istate(:), iz(:), ka(:)
Integer :: iuser(1), iwsav(liwsav)
Logical :: lwsav(llwsav)
Character (80) :: cwsav(lcwsav)
Character (8), Allocatable :: names(:)
! .. Intrinsic Procedures ..
Intrinsic :: max
! .. Executable Statements ..
Write (nout,*) 'E04UGA Example Program Results'
! Skip heading in data file.
Read (nin,*)
Read (nin,*) n, m
Read (nin,*) ncnln, nonln, njnln
Read (nin,*) nnz, iobj, start, nname
Allocate (ha(nnz),ka(n+1),istate(n+m),a(nnz),bl(n+m),bu(n+m),xs(n+m), &
clamda(n+m),names(nname))
Read (nin,*) names(1:nname)
! Read the matrix A from data file. Set up KA.
jcol = 1
ka(jcol) = 1
Do i = 1, nnz
! Element ( HA( I ), ICOL ) is stored in A( I ).
Read (nin,*) a(i), ha(i), icol
If (icol<jcol) Then
! Elements not ordered by increasing column index.
Write (nout,99999) 'Element in column', icol, &
' found after element in column', jcol, '. Problem', ' abandoned.'
Go To 100
Else If (icol==jcol+1) Then
! Index in A of the start of the ICOL-th column equals I.
ka(icol) = i
jcol = icol
Else If (icol>jcol+1) Then
! Index in A of the start of the ICOL-th column equals I,
! but columns JCOL+1,JCOL+2,...,ICOL-1 are empty. Set the
! corresponding elements of KA to I.
ka((jcol+1):icol) = i
jcol = icol
End If
End Do
ka(n+1) = nnz + 1
! Columns N,N-1,...,ICOL+1 are empty. Set the corresponding
! elements of KA accordingly.
Do i = n, icol + 1, -1
ka(i) = ka(i+1)
End Do
Read (nin,*) bl(1:(n+m))
Read (nin,*) bu(1:(n+m))
If (start=='C') Then
Read (nin,*) istate(1:n)
Else If (start=='W') Then
Read (nin,*) istate(1:(n+m))
End If
Read (nin,*) xs(1:n)
If (ncnln>0) Then
Read (nin,*) clamda((n+1):(n+ncnln))
End If
! Initialise E04UGA
ifail = 0
Call e04wbf('E04UGA',cwsav,lcwsav,lwsav,llwsav,iwsav,liwsav,rwsav, &
lrwsav,ifail)
! Solve the problem.
! First call is a workspace query
leniz = max(500,n+m)
lenz = 500
Allocate (iz(leniz),z(lenz))
ifail = 1
Call e04uga(confun,objfun,n,m,ncnln,nonln,njnln,iobj,nnz,a,ha,ka,bl,bu, &
start,nname,names,ns,xs,istate,clamda,miniz,minz,ninf,sinf,obj,iz, &
leniz,z,lenz,iuser,user,lwsav,iwsav,rwsav,ifail)
If (ifail/=0 .And. ifail/=15 .And. ifail/=16) Then
Write (nout,99990) 'Query call to E04UGA failed with IFAIL =', ifail
Go To 100
End If
Deallocate (iz,z)
! The length of the workspace required for the basis factors in this
! problem is longer than the minimum returned by the query
lenz = 2*minz
leniz = 2*miniz
Allocate (iz(leniz),z(lenz))
ifail = -1
Call e04uga(confun,objfun,n,m,ncnln,nonln,njnln,iobj,nnz,a,ha,ka,bl,bu, &
start,nname,names,ns,xs,istate,clamda,miniz,minz,ninf,sinf,obj,iz, &
leniz,z,lenz,iuser,user,lwsav,iwsav,rwsav,ifail)
Select Case (ifail)
Case (0:6)
Write (nout,*)
Write (nout,99998)
Write (nout,*)
Do i = 1, n
Write (nout,99997) i, istate(i), xs(i), clamda(i)
End Do
Write (nout,*)
Write (nout,*)
Write (nout,99995)
Write (nout,*)
If (ncnln>0) Then
Do i = n + 1, n + ncnln
j = i - n
Write (nout,99994) j, istate(i), xs(i), clamda(i)
End Do
End If
If ((ncnln==0) .And. (m==1) .And. (a(1)==0.0E0_nag_wp)) Then
Write (nout,99992) istate(n+1), xs(n+1), clamda(n+1)
Else If (m>ncnln) Then
Do i = n + ncnln + 1, n + m
j = i - n - ncnln
If (i-n==iobj) Then
Write (nout,99993) istate(i), xs(i), clamda(i)
Else
Write (nout,99996) j, istate(i), xs(i), clamda(i)
End If
End Do
End If
Write (nout,*)
Write (nout,*)
Write (nout,99991) obj
End Select
100 Continue
99999 Format (/,1X,A,I5,A,I5,A,A)
99998 Format (1X,'Variable',2X,'Istate',5X,'Value',9X,'Lagr Mult')
99997 Format (1X,'Varble',1X,I2,1X,I3,4X,1P,G14.6,2X,1P,G12.4)
99996 Format (1X,'LinCon',1X,I2,1X,I3,4X,1P,G14.6,2X,1P,G12.4)
99995 Format (1X,'Constrnt',2X,'Istate',5X,'Value',9X,'Lagr Mult')
99994 Format (1X,'NlnCon',1X,I2,1X,I3,4X,1P,G14.6,2X,1P,G12.4)
99993 Format (1X,'Free Row',2X,I3,4X,1P,G14.6,2X,1P,G12.4)
99992 Format (1X,'DummyRow',2X,I3,4X,1P,G14.6,2X,1P,G12.4)
99991 Format (1X,'Final objective value = ',1P,G15.7)
99990 Format (1X,A,I5)
End Program e04ugae