LAPACK 3.11.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dqrt12.f
Go to the documentation of this file.
1*> \brief \b DQRT12
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* DOUBLE PRECISION FUNCTION DQRT12( M, N, A, LDA, S, WORK, LWORK )
12*
13* .. Scalar Arguments ..
14* INTEGER LDA, LWORK, M, N
15* ..
16* .. Array Arguments ..
17* DOUBLE PRECISION A( LDA, * ), S( * ), WORK( LWORK )
18* ..
19*
20*
21*> \par Purpose:
22* =============
23*>
24*> \verbatim
25*>
26*> DQRT12 computes the singular values `svlues' of the upper trapezoid
27*> of A(1:M,1:N) and returns the ratio
28*>
29*> || s - svlues||/(||svlues||*eps*max(M,N))
30*> \endverbatim
31*
32* Arguments:
33* ==========
34*
35*> \param[in] M
36*> \verbatim
37*> M is INTEGER
38*> The number of rows of the matrix A.
39*> \endverbatim
40*>
41*> \param[in] N
42*> \verbatim
43*> N is INTEGER
44*> The number of columns of the matrix A.
45*> \endverbatim
46*>
47*> \param[in] A
48*> \verbatim
49*> A is DOUBLE PRECISION array, dimension (LDA,N)
50*> The M-by-N matrix A. Only the upper trapezoid is referenced.
51*> \endverbatim
52*>
53*> \param[in] LDA
54*> \verbatim
55*> LDA is INTEGER
56*> The leading dimension of the array A.
57*> \endverbatim
58*>
59*> \param[in] S
60*> \verbatim
61*> S is DOUBLE PRECISION array, dimension (min(M,N))
62*> The singular values of the matrix A.
63*> \endverbatim
64*>
65*> \param[out] WORK
66*> \verbatim
67*> WORK is DOUBLE PRECISION array, dimension (LWORK)
68*> \endverbatim
69*>
70*> \param[in] LWORK
71*> \verbatim
72*> LWORK is INTEGER
73*> The length of the array WORK. LWORK >= max(M*N + 4*min(M,N) +
74*> max(M,N), M*N+2*MIN( M, N )+4*N).
75*> \endverbatim
76*
77* Authors:
78* ========
79*
80*> \author Univ. of Tennessee
81*> \author Univ. of California Berkeley
82*> \author Univ. of Colorado Denver
83*> \author NAG Ltd.
84*
85*> \ingroup double_lin
86*
87* =====================================================================
88 DOUBLE PRECISION FUNCTION dqrt12( M, N, A, LDA, S, WORK, LWORK )
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 DOUBLE PRECISION a( lda, * ), s( * ), work( lwork )
99* ..
100*
101* =====================================================================
102*
103* .. Parameters ..
104 DOUBLE PRECISION zero, one
105 parameter( zero = 0.0d0, one = 1.0d0 )
106* ..
107* .. Local Scalars ..
108 INTEGER i, info, iscl, j, mn
109 DOUBLE PRECISION anrm, bignum, nrmsvl, smlnum
110* ..
111* .. External Functions ..
112 DOUBLE PRECISION dasum, dlamch, dlange, dnrm2
113 EXTERNAL dasum, dlamch, dlange, dnrm2
114* ..
115* .. External Subroutines ..
116 EXTERNAL daxpy, dbdsqr, dgebd2, dlabad, dlascl, dlaset,
117 $ xerbla
118* ..
119* .. Intrinsic Functions ..
120 INTRINSIC dble, max, min
121* ..
122* .. Local Arrays ..
123 DOUBLE PRECISION dummy( 1 )
124* ..
125* .. Executable Statements ..
126*
127 dqrt12 = zero
128*
129* Test that enough workspace is supplied
130*
131 IF( lwork.LT.max( m*n+4*min( m, n )+max( m, n ),
132 $ m*n+2*min( m, n )+4*n) ) THEN
133 CALL xerbla( 'DQRT12', 7 )
134 RETURN
135 END IF
136*
137* Quick return if possible
138*
139 mn = min( m, n )
140 IF( mn.LE.zero )
141 $ RETURN
142*
143 nrmsvl = dnrm2( mn, s, 1 )
144*
145* Copy upper triangle of A into work
146*
147 CALL dlaset( 'Full', m, n, zero, zero, work, m )
148 DO 20 j = 1, n
149 DO 10 i = 1, min( j, m )
150 work( ( j-1 )*m+i ) = a( i, j )
151 10 CONTINUE
152 20 CONTINUE
153*
154* Get machine parameters
155*
156 smlnum = dlamch( 'S' ) / dlamch( 'P' )
157 bignum = one / smlnum
158 CALL dlabad( smlnum, bignum )
159*
160* Scale work if max entry outside range [SMLNUM,BIGNUM]
161*
162 anrm = dlange( 'M', m, n, work, m, dummy )
163 iscl = 0
164 IF( anrm.GT.zero .AND. anrm.LT.smlnum ) THEN
165*
166* Scale matrix norm up to SMLNUM
167*
168 CALL dlascl( 'G', 0, 0, anrm, smlnum, m, n, work, m, info )
169 iscl = 1
170 ELSE IF( anrm.GT.bignum ) THEN
171*
172* Scale matrix norm down to BIGNUM
173*
174 CALL dlascl( 'G', 0, 0, anrm, bignum, m, n, work, m, info )
175 iscl = 1
176 END IF
177*
178 IF( anrm.NE.zero ) THEN
179*
180* Compute SVD of work
181*
182 CALL dgebd2( m, n, work, m, work( m*n+1 ), work( m*n+mn+1 ),
183 $ work( m*n+2*mn+1 ), work( m*n+3*mn+1 ),
184 $ work( m*n+4*mn+1 ), info )
185 CALL dbdsqr( 'Upper', mn, 0, 0, 0, work( m*n+1 ),
186 $ work( m*n+mn+1 ), dummy, mn, dummy, 1, dummy, mn,
187 $ work( m*n+2*mn+1 ), info )
188*
189 IF( iscl.EQ.1 ) THEN
190 IF( anrm.GT.bignum ) THEN
191 CALL dlascl( 'G', 0, 0, bignum, anrm, mn, 1,
192 $ work( m*n+1 ), mn, info )
193 END IF
194 IF( anrm.LT.smlnum ) THEN
195 CALL dlascl( 'G', 0, 0, smlnum, anrm, mn, 1,
196 $ work( m*n+1 ), mn, info )
197 END IF
198 END IF
199*
200 ELSE
201*
202 DO 30 i = 1, mn
203 work( m*n+i ) = zero
204 30 CONTINUE
205 END IF
206*
207* Compare s and singular values of work
208*
209 CALL daxpy( mn, -one, s, 1, work( m*n+1 ), 1 )
210 dqrt12 = dasum( mn, work( m*n+1 ), 1 ) /
211 $ ( dlamch( 'Epsilon' )*dble( max( m, n ) ) )
212 IF( nrmsvl.NE.zero )
213 $ dqrt12 = dqrt12 / nrmsvl
214*
215 RETURN
216*
217* End of DQRT12
218*
219 END
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:69
subroutine dlabad(SMALL, LARGE)
DLABAD
Definition: dlabad.f:74
subroutine dlascl(TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO)
DLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
Definition: dlascl.f:143
subroutine dlaset(UPLO, M, N, ALPHA, BETA, A, LDA)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition: dlaset.f:110
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
subroutine dbdsqr(UPLO, N, NCVT, NRU, NCC, D, E, VT, LDVT, U, LDU, C, LDC, WORK, INFO)
DBDSQR
Definition: dbdsqr.f:241
double precision function dasum(N, DX, INCX)
DASUM
Definition: dasum.f:71
subroutine daxpy(N, DA, DX, INCX, DY, INCY)
DAXPY
Definition: daxpy.f:89
double precision function dqrt12(M, N, A, LDA, S, WORK, LWORK)
DQRT12
Definition: dqrt12.f:89
double precision function dlange(NORM, M, N, A, LDA, WORK)
DLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: dlange.f:114
subroutine dgebd2(M, N, A, LDA, D, E, TAUQ, TAUP, WORK, INFO)
DGEBD2 reduces a general matrix to bidiagonal form using an unblocked algorithm.
Definition: dgebd2.f:189
real(wp) function dnrm2(n, x, incx)
DNRM2
Definition: dnrm2.f90:89