LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cqrt12.f
Go to the documentation of this file.
1 *> \brief \b CQRT12
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * REAL FUNCTION CQRT12( M, N, A, LDA, S, WORK, LWORK,
12 * RWORK )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER LDA, LWORK, M, N
16 * ..
17 * .. Array Arguments ..
18 * REAL RWORK( * ), S( * )
19 * COMPLEX A( LDA, * ), WORK( LWORK )
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> CQRT12 computes the singular values `svlues' of the upper trapezoid
29 *> of A(1:M,1:N) and returns the ratio
30 *>
31 *> || s - svlues||/(||svlues||*eps*max(M,N))
32 *> \endverbatim
33 *
34 * Arguments:
35 * ==========
36 *
37 *> \param[in] M
38 *> \verbatim
39 *> M is INTEGER
40 *> The number of rows of the matrix A.
41 *> \endverbatim
42 *>
43 *> \param[in] N
44 *> \verbatim
45 *> N is INTEGER
46 *> The number of columns of the matrix A.
47 *> \endverbatim
48 *>
49 *> \param[in] A
50 *> \verbatim
51 *> A is COMPLEX array, dimension (LDA,N)
52 *> The M-by-N matrix A. Only the upper trapezoid is referenced.
53 *> \endverbatim
54 *>
55 *> \param[in] LDA
56 *> \verbatim
57 *> LDA is INTEGER
58 *> The leading dimension of the array A.
59 *> \endverbatim
60 *>
61 *> \param[in] S
62 *> \verbatim
63 *> S is REAL array, dimension (min(M,N))
64 *> The singular values of the matrix A.
65 *> \endverbatim
66 *>
67 *> \param[out] WORK
68 *> \verbatim
69 *> WORK is COMPLEX array, dimension (LWORK)
70 *> \endverbatim
71 *>
72 *> \param[in] LWORK
73 *> \verbatim
74 *> LWORK is INTEGER
75 *> The length of the array WORK. LWORK >= M*N + 2*min(M,N) +
76 *> max(M,N).
77 *> \endverbatim
78 *>
79 *> \param[out] RWORK
80 *> \verbatim
81 *> RWORK is REAL array, dimension (4*min(M,N))
82 *> \endverbatim
83 *
84 * Authors:
85 * ========
86 *
87 *> \author Univ. of Tennessee
88 *> \author Univ. of California Berkeley
89 *> \author Univ. of Colorado Denver
90 *> \author NAG Ltd.
91 *
92 *> \date November 2011
93 *
94 *> \ingroup complex_lin
95 *
96 * =====================================================================
97  REAL FUNCTION cqrt12( M, N, A, LDA, S, WORK, LWORK,
98  $ rwork )
99 *
100 * -- LAPACK test routine (version 3.4.0) --
101 * -- LAPACK is a software package provided by Univ. of Tennessee, --
102 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
103 * November 2011
104 *
105 * .. Scalar Arguments ..
106  INTEGER LDA, LWORK, M, N
107 * ..
108 * .. Array Arguments ..
109  REAL RWORK( * ), S( * )
110  COMPLEX A( lda, * ), WORK( lwork )
111 * ..
112 *
113 * =====================================================================
114 *
115 * .. Parameters ..
116  REAL ZERO, ONE
117  parameter ( zero = 0.0e0, one = 1.0e0 )
118 * ..
119 * .. Local Scalars ..
120  INTEGER I, INFO, ISCL, J, MN
121  REAL ANRM, BIGNUM, NRMSVL, SMLNUM
122 * ..
123 * .. Local Arrays ..
124  REAL DUMMY( 1 )
125 * ..
126 * .. External Functions ..
127  REAL CLANGE, SASUM, SLAMCH, SNRM2
128  EXTERNAL clange, sasum, slamch, snrm2
129 * ..
130 * .. External Subroutines ..
131  EXTERNAL cgebd2, clascl, claset, saxpy, sbdsqr, slabad,
132  $ slascl, xerbla
133 * ..
134 * .. Intrinsic Functions ..
135  INTRINSIC cmplx, max, min, real
136 * ..
137 * .. Executable Statements ..
138 *
139  cqrt12 = zero
140 *
141 * Test that enough workspace is supplied
142 *
143  IF( lwork.LT.m*n+2*min( m, n )+max( m, n ) ) THEN
144  CALL xerbla( 'CQRT12', 7 )
145  RETURN
146  END IF
147 *
148 * Quick return if possible
149 *
150  mn = min( m, n )
151  IF( mn.LE.zero )
152  $ RETURN
153 *
154  nrmsvl = snrm2( mn, s, 1 )
155 *
156 * Copy upper triangle of A into work
157 *
158  CALL claset( 'Full', m, n, cmplx( zero ), cmplx( zero ), work, m )
159  DO 20 j = 1, n
160  DO 10 i = 1, min( j, m )
161  work( ( j-1 )*m+i ) = a( i, j )
162  10 CONTINUE
163  20 CONTINUE
164 *
165 * Get machine parameters
166 *
167  smlnum = slamch( 'S' ) / slamch( 'P' )
168  bignum = one / smlnum
169  CALL slabad( smlnum, bignum )
170 *
171 * Scale work if max entry outside range [SMLNUM,BIGNUM]
172 *
173  anrm = clange( 'M', m, n, work, m, dummy )
174  iscl = 0
175  IF( anrm.GT.zero .AND. anrm.LT.smlnum ) THEN
176 *
177 * Scale matrix norm up to SMLNUM
178 *
179  CALL clascl( 'G', 0, 0, anrm, smlnum, m, n, work, m, info )
180  iscl = 1
181  ELSE IF( anrm.GT.bignum ) THEN
182 *
183 * Scale matrix norm down to BIGNUM
184 *
185  CALL clascl( 'G', 0, 0, anrm, bignum, m, n, work, m, info )
186  iscl = 1
187  END IF
188 *
189  IF( anrm.NE.zero ) THEN
190 *
191 * Compute SVD of work
192 *
193  CALL cgebd2( m, n, work, m, rwork( 1 ), rwork( mn+1 ),
194  $ work( m*n+1 ), work( m*n+mn+1 ),
195  $ work( m*n+2*mn+1 ), info )
196  CALL sbdsqr( 'Upper', mn, 0, 0, 0, rwork( 1 ), rwork( mn+1 ),
197  $ dummy, mn, dummy, 1, dummy, mn, rwork( 2*mn+1 ),
198  $ info )
199 *
200  IF( iscl.EQ.1 ) THEN
201  IF( anrm.GT.bignum ) THEN
202  CALL slascl( 'G', 0, 0, bignum, anrm, mn, 1, rwork( 1 ),
203  $ mn, info )
204  END IF
205  IF( anrm.LT.smlnum ) THEN
206  CALL slascl( 'G', 0, 0, smlnum, anrm, mn, 1, rwork( 1 ),
207  $ mn, info )
208  END IF
209  END IF
210 *
211  ELSE
212 *
213  DO 30 i = 1, mn
214  rwork( i ) = zero
215  30 CONTINUE
216  END IF
217 *
218 * Compare s and singular values of work
219 *
220  CALL saxpy( mn, -one, s, 1, rwork( 1 ), 1 )
221  cqrt12 = sasum( mn, rwork( 1 ), 1 ) /
222  $ ( slamch( 'Epsilon' )*REAL( MAX( M, N ) ) )
223  IF( nrmsvl.NE.zero )
224  $ cqrt12 = cqrt12 / nrmsvl
225 *
226  RETURN
227 *
228 * End of CQRT12
229 *
230  END
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:145
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:145
subroutine slabad(SMALL, LARGE)
SLABAD
Definition: slabad.f:76
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
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:108
subroutine saxpy(N, SA, SX, INCX, SY, INCY)
SAXPY
Definition: saxpy.f:54
subroutine sbdsqr(UPLO, N, NCVT, NRU, NCC, D, E, VT, LDVT, U, LDU, C, LDC, WORK, INFO)
SBDSQR
Definition: sbdsqr.f:232
real function cqrt12(M, N, A, LDA, S, WORK, LWORK, RWORK)
CQRT12
Definition: cqrt12.f:99
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:192