LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cqrt13.f
Go to the documentation of this file.
1*> \brief \b CQRT13
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 CQRT13( SCALE, M, N, A, LDA, NORMA, ISEED )
12*
13* .. Scalar Arguments ..
14* INTEGER LDA, M, N, SCALE
15* REAL NORMA
16* ..
17* .. Array Arguments ..
18* INTEGER ISEED( 4 )
19* COMPLEX A( LDA, * )
20* ..
21*
22*
23*> \par Purpose:
24* =============
25*>
26*> \verbatim
27*>
28*> CQRT13 generates a full-rank matrix that may be scaled to have large
29*> or small norm.
30*> \endverbatim
31*
32* Arguments:
33* ==========
34*
35*> \param[in] SCALE
36*> \verbatim
37*> SCALE is INTEGER
38*> SCALE = 1: normally scaled matrix
39*> SCALE = 2: matrix scaled up
40*> SCALE = 3: matrix scaled down
41*> \endverbatim
42*>
43*> \param[in] M
44*> \verbatim
45*> M is INTEGER
46*> The number of rows of the matrix A.
47*> \endverbatim
48*>
49*> \param[in] N
50*> \verbatim
51*> N is INTEGER
52*> The number of columns of A.
53*> \endverbatim
54*>
55*> \param[out] A
56*> \verbatim
57*> A is COMPLEX array, dimension (LDA,N)
58*> The M-by-N matrix A.
59*> \endverbatim
60*>
61*> \param[in] LDA
62*> \verbatim
63*> LDA is INTEGER
64*> The leading dimension of the array A.
65*> \endverbatim
66*>
67*> \param[out] NORMA
68*> \verbatim
69*> NORMA is REAL
70*> The one-norm of A.
71*> \endverbatim
72*>
73*> \param[in,out] ISEED
74*> \verbatim
75*> ISEED is integer array, dimension (4)
76*> Seed for random number generator
77*> \endverbatim
78*
79* Authors:
80* ========
81*
82*> \author Univ. of Tennessee
83*> \author Univ. of California Berkeley
84*> \author Univ. of Colorado Denver
85*> \author NAG Ltd.
86*
87*> \ingroup complex_lin
88*
89* =====================================================================
90 SUBROUTINE cqrt13( SCALE, M, N, A, LDA, NORMA, ISEED )
91*
92* -- LAPACK test routine --
93* -- LAPACK is a software package provided by Univ. of Tennessee, --
94* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
95*
96* .. Scalar Arguments ..
97 INTEGER LDA, M, N, SCALE
98 REAL NORMA
99* ..
100* .. Array Arguments ..
101 INTEGER ISEED( 4 )
102 COMPLEX A( LDA, * )
103* ..
104*
105* =====================================================================
106*
107* .. Parameters ..
108 REAL ONE
109 parameter( one = 1.0e0 )
110* ..
111* .. Local Scalars ..
112 INTEGER INFO, J
113 REAL BIGNUM, SMLNUM
114* ..
115* .. External Functions ..
116 REAL CLANGE, SCASUM, SLAMCH
117 EXTERNAL clange, scasum, slamch
118* ..
119* .. External Subroutines ..
120 EXTERNAL clarnv, clascl
121* ..
122* .. Intrinsic Functions ..
123 INTRINSIC cmplx, real, sign
124* ..
125* .. Local Arrays ..
126 REAL DUMMY( 1 )
127* ..
128* .. Executable Statements ..
129*
130 IF( m.LE.0 .OR. n.LE.0 )
131 $ RETURN
132*
133* benign matrix
134*
135 DO 10 j = 1, n
136 CALL clarnv( 2, iseed, m, a( 1, j ) )
137 IF( j.LE.m ) THEN
138 a( j, j ) = a( j, j ) + cmplx( sign( scasum( m, a( 1, j ),
139 $ 1 ), real( a( j, j ) ) ) )
140 END IF
141 10 CONTINUE
142*
143* scaled versions
144*
145 IF( scale.NE.1 ) THEN
146 norma = clange( 'Max', m, n, a, lda, dummy )
147 smlnum = slamch( 'Safe minimum' )
148 bignum = one / smlnum
149 smlnum = smlnum / slamch( 'Epsilon' )
150 bignum = one / smlnum
151*
152 IF( scale.EQ.2 ) THEN
153*
154* matrix scaled up
155*
156 CALL clascl( 'General', 0, 0, norma, bignum, m, n, a, lda,
157 $ info )
158 ELSE IF( scale.EQ.3 ) THEN
159*
160* matrix scaled down
161*
162 CALL clascl( 'General', 0, 0, norma, smlnum, m, n, a, lda,
163 $ info )
164 END IF
165 END IF
166*
167 norma = clange( 'One-norm', m, n, a, lda, dummy )
168 RETURN
169*
170* End of CQRT13
171*
172 END
subroutine cqrt13(scale, m, n, a, lda, norma, iseed)
CQRT13
Definition cqrt13.f:91
subroutine clarnv(idist, iseed, n, x)
CLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition clarnv.f:99
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:143