! E04UCF Example Program Text ! Mark 24 Release. NAG Copyright 2012. Module e04ucfe_mod ! E04UCF Example Program Module: ! Parameters and User-defined Routines ! .. Use Statements .. Use nag_library, Only: nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nin = 5, nout = 6 Contains Subroutine objfun(mode,n,x,objf,objgrd,nstate,iuser,ruser) ! Routine to evaluate objective function and its 1st derivatives. ! .. Scalar Arguments .. Real (Kind=nag_wp), Intent (Out) :: objf Integer, Intent (Inout) :: mode Integer, Intent (In) :: n, nstate ! .. Array Arguments .. Real (Kind=nag_wp), Intent (Inout) :: objgrd(n), ruser(*) Real (Kind=nag_wp), Intent (In) :: x(n) Integer, Intent (Inout) :: iuser(*) ! .. Executable Statements .. If (mode==0 .Or. mode==2) Then objf = x(1)*x(4)*(x(1)+x(2)+x(3)) + x(3) End If If (mode==1 .Or. mode==2) Then objgrd(1) = x(4)*(2.0E0_nag_wp*x(1)+x(2)+x(3)) objgrd(2) = x(1)*x(4) objgrd(3) = x(1)*x(4) + 1.0E0_nag_wp objgrd(4) = x(1)*(x(1)+x(2)+x(3)) End If Return End Subroutine objfun Subroutine confun(mode,ncnln,n,ldcj,needc,x,c,cjac,nstate,iuser,ruser) ! Routine to evaluate the nonlinear constraints and their 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)**2 + x(2)**2 + x(3)**2 + x(4)**2 End If If (mode==1 .Or. mode==2) Then cjac(1,1) = 2.0E0_nag_wp*x(1) cjac(1,2) = 2.0E0_nag_wp*x(2) cjac(1,3) = 2.0E0_nag_wp*x(3) cjac(1,4) = 2.0E0_nag_wp*x(4) End If End If If (needc(2)>0) Then If (mode==0 .Or. mode==2) Then c(2) = x(1)*x(2)*x(3)*x(4) End If If (mode==1 .Or. mode==2) Then cjac(2,1) = x(2)*x(3)*x(4) cjac(2,2) = x(1)*x(3)*x(4) cjac(2,3) = x(1)*x(2)*x(4) cjac(2,4) = x(1)*x(2)*x(3) End If End If Return End Subroutine confun End Module e04ucfe_mod Program e04ucfe ! E04UCF Example Main Program ! .. Use Statements .. Use nag_library, Only: e04ucf, nag_wp Use e04ucfe_mod, Only: confun, nin, nout, objfun ! .. Implicit None Statement .. Implicit None ! .. Local Scalars .. Real (Kind=nag_wp) :: objf Integer :: i, ifail, iter, lda, ldcj, ldr, & liwork, lwork, n, nclin, ncnln, & sda, sdcjac ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: a(:,:), bl(:), bu(:), c(:), & cjac(:,:), clamda(:), objgrd(:), & r(:,:), work(:), x(:) Real (Kind=nag_wp) :: ruser(1) Integer, Allocatable :: istate(:), iwork(:) Integer :: iuser(1) ! .. Intrinsic Procedures .. Intrinsic :: max ! .. Executable Statements .. Write (nout,*) 'E04UCF Example Program Results' Flush (nout) ! Skip heading in data file Read (nin,*) Read (nin,*) n, 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 ldr = n If (ncnln==0 .And. nclin>0) Then lwork = 2*n**2 + 20*n + 11*nclin Else If (ncnln>0 .And. nclin>=0) Then lwork = 2*n**2 + n*nclin + 2*n*ncnln + 20*n + 11*nclin + 21*ncnln Else lwork = 20*n End If Allocate (istate(n+nclin+ncnln),iwork(liwork),a(lda,sda), & bl(n+nclin+ncnln),bu(n+nclin+ncnln),c(max(1, & ncnln)),cjac(ldcj,sdcjac),clamda(n+nclin+ncnln),objgrd(n),r(ldr,n), & x(n),work(lwork)) If (nclin>0) Then Read (nin,*)(a(i,1:sda),i=1,nclin) End If Read (nin,*) bl(1:(n+nclin+ncnln)) Read (nin,*) bu(1:(n+nclin+ncnln)) Read (nin,*) x(1:n) ifail = 0 Call e04ucf(n,nclin,ncnln,lda,ldcj,ldr,a,bl,bu,confun,objfun,iter, & istate,c,cjac,clamda,objf,objgrd,r,x,iwork,liwork,work,lwork,iuser, & ruser,ifail) End Program e04ucfe