Program f08kzfe
! F08KZF Example Program Text
! Mark 29.2 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: nag_wp, zgesvdx
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: vl, vu
Integer :: i, il, info, iu, lda, ldu, ldvt, &
liwork, lrwork, lwork, m, n, ns
Character (1) :: range
! .. Local Arrays ..
Complex (Kind=nag_wp), Allocatable :: a(:,:), u(:,:), vt(:,:), work(:)
Real (Kind=nag_wp), Allocatable :: rwork(:), s(:)
Integer, Allocatable :: iwork(:)
! .. Intrinsic Procedures ..
Intrinsic :: nint
! .. Executable Statements ..
Write (nout,*) 'F08KZF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
Read (nin,*) m, n
lda = m
ldu = m
ldvt = n
lwork = 2*n**2 + 4*n
lrwork = 2*n*2 + 34*n
liwork = 12*n
Allocate (a(lda,n),s(n),vt(ldvt,n),u(ldu,m),iwork(liwork),work(lwork), &
rwork(lrwork))
! Read the m by n matrix A from data file
Read (nin,*)(a(i,1:n),i=1,m)
! Read range for selected singular values
Read (nin,*) range
If (range=='I' .Or. range=='i') Then
Read (nin,*) il, iu
Else If (range=='V' .Or. range=='v') Then
Read (nin,*) vl, vu
End If
! Compute the singular values and left and right singular vectors
! of A.
! The NAG name equivalent of zgesvd is f08kzf
Call zgesvdx('V','V',range,m,n,a,lda,vl,vu,il,iu,ns,s,u,ldu,vt,ldvt, &
work,lwork,rwork,iwork,info)
If (info/=0) Then
Write (nout,99999) 'Failure in ZGESVDX. INFO =', info
99999 Format (1X,A,I4)
Go To 100
End If
! Print the selected singular values of A
Write (nout,*) 'Singular values of A:'
Write (nout,99998) s(1:ns)
99998 Format (1X,4(3X,F11.4))
Call compute_error_bounds(m,ns,s)
100 Continue
Contains
Subroutine compute_error_bounds(m,n,s)
! Error estimates for singular values and vectors is computed
! and printed here.
! .. Use Statements ..
Use nag_library, Only: ddisna, nag_wp, x02ajf, x02amf
! .. Implicit None Statement ..
Implicit None
! .. Scalar Arguments ..
Integer, Intent (In) :: m, n
! .. Array Arguments ..
Real (Kind=nag_wp), Intent (In) :: s(n)
! .. Local Scalars ..
Real (Kind=nag_wp) :: eps, serrbd
Integer :: i, info, nl
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: rcondu(:), rcondv(:), uerrbd(:), &
verrbd(:)
! .. Executable Statements ..
Allocate (rcondu(n),rcondv(n),uerrbd(n),verrbd(n))
! Get the machine precision, EPS and compute the approximate
! error bound for the computed singular values. Note that for
! the 2-norm, S(1) = norm(A)
eps = x02ajf()
serrbd = eps*s(1)
! Call DDISNA (F08FLF) to estimate reciprocal condition
! numbers for the singular vectors
Call ddisna('Left',m,n,s,rcondu,info)
Call ddisna('Right',m,n,s,rcondv,info)
! Compute the error estimates for the singular vectors
nl = n
Do i = 1, n
If (s(i)<x02amf()) Then
nl = i - 1
Else
uerrbd(i) = serrbd/rcondu(i)
End If
verrbd(i) = serrbd/rcondv(i)
End Do
! Print the approximate error bounds for the singular values
! and vectors
Write (nout,*)
Write (nout,*) 'Error estimates (as multiples of machine precision):'
Write (nout,*) ' for the singular values'
Write (nout,99999) nint(serrbd/x02ajf())
Write (nout,*)
Write (nout,*) ' for the left (non-zero) singular vectors'
Write (nout,99999) nint(uerrbd(1:nl)/x02ajf())
Write (nout,*)
Write (nout,*) ' for the right singular vectors'
Write (nout,99999) nint(verrbd(1:n)/x02ajf())
99999 Format (4X,6I11)
End Subroutine compute_error_bounds
End Program f08kzfe