! E04MWF Example Program Text
! Mark 29.2 Release. NAG Copyright 2023.
Module e04mwfe_mod
! E04MWF 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 :: qphx
Contains
Subroutine qphx(ncolh,x,hx,nstate,cuser,iuser,ruser)
! Subroutine to compute H*x.
! Note: IUSER and RUSER contain the following data:
! RUSER(1:NNZH) = H(1:NNZH)
! IUSER(1:NCOLH+1) = ICCOLH(1:NCOLH+1)
! IUSER(NCOLH+2:NNZH+NCOLH+1) = IROWH(1:NNZH)
! .. Scalar Arguments ..
Integer, Intent (In) :: ncolh, nstate
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (Out) :: hx(ncolh)
Real (Kind=nag_wp), Intent (Inout) :: ruser(*)
Real (Kind=nag_wp), Intent (In) :: x(ncolh)
Integer, Intent (Inout) :: iuser(*)
Character (8), Intent (Inout) :: cuser(*)
! .. Local Scalars ..
Integer :: icol, idx, iend, irow, istart
! .. Executable Statements ..
hx(1:ncolh) = 0.0E0_nag_wp
Do icol = 1, ncolh
istart = iuser(icol)
iend = iuser(icol+1) - 1
Do idx = istart, iend
irow = iuser(ncolh+1+idx)
hx(irow) = hx(irow) + x(icol)*ruser(idx)
If (irow/=icol) Then
hx(icol) = hx(icol) + x(irow)*ruser(idx)
End If
End Do
End Do
Return
End Subroutine qphx
End Module e04mwfe_mod
Program e04mwfe
! E04MWF Example Main Program
! .. Use Statements ..
Use e04mwfe_mod, Only: qphx
Use nag_library, Only: e04mwf, e04npf, e04nqf, e04ntf, nag_wp, x04acf, &
x04adf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: lencw = 600, leniw = 600, &
lenrw = 600, nin = 5, nout = 6, &
outfile = 42
Character (*), Parameter :: outfile_name = 'e04mwfe.mps'
! .. Local Scalars ..
Real (Kind=nag_wp) :: obj, objadd, sinf
Integer :: i, icol, ierr, ifail, iobj, jcol, &
lenc, lintvar, m, minmax, n, ncolh, &
ne, ninf, nname, nnzh, ns
Logical :: verbose_output
Character (1) :: istart
Character (8) :: prob
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: acol(:), bl(:), bu(:), c(:), h(:), &
pi(:), rc(:), ruser(:), x(:)
Real (Kind=nag_wp) :: rw(lenrw)
Integer, Allocatable :: helast(:), hs(:), iccolh(:), &
idxc(:), inda(:), intvar(:), &
irowh(:), iuser(:), loca(:)
Integer :: iw(leniw)
Character (8) :: cuser(1), cw(lencw), pnames(5)
Character (8), Allocatable :: names(:)
! .. Intrinsic Procedures ..
Intrinsic :: max
! .. Executable Statements ..
Write (nout,*) 'E04MWF Example Program Results'
! Skip heading in data file.
Read (nin,*)
Read (nin,*) n, m
Read (nin,*) ne, iobj, ncolh, nnzh, nname
Allocate (inda(ne),loca(n+1),helast(n+m),hs(n+m),acol(ne),bl(n+m), &
bu(n+m),x(n+m),pi(m),rc(n+m),names(nname),h(nnzh),irowh(nnzh), &
iccolh(ncolh+1))
! Read array of names
Read (nin,*) names(1:nname)
! Read the matrix ACOL from data file. Set up LOCA.
jcol = 1
loca(jcol) = 1
Do i = 1, ne
! Element ( INDA( I ), ICOL ) is stored in ACOL( I ).
Read (nin,*) acol(i), inda(i), icol
If (icol<jcol) Then
! Elements not ordered by increasing column index.
Write (nout,99998) 'Element in column', icol, &
' found after element in column', jcol, '. Problem', ' abandoned.'
Go To 100
Else If (icol==jcol+1) Then
! Index in ACOL of the start of the ICOL-th column equals I.
loca(icol) = i
jcol = icol
Else If (icol>jcol+1) Then
! Columns JCOL+1,JCOL+2,...,ICOL-1 are empty. Set the
! corresponding elements of LOCA to I.
loca((jcol+1):icol) = i
jcol = icol
End If
End Do
loca(n+1) = ne + 1
! Columns N,N-1,...,ICOL+1 are empty. Set the corresponding
! elements of LOCA accordingly.
Do i = n, icol + 1, -1
loca(i) = loca(i+1)
End Do
! Read the matrix H from data file. Set up ICCOLH.
jcol = 1
iccolh(1) = 1
Do i = 1, nnzh
! Element ( IROWH( I ), ICOL ) is stored in H( I ).
Read (nin,*) h(i), irowh(i), icol
If (icol<jcol) Then
! Elements not ordered by increasing column index
Write (nout,99998) 'Element in column', icol, &
' found after element in column', jcol, '. Problem', ' abandoned.'
Go To 100
Else If (icol==jcol+1) Then
! Index in ICCOLH of the start of the ICOL-th column equals I.
iccolh(icol) = i
jcol = icol
Else If (icol>jcol+1) Then
! Columns JCOL+1,JCOL+2,...,ICOL-1 are empty. Set the
! corresponding elements of ICCOLH to I.
iccolh((jcol+1):icol) = i
jcol = icol
End If
End Do
iccolh(ncolh+1) = nnzh + 1
! Columns N,N-1,...,ICOL+1 are empty. Set the corresponding
! elements of ICCOLH accordingly.
Do i = n, icol + 1, -1
iccolh(i) = iccolh(i+1)
End Do
! Read lower and upper bounds
Read (nin,*) bl(1:(n+m))
Read (nin,*) bu(1:(n+m))
! Set cold start
istart = 'C'
hs(1:(n+m)) = 0.0_nag_wp
! Read the initial point x_0
Read (nin,*) x(1:n)
! Print dimensions of the QP problem
Write (nout,99999) n, m
! Call e04npf to initialize E04NQF.
ifail = 0
Call e04npf(cw,lencw,iw,leniw,rw,lenrw,ifail)
! Set this to .True. to cause e04nqf to produce intermediate
! progress output
verbose_output = .False.
If (verbose_output) Then
! By default e04nqf does not print monitoring
! information. Set the print file unit or the summary
! file unit to get information.
ifail = 0
Call e04ntf('Print file',nout,cw,iw,rw,ifail)
End If
! We have no explicit objective vector so set LENC = 0; the
! objective vector is stored in row IOBJ of ACOL.
lenc = 0
Allocate (c(max(1,lenc)),iuser(ncolh+1+nnzh),ruser(nnzh))
objadd = 0.0E0_nag_wp
prob = ' '
! Do not allow any elastic variables (i.e. they cannot be
! infeasible). If we'd set optional argument "Elastic mode" to 0,
! we wouldn't need to set the individual elements of array HELAST.
helast(1:(n+m)) = 0
If (ncolh>0) Then
! Store the non zeros of H in ruser for use by qphx
ruser(1:nnzh) = h(1:nnzh)
! Store iccolh and irowh in iuser for use by qphx
iuser(1:ncolh+1) = iccolh(1:ncolh+1)
iuser(ncolh+2:nnzh+ncolh+1) = irowh(1:nnzh)
End If
! Call e04nqf to solve the problem.
ifail = 0
Call e04nqf(istart,qphx,m,n,ne,nname,lenc,ncolh,iobj,objadd,prob,acol, &
inda,loca,bl,bu,c,names,helast,hs,x,pi,rc,ns,ninf,sinf,obj,cw,lencw, &
iw,leniw,rw,lenrw,cuser,iuser,ruser,ifail)
! Print objective function and optimal x*
Write (nout,*)
Write (nout,99997) obj
Write (nout,99996) x(1:n)
! Set the rest of inputs for e04mwf. Due to IOBJ > 0, LENC = 0 and
! C and IDXC will not be referenced.
lintvar = 0
Allocate (idxc(lenc),intvar(lintvar))
c(:) = 0
idxc(:) = 0
intvar(:) = 0
pnames(:) = ' '
pnames(1) = 'USRPNAME'
pnames(2) = 'OBJ.....'
minmax = -1
! Open data file for writing
ifail = 0
Call x04acf(outfile,outfile_name,1,ifail)
! Call e04mwf to store the problem in a MPS file with fixed format.
ifail = 0
Call e04mwf(outfile,n,m,lenc,ne,ncolh,nnzh,lintvar,idxc,c,iobj,acol, &
inda,loca,bl,bu,pnames,nname,names,h,irowh,iccolh,minmax,intvar,ifail)
Write (nout,99995) outfile_name
! Close data file
ierr = 0
Call x04adf(outfile,ierr)
100 Continue
99999 Format (1X,/,1X,'QP problem contains ',I3,' variables and ',I3, &
' linear constraints')
99998 Format (1X,A,I5,A,I5,A,A)
99997 Format (1X,'Final objective value = ',1P,E11.3)
99996 Format (1X,'Optimal X = ',7F9.2)
99995 Format (1X,/,1X,'MPS file was written: ',A)
End Program e04mwfe