LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 *> \date November 2011
86 *
87 *> \ingroup double_lin
88 *
89 * =====================================================================
90  DOUBLE PRECISION FUNCTION dqrt12( M, N, A, LDA, S, WORK, LWORK )
91 *
92 * -- LAPACK test routine (version 3.4.0) --
93 * -- LAPACK is a software package provided by Univ. of Tennessee, --
94 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
95 * November 2011
96 *
97 * .. Scalar Arguments ..
98  INTEGER LDA, LWORK, M, N
99 * ..
100 * .. Array Arguments ..
101  DOUBLE PRECISION A( lda, * ), S( * ), WORK( lwork )
102 * ..
103 *
104 * =====================================================================
105 *
106 * .. Parameters ..
107  DOUBLE PRECISION ZERO, ONE
108  parameter ( zero = 0.0d0, one = 1.0d0 )
109 * ..
110 * .. Local Scalars ..
111  INTEGER I, INFO, ISCL, J, MN
112  DOUBLE PRECISION ANRM, BIGNUM, NRMSVL, SMLNUM
113 * ..
114 * .. External Functions ..
115  DOUBLE PRECISION DASUM, DLAMCH, DLANGE, DNRM2
116  EXTERNAL dasum, dlamch, dlange, dnrm2
117 * ..
118 * .. External Subroutines ..
119  EXTERNAL daxpy, dbdsqr, dgebd2, dlabad, dlascl, dlaset,
120  $ xerbla
121 * ..
122 * .. Intrinsic Functions ..
123  INTRINSIC dble, max, min
124 * ..
125 * .. Local Arrays ..
126  DOUBLE PRECISION DUMMY( 1 )
127 * ..
128 * .. Executable Statements ..
129 *
130  dqrt12 = zero
131 *
132 * Test that enough workspace is supplied
133 *
134  IF( lwork.LT.max( m*n+4*min( m, n )+max( m, n ),
135  $ m*n+2*min( m, n )+4*n) ) THEN
136  CALL xerbla( 'DQRT12', 7 )
137  RETURN
138  END IF
139 *
140 * Quick return if possible
141 *
142  mn = min( m, n )
143  IF( mn.LE.zero )
144  $ RETURN
145 *
146  nrmsvl = dnrm2( mn, s, 1 )
147 *
148 * Copy upper triangle of A into work
149 *
150  CALL dlaset( 'Full', m, n, zero, zero, work, m )
151  DO 20 j = 1, n
152  DO 10 i = 1, min( j, m )
153  work( ( j-1 )*m+i ) = a( i, j )
154  10 CONTINUE
155  20 CONTINUE
156 *
157 * Get machine parameters
158 *
159  smlnum = dlamch( 'S' ) / dlamch( 'P' )
160  bignum = one / smlnum
161  CALL dlabad( smlnum, bignum )
162 *
163 * Scale work if max entry outside range [SMLNUM,BIGNUM]
164 *
165  anrm = dlange( 'M', m, n, work, m, dummy )
166  iscl = 0
167  IF( anrm.GT.zero .AND. anrm.LT.smlnum ) THEN
168 *
169 * Scale matrix norm up to SMLNUM
170 *
171  CALL dlascl( 'G', 0, 0, anrm, smlnum, m, n, work, m, info )
172  iscl = 1
173  ELSE IF( anrm.GT.bignum ) THEN
174 *
175 * Scale matrix norm down to BIGNUM
176 *
177  CALL dlascl( 'G', 0, 0, anrm, bignum, m, n, work, m, info )
178  iscl = 1
179  END IF
180 *
181  IF( anrm.NE.zero ) THEN
182 *
183 * Compute SVD of work
184 *
185  CALL dgebd2( m, n, work, m, work( m*n+1 ), work( m*n+mn+1 ),
186  $ work( m*n+2*mn+1 ), work( m*n+3*mn+1 ),
187  $ work( m*n+4*mn+1 ), info )
188  CALL dbdsqr( 'Upper', mn, 0, 0, 0, work( m*n+1 ),
189  $ work( m*n+mn+1 ), dummy, mn, dummy, 1, dummy, mn,
190  $ work( m*n+2*mn+1 ), info )
191 *
192  IF( iscl.EQ.1 ) THEN
193  IF( anrm.GT.bignum ) THEN
194  CALL dlascl( 'G', 0, 0, bignum, anrm, mn, 1,
195  $ work( m*n+1 ), mn, info )
196  END IF
197  IF( anrm.LT.smlnum ) THEN
198  CALL dlascl( 'G', 0, 0, smlnum, anrm, mn, 1,
199  $ work( m*n+1 ), mn, info )
200  END IF
201  END IF
202 *
203  ELSE
204 *
205  DO 30 i = 1, mn
206  work( m*n+i ) = zero
207  30 CONTINUE
208  END IF
209 *
210 * Compare s and singular values of work
211 *
212  CALL daxpy( mn, -one, s, 1, work( m*n+1 ), 1 )
213  dqrt12 = dasum( mn, work( m*n+1 ), 1 ) /
214  $ ( dlamch( 'Epsilon' )*dble( max( m, n ) ) )
215  IF( nrmsvl.NE.zero )
216  $ dqrt12 = dqrt12 / nrmsvl
217 *
218  RETURN
219 *
220 * End of DQRT12
221 *
222  END
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:112
double precision function dqrt12(M, N, A, LDA, S, WORK, LWORK)
DQRT12
Definition: dqrt12.f:91
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:145
subroutine daxpy(N, DA, DX, INCX, DY, INCY)
DAXPY
Definition: daxpy.f:54
subroutine dbdsqr(UPLO, N, NCVT, NRU, NCC, D, E, VT, LDVT, U, LDU, C, LDC, WORK, INFO)
DBDSQR
Definition: dbdsqr.f:232
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:191
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine dlabad(SMALL, LARGE)
DLABAD
Definition: dlabad.f:76