PROGRAM f08vafe ! F08VAF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : dggsvd, dtrcon, nag_wp, x02ajf, x04cbf ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nin = 5, nout = 6 ! .. Local Scalars .. REAL (KIND=nag_wp) :: eps, rcond, serrbd INTEGER :: i, ifail, info, irank, j, k, l, lda, & ldb, ldq, ldu, ldv, m, n, p ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: a(:,:), alpha(:), b(:,:), beta(:), & q(:,:), u(:,:), v(:,:), work(:) INTEGER, ALLOCATABLE :: iwork(:) CHARACTER (1) :: clabs(1), rlabs(1) ! .. Executable Statements .. WRITE (nout,*) 'F08VAF Example Program Results' WRITE (nout,*) FLUSH (nout) ! Skip heading in data file READ (nin,*) READ (nin,*) m, n, p lda = m ldb = p ldq = n ldu = m ldv = p ALLOCATE (a(lda,n),alpha(n),b(ldb,n),beta(n),q(ldq,n),u(ldu,m), & v(ldv,p),work(m+3*n),iwork(n)) ! Read the m by n matrix A and p by n matrix B from data file READ (nin,*) (a(i,1:n),i=1,m) READ (nin,*) (b(i,1:n),i=1,p) ! Compute the generalized singular value decomposition of (A, B) ! (A = U*D1*(0 R)*(Q**T), B = V*D2*(0 R)*(Q**T), m>=n) ! The NAG name equivalent of dggsvd is f08vaf CALL dggsvd('U','V','Q',m,n,p,k,l,a,lda,b,ldb,alpha,beta,u,ldu,v,ldv,q, & ldq,work,iwork,info) IF (info==0) THEN ! Print solution irank = k + l WRITE (nout,*) 'Number of infinite generalized singular values (K)' WRITE (nout,99999) k WRITE (nout,*) 'Number of finite generalized singular values (L)' WRITE (nout,99999) l WRITE (nout,*) 'Numerical rank of (A**T B**T)**T (K+L)' WRITE (nout,99999) irank WRITE (nout,*) WRITE (nout,*) 'Finite generalized singular values' WRITE (nout,99998) (alpha(j)/beta(j),j=k+1,irank) WRITE (nout,*) FLUSH (nout) ! ifail: behaviour on error exit ! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft ifail = 0 CALL x04cbf('General',' ',m,m,u,ldu,'1P,E12.4', & 'Orthogonal matrix U','Integer',rlabs,'Integer',clabs,80,0,ifail) WRITE (nout,*) FLUSH (nout) CALL x04cbf('General',' ',p,p,v,ldv,'1P,E12.4', & 'Orthogonal matrix V','Integer',rlabs,'Integer',clabs,80,0,ifail) WRITE (nout,*) FLUSH (nout) CALL x04cbf('General',' ',n,n,q,ldq,'1P,E12.4', & 'Orthogonal matrix Q','Integer',rlabs,'Integer',clabs,80,0,ifail) WRITE (nout,*) FLUSH (nout) CALL x04cbf('Upper triangular','Non-unit',irank,irank, & a(1,n-irank+1),lda,'1P,E12.4', & 'Non singular upper triangular matrix R','Integer',rlabs, & 'Integer',clabs,80,0,ifail) ! Call DTRCON (F07TGF) to estimate the reciprocal condition ! number of R CALL dtrcon('Infinity-norm','Upper','Non-unit',irank,a(1,n-irank+1), & lda,rcond,work,iwork,info) WRITE (nout,*) WRITE (nout,*) 'Estimate of reciprocal condition number for R' WRITE (nout,99997) rcond WRITE (nout,*) ! So long as irank = n, get the machine precision, eps, and ! compute the approximate error bound for the computed ! generalized singular values IF (irank==n) THEN eps = x02ajf() serrbd = eps/rcond WRITE (nout,*) & 'Error estimate for the generalized singular values' WRITE (nout,99997) serrbd ELSE WRITE (nout,*) '(A**T B**T)**T is not of full rank' END IF ELSE WRITE (nout,99996) 'Failure in DGGSVD. INFO =', info END IF 99999 FORMAT (1X,I5) 99998 FORMAT (3X,8(1P,E12.4)) 99997 FORMAT (1X,1P,E11.1) 99996 FORMAT (1X,A,I4) END PROGRAM f08vafe