! E04SBF Example Program Text
! Mark 31.1 Release. nAG Copyright 2025.
Program e04sbfe
! .. Use Statements ..
Use iso_c_binding, Only: c_ptr, c_null_ptr
Use nag_library, Only: e04mtf, e04mtu, e04raf, e04rff, e04rhf, e04rjf, &
e04rzf, e04saf, e04sbf, e04zmf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
Character (*), Parameter :: fname = 'data.dat'
! .. Local Scalars ..
Type (c_ptr) :: cpuser, handle, rehandle
Integer :: idlc, ifail, m, n, nnza, nnzc, nnzu, &
infile, stat
Character(8) :: ftype
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:), bla(:), bua(:), c(:), u(:), &
x(:), xl(:), xu(:)
Real (Kind=nag_wp) :: h(1), rinfo(100), ruser(1), &
stats(100)
Integer, Allocatable :: cindex(:), icola(:), irowa(:)
Integer :: icolh(1), irowh(1), iuser(2), &
pinfo(100)
! .. Executable Statements ..
Continue
Write(nout,*) 'E04SBF Example Program results'
Write(nout,*) ''
Write(nout,*) 'Setting up original handle...'
! Skip Header in data file
Read (nin,*)
! Read dimensions of the problem
Read (nin,*) m, n, nnza, nnzc
nnzu = 2*n + 2*m
! Allocate memory
Allocate (cindex(nnzc),icola(nnza),irowa(nnza),a(nnza),bla(m),bua(m), &
xl(n),xu(n),c(nnzc),x(n),u(nnzu))
! Read problem data
Read (nin,*) cindex(1:nnzc)
Read (nin,*) c(1:nnzc)
Read (nin,*) irowa(1:nnza)
Read (nin,*) icola(1:nnza)
Read (nin,*) a(1:nnza)
Read (nin,*) bla(1:m)
Read (nin,*) bua(1:m)
Read (nin,*) xl(1:n)
Read (nin,*) xu(1:n)
! Create the problem handle
! Initialize handle
ifail = 0
Call e04raf(handle,n,ifail)
! Set objective function
Call e04rff(handle,nnzc,cindex,c,0,irowh,icolh,h,ifail)
! Set box constraints
Call e04rhf(handle,n,xl,xu,ifail)
! Set linear constraints
idlc = 0
Call e04rjf(handle,m,bla,bua,nnza,irowa,icola,a,idlc,ifail)
! Require printing of the solution at the end of the solve
Call e04zmf(handle,'Print Solution = YES',ifail)
Write(nout,*) 'Creating a Nag Binary data file to represent the ', &
'original handle'
! Create data file from handle
Call e04sbf(handle,fname,'NAGBIN',ifail)
! Free handle
Call e04rzf(handle,ifail)
Write(nout,*) ''
Write(nout,*) 'Create new handle from data file'
! Create new handle from data file
ftype = 'nagbin'
Call e04saf(rehandle,fname,ftype,pinfo,ifail)
Write(nout,*) 'Solve new handle...'
cpuser = c_null_ptr
iuser(1) = nout
iuser(2) = 1
ifail = -1
Call e04mtf(rehandle,n,x,nnzu,u,rinfo,stats,e04mtu,iuser,ruser,cpuser, &
ifail)
! Free handle
Call e04rzf(rehandle,ifail)
End Program e04sbfe