Program e04pcfe
! E04PCF Example Program Text
! Mark 29.2 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: e04pcf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Real (Kind=nag_wp), Parameter :: tol = 0.0_nag_wp
Integer, Parameter :: itype = 1, nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: rnorm
Integer :: i, ifail, lda, lw, m, n, nfree
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:,:), b(:), bl(:), bu(:), w(:), &
x(:)
Integer, Allocatable :: indx(:)
! .. Executable Statements ..
Write (nout,*) 'E04PCF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
Read (nin,*) m, n
lda = m
lw = n
Allocate (a(lda,n),b(m),w(lw),bl(n),bu(n),x(n))
Allocate (indx(n))
Read (nin,*)(a(i,1:n),i=1,m)
Read (nin,*) b(1:m)
Read (nin,*) bl(1:n)
Read (nin,*) bu(1:n)
ifail = 0
Call e04pcf(itype,m,n,a,lda,b,bl,bu,tol,x,rnorm,nfree,w,indx,ifail)
Write (nout,99999) 'Solution vector', x(1:n)
Write (nout,*)
Write (nout,99999) 'Dual Solution', w(1:n)
Write (nout,*)
Write (nout,99998) 'Residual', rnorm
99999 Format (1X,A,/,1X,8F9.4)
99998 Format (1X,A,1X,1F9.4)
End Program e04pcfe