! E04VHF Example Program Text ! Mark 24 Release. NAG Copyright 2012. Module e04vhfe_mod ! E04VHF Example Program Module: ! Parameters and User-defined Routines ! .. Use Statements .. Use nag_library, Only: nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: lencw = 600, leniw = 600, & lenrw = 600, nin = 5, nout = 6 Contains Subroutine usrfun(status,n,x,needf,nf,f,needg,leng,g,cuser,iuser,ruser) ! .. Scalar Arguments .. Integer, Intent (In) :: leng, n, needf, needg, nf Integer, Intent (Inout) :: status ! .. Array Arguments .. Real (Kind=nag_wp), Intent (Inout) :: f(nf), g(leng), ruser(*) Real (Kind=nag_wp), Intent (In) :: x(n) Integer, Intent (Inout) :: iuser(*) Character (8), Intent (Inout) :: cuser(*) ! .. Intrinsic Procedures .. Intrinsic :: cos, sin ! .. Executable Statements .. If (needf>0) Then ! The nonlinear components of f_i(x) need to be assigned, ! for i = 1 to NF 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) ! N.B. in this example there is no need to assign for the wholly ! linear components f_4(x) and f_5(x). f(6) = 1.0E-6_nag_wp*x(3)**3 + 2.0E-6_nag_wp*x(4)**3/3.0E+0_nag_wp End If If (needg>0) Then ! The derivatives of the function f_i(x) need to be assigned. ! G(k) should be set to partial derivative df_i(x)/dx_j where ! i = IGFUN(k) and j = IGVAR(k), for k = 1 to LENG. g(1) = -1000.0E+0_nag_wp*cos(-x(1)-0.25E+0_nag_wp) g(2) = -1000.0E+0_nag_wp*cos(-x(2)-0.25E+0_nag_wp) g(3) = 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) g(4) = -1000.0E+0_nag_wp*cos(x(1)-x(2)-0.25E+0_nag_wp) g(5) = -1000.0E+0_nag_wp*cos(x(2)-x(1)-0.25E+0_nag_wp) g(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) g(7) = 3.0E-6_nag_wp*x(3)**2 g(8) = 2.0E-6_nag_wp*x(4)**2 End If Return End Subroutine usrfun End Module e04vhfe_mod Program e04vhfe ! E04VHF Example Main Program ! .. Use Statements .. Use nag_library, Only: e04vgf, e04vhf, e04vmf, nag_wp Use e04vhfe_mod, Only: lencw, leniw, lenrw, nin, nout, usrfun ! .. Implicit None Statement .. Implicit None ! .. Local Scalars .. Real (Kind=nag_wp) :: objadd, sinf Integer :: i, ifail, lena, leng, n, nea, & neg, nf, nfname, ninf, ns, & nxname, objrow, start Character (8) :: prob ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: a(:), f(:), flow(:), fmul(:), & fupp(:), x(:), xlow(:), xmul(:), & xupp(:) Real (Kind=nag_wp) :: ruser(1), rw(lenrw) Integer, Allocatable :: fstate(:), iafun(:), igfun(:), & javar(:), jgvar(:), xstate(:) Integer :: iuser(1), iw(leniw) Character (8) :: cuser(1), cw(lencw) Character (8), Allocatable :: fnames(:), xnames(:) ! .. Intrinsic Procedures .. Intrinsic :: max ! .. Executable Statements .. Write (nout,*) 'E04VHF Example Program Results' Flush (nout) ! Skip heading in data file Read (nin,*) Read (nin,*) n, nf Read (nin,*) nea, neg, objrow, start lena = max(1,nea) leng = max(1,neg) nxname = n nfname = nf Allocate (iafun(lena),javar(lena),igfun(leng),jgvar(leng),xstate(n), & fstate(nf),a(lena),xlow(n),xupp(n),flow(nf),fupp(nf),x(n),xmul(n), & f(nf),fmul(nf),xnames(nxname),fnames(nfname)) ! Read the variable names Read (nin,*) xnames(1:nxname) ! Read the function names Read (nin,*) fnames(1:nfname) ! Read the sparse matrix A, the linear part of F Do i = 1, nea ! For each element read row, column, A(row,column) Read (nin,*) iafun(i), javar(i), a(i) End Do ! Read the structure of sparse matrix G, the nonlinear part of F Do i = 1, neg ! For each element read row, column Read (nin,*) igfun(i), jgvar(i) End Do ! Read the lower and upper bounds on the variables Do i = 1, n Read (nin,*) xlow(i), xupp(i) End Do ! Read the lower and upper bounds on the functions Do i = 1, nf Read (nin,*) flow(i), fupp(i) End Do ! Initialise X, XSTATE, XMUL, F, FSTATE, FMUL Read (nin,*) x(1:n) Read (nin,*) xstate(1:n) Read (nin,*) xmul(1:n) Read (nin,*) f(1:nf) Read (nin,*) fstate(1:nf) Read (nin,*) fmul(1:nf) objadd = 0.0E0_nag_wp prob = ' ' ! Call E04VGF to initialise E04VHF. ifail = 0 Call e04vgf(cw,lencw,iw,leniw,rw,lenrw,ifail) ! By default E04VHF does not print monitoring ! information. Set the print file unit or the summary ! file unit to get information. ifail = 0 Call e04vmf('Print file',nout,cw,iw,rw,ifail) ! Solve the problem. ifail = 0 Call e04vhf(start,nf,n,nxname,nfname,objadd,objrow,prob,usrfun,iafun, & javar,a,lena,nea,igfun,jgvar,leng,neg,xlow,xupp,xnames,flow,fupp, & fnames,x,xstate,xmul,f,fstate,fmul,ns,ninf,sinf,cw,lencw,iw,leniw,rw, & lenrw,cuser,iuser,ruser,ifail) Write (nout,*) Write (nout,99999) f(objrow) Write (nout,99998) x(1:n) 99999 Format (1X,'Final objective value = ',F11.1) 99998 Format (1X,'Optimal X = ',7F9.2) End Program e04vhfe