Program h02cbfe
! H02CBF Example Program Text
! Mark 26.2 Release. NAG Copyright 2017.
! .. Use Statements ..
Use nag_library, Only: e04nfu, h02cbf, h02cbu, h02cdf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: lintvr = 1, mdepth = 30, nin = 5, &
nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: obj
Integer :: i, ifail, j, lda, ldh, liwrk, lwrk, &
n, nclin, strtgy
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:,:), ax(:), bl(:), bu(:), &
clamda(:), cvec(:), h(:,:), wrk(:), &
xs(:)
Integer, Allocatable :: intvar(:), istate(:), iwrk(:)
! .. Executable Statements ..
Write (nout,*) 'H02CBF Example Program Results'
! Skip heading in data file
Read (nin,*)
Read (nin,*) n, nclin
lda = nclin
ldh = n
liwrk = 2*n + 3 + 2*mdepth
! LWRK for default problem-type QP2
If (nclin==0) Then
lwrk = n**2 + 9*n + 4*mdepth
Else
lwrk = 2*n**2 + 9*n + 5*nclin + 4*mdepth
End If
Allocate (a(lda,n),ax(nclin),bl(n+nclin),bu(n+nclin),clamda(n+nclin), &
cvec(n),h(ldh,n),xs(n),intvar(lintvr),istate(n+nclin),iwrk(liwrk), &
wrk(lwrk))
Read (nin,*)(cvec(i),i=1,n)
Read (nin,*)((a(i,j),j=1,n),i=1,nclin)
Read (nin,*)(bl(i),i=1,n+nclin)
Read (nin,*)(bu(i),i=1,n+nclin)
Read (nin,*)(xs(i),i=1,n)
Read (nin,*)((h(i,j),j=1,n),i=1,n)
strtgy = 2
intvar(1) = 4
Call h02cdf('Nolist')
Call h02cdf('Print Level = 0')
! Solve the problem
ifail = 0
Call h02cbf(n,nclin,a,lda,bl,bu,cvec,h,ldh,e04nfu,intvar,lintvr,mdepth, &
istate,xs,obj,ax,clamda,strtgy,iwrk,liwrk,wrk,lwrk,h02cbu,ifail)
! Print out the best integer solution found
Write (nout,99999) obj, (i,xs(i),i=1,n)
99999 Format (' Optimal Integer Value is = ',E20.8,/,' Components are ', &
7(/,' X(',I3,') = ',F15.8))
End Program h02cbfe