PROGRAM f08zafe ! F08ZAF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : dgglse, dnrm2, nag_wp ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nb = 64, nin = 5, nout = 6 ! .. Local Scalars .. REAL (KIND=nag_wp) :: rnorm INTEGER :: i, info, lda, ldb, lwork, m, n, p ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: a(:,:), b(:,:), c(:), d(:), work(:), & x(:) ! .. Executable Statements .. WRITE (nout,*) 'F08ZAF Example Program Results' WRITE (nout,*) ! Skip heading in data file READ (nin,*) READ (nin,*) m, n, p lda = m ldb = p lwork = p + n + nb*(m+n) ALLOCATE (a(lda,n),b(ldb,n),c(m),d(p),work(lwork),x(n)) ! Read A, B, C and D from data file READ (nin,*) (a(i,1:n),i=1,m) READ (nin,*) (b(i,1:n),i=1,p) READ (nin,*) c(1:m) READ (nin,*) d(1:p) ! Solve the equality-constrained least-squares problem ! minimize ||c - A*x|| (in the 2-norm) subject to B*x = D ! The NAG name equivalent of dgglse is f08zaf CALL dgglse(m,n,p,a,lda,b,ldb,c,d,x,work,lwork,info) ! Print least-squares solution WRITE (nout,*) 'Constrained least-squares solution' WRITE (nout,99999) x(1:n) ! Compute the square root of the residual sum of squares ! The NAG name equivalent of dnrm2 is f06ejf rnorm = dnrm2(m-n+p,c(n-p+1),1) WRITE (nout,*) WRITE (nout,*) 'Square root of the residual sum of squares' WRITE (nout,99998) rnorm 99999 FORMAT (1X,7F11.4) 99998 FORMAT (3X,1P,E11.2) END PROGRAM f08zafe