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

◆ sqrt12()

real function sqrt12 ( integer  m,
integer  n,
real, dimension( lda, * )  a,
integer  lda,
real, dimension( * )  s,
real, dimension( lwork )  work,
integer  lwork 
)

SQRT12

Purpose:
 SQRT12 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 REAL 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 REAL array, dimension (LWORK)
[in]LWORK
          LWORK is INTEGER
          The length of the array WORK. LWORK >= max(M*N + 4*min(M,N) +
          max(M,N), M*N+2*MIN( M, N )+4*N).
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 88 of file sqrt12.f.

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