! E04SAF Example Program Text
! Mark 29.3 Release. NAG Copyright 2023.
Program e04safe
! .. Use Statements ..
Use iso_c_binding, Only: c_null_ptr, c_ptr
Use nag_library, Only: e04ptf, e04ptu, e04rcf, e04rzf, e04saf, e04zmf, &
nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nout = 6
Character (*), Parameter :: fname = 'e04safe.opt'
! .. Local Scalars ..
Type (c_ptr) :: cpuser, handle
Integer :: ifail, n, nnzu, nnzuc, x_idx
Logical :: verbose_output
Character (8) :: ftype
! .. Local Arrays ..
Real (Kind=nag_wp) :: rinfo(100), ruser(1), stats(100)
Real (Kind=nag_wp), Allocatable :: u(:), uc(:), x(:)
Integer :: iuser(1), pinfo(100)
! .. Executable Statements ..
Write (nout,*) 'E04SAF Example Program Results'
! Read mps file to a handle
ifail = 0
ftype = 'mps'
Call e04saf(handle,fname,ftype,pinfo,ifail)
! Get problem size from pinfo
n = pinfo(1)
nnzu = pinfo(11)
nnzuc = pinfo(12)
! Set all variables as continuous
ifail = 0
Call e04rcf(handle,'CONT',n,(/(x_idx,x_idx=1,n)/),ifail)
! Allocate memory
Allocate (x(n),u(nnzu),uc(nnzuc))
! Set this to .True. to cause e04ptf to produce intermediate
! progress output
verbose_output = .False.
If (verbose_output) Then
! Require printing of primal and dual solutions at the end of the solve
ifail = 0
Call e04zmf(handle,'Print Solution = YES',ifail)
Else
! Turn off printing of intermediate progress output
ifail = 0
Call e04zmf(handle,'Print Level = 1',ifail)
End If
! Call SOCP interior point solver
cpuser = c_null_ptr
ifail = -1
Call e04ptf(handle,n,x,nnzu,u,nnzuc,uc,rinfo,stats,e04ptu,iuser,ruser, &
cpuser,ifail)
! Print solution if optimal or suboptimal solution found
If (ifail==0 .Or. ifail==50) Then
Write (nout,99999) 'Optimal X:'
Write (nout,99997) 'x_idx', ' Value '
Do x_idx = 1, n
Write (nout,99998) x_idx, x(x_idx)
End Do
End If
! Free the handle memory
ifail = 0
Call e04rzf(handle,ifail)
99999 Format (1X,A)
99998 Format (2X,I5,3X,Es12.5e2)
99997 Format (2X,A5,3X,A12)
End Program e04safe