LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ cqrt12()

real function cqrt12 ( integer  m,
integer  n,
complex, dimension( lda, * )  a,
integer  lda,
real, dimension( * )  s,
complex, dimension( lwork )  work,
integer  lwork,
real, dimension( * )  rwork 
)

CQRT12

Purpose:
 CQRT12 computes the singular values `svlues' of the upper trapezoid
 of A(1:M,1:N) and returns the ratio

      || svlues -s ||/( ||s||*eps*max(M,N) )
Parameters
[in]M
          M is INTEGER
          The number of rows of the matrix A.
[in]N
          N is INTEGER
          The number of columns of the matrix A.
[in]A
          A is COMPLEX array, dimension (LDA,N)
          The M-by-N matrix A. Only the upper trapezoid is referenced.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.
[in]S
          S is REAL array, dimension (min(M,N))
          The singular values of the matrix A.
[out]WORK
          WORK is COMPLEX array, dimension (LWORK)
[in]LWORK
          LWORK is INTEGER
          The length of the array WORK. LWORK >= M*N + 2*min(M,N) +
          max(M,N).
[out]RWORK
          RWORK is REAL array, dimension (4*min(M,N))
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 95 of file cqrt12.f.

97*
98* -- LAPACK test routine --
99* -- LAPACK is a software package provided by Univ. of Tennessee, --
100* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
101*
102* .. Scalar Arguments ..
103 INTEGER LDA, LWORK, M, N
104* ..
105* .. Array Arguments ..
106 REAL RWORK( * ), S( * )
107 COMPLEX A( LDA, * ), WORK( LWORK )
108* ..
109*
110* =====================================================================
111*
112* .. Parameters ..
113 REAL ZERO, ONE
114 parameter( zero = 0.0e0, one = 1.0e0 )
115* ..
116* .. Local Scalars ..
117 INTEGER I, INFO, ISCL, J, MN
118 REAL ANRM, BIGNUM, NRMSVL, SMLNUM
119* ..
120* .. Local Arrays ..
121 REAL DUMMY( 1 )
122* ..
123* .. External Functions ..
124 REAL CLANGE, SASUM, SLAMCH, SNRM2
125 EXTERNAL clange, sasum, slamch, snrm2
126* ..
127* .. External Subroutines ..
128 EXTERNAL cgebd2, clascl, claset, saxpy, sbdsqr, slascl,
129 $ xerbla
130* ..
131* .. Intrinsic Functions ..
132 INTRINSIC cmplx, max, min, real
133* ..
134* .. Executable Statements ..
135*
136 cqrt12 = zero
137*
138* Test that enough workspace is supplied
139*
140 IF( lwork.LT.m*n+2*min( m, n )+max( m, n ) ) THEN
141 CALL xerbla( 'CQRT12', 7 )
142 RETURN
143 END IF
144*
145* Quick return if possible
146*
147 mn = min( m, n )
148 IF( mn.LE.zero )
149 $ RETURN
150*
151 nrmsvl = snrm2( mn, s, 1 )
152*
153* Copy upper triangle of A into work
154*
155 CALL claset( 'Full', m, n, cmplx( zero ), cmplx( zero ), work, m )
156 DO j = 1, n
157 DO i = 1, min( j, m )
158 work( ( j-1 )*m+i ) = a( i, j )
159 END DO
160 END DO
161*
162* Get machine parameters
163*
164 smlnum = slamch( 'S' ) / slamch( 'P' )
165 bignum = one / smlnum
166*
167* Scale work if max entry outside range [SMLNUM,BIGNUM]
168*
169 anrm = clange( 'M', m, n, work, m, dummy )
170 iscl = 0
171 IF( anrm.GT.zero .AND. anrm.LT.smlnum ) THEN
172*
173* Scale matrix norm up to SMLNUM
174*
175 CALL clascl( 'G', 0, 0, anrm, smlnum, m, n, work, m, info )
176 iscl = 1
177 ELSE IF( anrm.GT.bignum ) THEN
178*
179* Scale matrix norm down to BIGNUM
180*
181 CALL clascl( 'G', 0, 0, anrm, bignum, m, n, work, m, info )
182 iscl = 1
183 END IF
184*
185 IF( anrm.NE.zero ) THEN
186*
187* Compute SVD of work
188*
189 CALL cgebd2( m, n, work, m, rwork( 1 ), rwork( mn+1 ),
190 $ work( m*n+1 ), work( m*n+mn+1 ),
191 $ work( m*n+2*mn+1 ), info )
192 CALL sbdsqr( 'Upper', mn, 0, 0, 0, rwork( 1 ), rwork( mn+1 ),
193 $ dummy, mn, dummy, 1, dummy, mn, rwork( 2*mn+1 ),
194 $ info )
195*
196 IF( iscl.EQ.1 ) THEN
197 IF( anrm.GT.bignum ) THEN
198 CALL slascl( 'G', 0, 0, bignum, anrm, mn, 1, rwork( 1 ),
199 $ mn, info )
200 END IF
201 IF( anrm.LT.smlnum ) THEN
202 CALL slascl( 'G', 0, 0, smlnum, anrm, mn, 1, rwork( 1 ),
203 $ mn, info )
204 END IF
205 END IF
206*
207 ELSE
208*
209 DO i = 1, mn
210 rwork( i ) = zero
211 END DO
212 END IF
213*
214* Compare s and singular values of work
215*
216 CALL saxpy( mn, -one, s, 1, rwork( 1 ), 1 )
217 cqrt12 = sasum( mn, rwork( 1 ), 1 ) /
218 $ ( slamch( 'Epsilon' )*real( max( m, n ) ) )
219 IF( nrmsvl.NE.zero )
220 $ cqrt12 = cqrt12 / nrmsvl
221*
222 RETURN
223*
224* End of CQRT12
225*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
real function cqrt12(m, n, a, lda, s, work, lwork, rwork)
CQRT12
Definition cqrt12.f:97
real function sasum(n, sx, incx)
SASUM
Definition sasum.f:72
subroutine saxpy(n, sa, sx, incx, sy, incy)
SAXPY
Definition saxpy.f:89
subroutine sbdsqr(uplo, n, ncvt, nru, ncc, d, e, vt, ldvt, u, ldu, c, ldc, work, info)
SBDSQR
Definition sbdsqr.f:240
subroutine cgebd2(m, n, a, lda, d, e, tauq, taup, work, info)
CGEBD2 reduces a general matrix to bidiagonal form using an unblocked algorithm.
Definition cgebd2.f:190
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
real function clange(norm, m, n, a, lda, work)
CLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition clange.f:115
subroutine clascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)
CLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
Definition clascl.f:143
subroutine slascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)
SLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
Definition slascl.f:143
subroutine claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition claset.f:106
real(wp) function snrm2(n, x, incx)
SNRM2
Definition snrm2.f90:89
Here is the call graph for this function:
Here is the caller graph for this function: