LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cqrt15.f
Go to the documentation of this file.
1 *> \brief \b CQRT15
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE CQRT15( SCALE, RKSEL, M, N, NRHS, A, LDA, B, LDB, S,
12 * RANK, NORMA, NORMB, ISEED, WORK, LWORK )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER LDA, LDB, LWORK, M, N, NRHS, RANK, RKSEL, SCALE
16 * REAL NORMA, NORMB
17 * ..
18 * .. Array Arguments ..
19 * INTEGER ISEED( 4 )
20 * REAL S( * )
21 * COMPLEX A( LDA, * ), B( LDB, * ), WORK( LWORK )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> CQRT15 generates a matrix with full or deficient rank and of various
31 *> norms.
32 *> \endverbatim
33 *
34 * Arguments:
35 * ==========
36 *
37 *> \param[in] SCALE
38 *> \verbatim
39 *> SCALE is INTEGER
40 *> SCALE = 1: normally scaled matrix
41 *> SCALE = 2: matrix scaled up
42 *> SCALE = 3: matrix scaled down
43 *> \endverbatim
44 *>
45 *> \param[in] RKSEL
46 *> \verbatim
47 *> RKSEL is INTEGER
48 *> RKSEL = 1: full rank matrix
49 *> RKSEL = 2: rank-deficient matrix
50 *> \endverbatim
51 *>
52 *> \param[in] M
53 *> \verbatim
54 *> M is INTEGER
55 *> The number of rows of the matrix A.
56 *> \endverbatim
57 *>
58 *> \param[in] N
59 *> \verbatim
60 *> N is INTEGER
61 *> The number of columns of A.
62 *> \endverbatim
63 *>
64 *> \param[in] NRHS
65 *> \verbatim
66 *> NRHS is INTEGER
67 *> The number of columns of B.
68 *> \endverbatim
69 *>
70 *> \param[out] A
71 *> \verbatim
72 *> A is COMPLEX array, dimension (LDA,N)
73 *> The M-by-N matrix A.
74 *> \endverbatim
75 *>
76 *> \param[in] LDA
77 *> \verbatim
78 *> LDA is INTEGER
79 *> The leading dimension of the array A.
80 *> \endverbatim
81 *>
82 *> \param[out] B
83 *> \verbatim
84 *> B is COMPLEX array, dimension (LDB, NRHS)
85 *> A matrix that is in the range space of matrix A.
86 *> \endverbatim
87 *>
88 *> \param[in] LDB
89 *> \verbatim
90 *> LDB is INTEGER
91 *> The leading dimension of the array B.
92 *> \endverbatim
93 *>
94 *> \param[out] S
95 *> \verbatim
96 *> S is REAL array, dimension MIN(M,N)
97 *> Singular values of A.
98 *> \endverbatim
99 *>
100 *> \param[out] RANK
101 *> \verbatim
102 *> RANK is INTEGER
103 *> number of nonzero singular values of A.
104 *> \endverbatim
105 *>
106 *> \param[out] NORMA
107 *> \verbatim
108 *> NORMA is REAL
109 *> one-norm norm of A.
110 *> \endverbatim
111 *>
112 *> \param[out] NORMB
113 *> \verbatim
114 *> NORMB is REAL
115 *> one-norm norm of B.
116 *> \endverbatim
117 *>
118 *> \param[in,out] ISEED
119 *> \verbatim
120 *> ISEED is integer array, dimension (4)
121 *> seed for random number generator.
122 *> \endverbatim
123 *>
124 *> \param[out] WORK
125 *> \verbatim
126 *> WORK is COMPLEX array, dimension (LWORK)
127 *> \endverbatim
128 *>
129 *> \param[in] LWORK
130 *> \verbatim
131 *> LWORK is INTEGER
132 *> length of work space required.
133 *> LWORK >= MAX(M+MIN(M,N),NRHS*MIN(M,N),2*N+M)
134 *> \endverbatim
135 *
136 * Authors:
137 * ========
138 *
139 *> \author Univ. of Tennessee
140 *> \author Univ. of California Berkeley
141 *> \author Univ. of Colorado Denver
142 *> \author NAG Ltd.
143 *
144 *> \date November 2011
145 *
146 *> \ingroup complex_lin
147 *
148 * =====================================================================
149  SUBROUTINE cqrt15( SCALE, RKSEL, M, N, NRHS, A, LDA, B, LDB, S,
150  $ rank, norma, normb, iseed, work, lwork )
151 *
152 * -- LAPACK test routine (version 3.4.0) --
153 * -- LAPACK is a software package provided by Univ. of Tennessee, --
154 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
155 * November 2011
156 *
157 * .. Scalar Arguments ..
158  INTEGER lda, ldb, lwork, m, n, nrhs, rank, rksel, scale
159  REAL norma, normb
160 * ..
161 * .. Array Arguments ..
162  INTEGER iseed( 4 )
163  REAL s( * )
164  COMPLEX a( lda, * ), b( ldb, * ), work( lwork )
165 * ..
166 *
167 * =====================================================================
168 *
169 * .. Parameters ..
170  REAL zero, one, two, svmin
171  parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0,
172  $ svmin = 0.1e+0 )
173  COMPLEX czero, cone
174  parameter( czero = ( 0.0e+0, 0.0e+0 ),
175  $ cone = ( 1.0e+0, 0.0e+0 ) )
176 * ..
177 * .. Local Scalars ..
178  INTEGER info, j, mn
179  REAL bignum, eps, smlnum, temp
180 * ..
181 * .. Local Arrays ..
182  REAL dummy( 1 )
183 * ..
184 * .. External Functions ..
185  REAL clange, sasum, scnrm2, slamch, slarnd
186  EXTERNAL clange, sasum, scnrm2, slamch, slarnd
187 * ..
188 * .. External Subroutines ..
189  EXTERNAL cgemm, clarf, clarnv, claror, clascl, claset,
191 * ..
192 * .. Intrinsic Functions ..
193  INTRINSIC abs, cmplx, max, min
194 * ..
195 * .. Executable Statements ..
196 *
197  mn = min( m, n )
198  IF( lwork.LT.max( m+mn, mn*nrhs, 2*n+m ) ) THEN
199  CALL xerbla( 'CQRT15', 16 )
200  return
201  END IF
202 *
203  smlnum = slamch( 'Safe minimum' )
204  bignum = one / smlnum
205  CALL slabad( smlnum, bignum )
206  eps = slamch( 'Epsilon' )
207  smlnum = ( smlnum / eps ) / eps
208  bignum = one / smlnum
209 *
210 * Determine rank and (unscaled) singular values
211 *
212  IF( rksel.EQ.1 ) THEN
213  rank = mn
214  ELSE IF( rksel.EQ.2 ) THEN
215  rank = ( 3*mn ) / 4
216  DO 10 j = rank + 1, mn
217  s( j ) = zero
218  10 continue
219  ELSE
220  CALL xerbla( 'CQRT15', 2 )
221  END IF
222 *
223  IF( rank.GT.0 ) THEN
224 *
225 * Nontrivial case
226 *
227  s( 1 ) = one
228  DO 30 j = 2, rank
229  20 continue
230  temp = slarnd( 1, iseed )
231  IF( temp.GT.svmin ) THEN
232  s( j ) = abs( temp )
233  ELSE
234  go to 20
235  END IF
236  30 continue
237  CALL slaord( 'Decreasing', rank, s, 1 )
238 *
239 * Generate 'rank' columns of a random orthogonal matrix in A
240 *
241  CALL clarnv( 2, iseed, m, work )
242  CALL csscal( m, one / scnrm2( m, work, 1 ), work, 1 )
243  CALL claset( 'Full', m, rank, czero, cone, a, lda )
244  CALL clarf( 'Left', m, rank, work, 1, cmplx( two ), a, lda,
245  $ work( m+1 ) )
246 *
247 * workspace used: m+mn
248 *
249 * Generate consistent rhs in the range space of A
250 *
251  CALL clarnv( 2, iseed, rank*nrhs, work )
252  CALL cgemm( 'No transpose', 'No transpose', m, nrhs, rank,
253  $ cone, a, lda, work, rank, czero, b, ldb )
254 *
255 * work space used: <= mn *nrhs
256 *
257 * generate (unscaled) matrix A
258 *
259  DO 40 j = 1, rank
260  CALL csscal( m, s( j ), a( 1, j ), 1 )
261  40 continue
262  IF( rank.LT.n )
263  $ CALL claset( 'Full', m, n-rank, czero, czero,
264  $ a( 1, rank+1 ), lda )
265  CALL claror( 'Right', 'No initialization', m, n, a, lda, iseed,
266  $ work, info )
267 *
268  ELSE
269 *
270 * work space used 2*n+m
271 *
272 * Generate null matrix and rhs
273 *
274  DO 50 j = 1, mn
275  s( j ) = zero
276  50 continue
277  CALL claset( 'Full', m, n, czero, czero, a, lda )
278  CALL claset( 'Full', m, nrhs, czero, czero, b, ldb )
279 *
280  END IF
281 *
282 * Scale the matrix
283 *
284  IF( scale.NE.1 ) THEN
285  norma = clange( 'Max', m, n, a, lda, dummy )
286  IF( norma.NE.zero ) THEN
287  IF( scale.EQ.2 ) THEN
288 *
289 * matrix scaled up
290 *
291  CALL clascl( 'General', 0, 0, norma, bignum, m, n, a,
292  $ lda, info )
293  CALL slascl( 'General', 0, 0, norma, bignum, mn, 1, s,
294  $ mn, info )
295  CALL clascl( 'General', 0, 0, norma, bignum, m, nrhs, b,
296  $ ldb, info )
297  ELSE IF( scale.EQ.3 ) THEN
298 *
299 * matrix scaled down
300 *
301  CALL clascl( 'General', 0, 0, norma, smlnum, m, n, a,
302  $ lda, info )
303  CALL slascl( 'General', 0, 0, norma, smlnum, mn, 1, s,
304  $ mn, info )
305  CALL clascl( 'General', 0, 0, norma, smlnum, m, nrhs, b,
306  $ ldb, info )
307  ELSE
308  CALL xerbla( 'CQRT15', 1 )
309  return
310  END IF
311  END IF
312  END IF
313 *
314  norma = sasum( mn, s, 1 )
315  normb = clange( 'One-norm', m, nrhs, b, ldb, dummy )
316 *
317  return
318 *
319 * End of CQRT15
320 *
321  END