LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zlarge.f
Go to the documentation of this file.
1*> \brief \b ZLARGE
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 ZLARGE( N, A, LDA, ISEED, WORK, INFO )
12*
13* .. Scalar Arguments ..
14* INTEGER INFO, LDA, N
15* ..
16* .. Array Arguments ..
17* INTEGER ISEED( 4 )
18* COMPLEX*16 A( LDA, * ), WORK( * )
19* ..
20*
21*
22*> \par Purpose:
23* =============
24*>
25*> \verbatim
26*>
27*> ZLARGE pre- and post-multiplies a complex general n by n matrix A
28*> with a random unitary matrix: A = U*D*U'.
29*> \endverbatim
30*
31* Arguments:
32* ==========
33*
34*> \param[in] N
35*> \verbatim
36*> N is INTEGER
37*> The order of the matrix A. N >= 0.
38*> \endverbatim
39*>
40*> \param[in,out] A
41*> \verbatim
42*> A is COMPLEX*16 array, dimension (LDA,N)
43*> On entry, the original n by n matrix A.
44*> On exit, A is overwritten by U*A*U' for some random
45*> unitary matrix U.
46*> \endverbatim
47*>
48*> \param[in] LDA
49*> \verbatim
50*> LDA is INTEGER
51*> The leading dimension of the array A. LDA >= N.
52*> \endverbatim
53*>
54*> \param[in,out] ISEED
55*> \verbatim
56*> ISEED is INTEGER array, dimension (4)
57*> On entry, the seed of the random number generator; the array
58*> elements must be between 0 and 4095, and ISEED(4) must be
59*> odd.
60*> On exit, the seed is updated.
61*> \endverbatim
62*>
63*> \param[out] WORK
64*> \verbatim
65*> WORK is COMPLEX*16 array, dimension (2*N)
66*> \endverbatim
67*>
68*> \param[out] INFO
69*> \verbatim
70*> INFO is INTEGER
71*> = 0: successful exit
72*> < 0: if INFO = -i, the i-th argument had an illegal value
73*> \endverbatim
74*
75* Authors:
76* ========
77*
78*> \author Univ. of Tennessee
79*> \author Univ. of California Berkeley
80*> \author Univ. of Colorado Denver
81*> \author NAG Ltd.
82*
83*> \ingroup complex16_matgen
84*
85* =====================================================================
86 SUBROUTINE zlarge( N, A, LDA, ISEED, WORK, INFO )
87*
88* -- LAPACK auxiliary routine --
89* -- LAPACK is a software package provided by Univ. of Tennessee, --
90* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
91*
92* .. Scalar Arguments ..
93 INTEGER INFO, LDA, N
94* ..
95* .. Array Arguments ..
96 INTEGER ISEED( 4 )
97 COMPLEX*16 A( LDA, * ), WORK( * )
98* ..
99*
100* =====================================================================
101*
102* .. Parameters ..
103 COMPLEX*16 ZERO, ONE
104 parameter( zero = ( 0.0d+0, 0.0d+0 ),
105 $ one = ( 1.0d+0, 0.0d+0 ) )
106* ..
107* .. Local Scalars ..
108 INTEGER I
109 DOUBLE PRECISION WN
110 COMPLEX*16 TAU, WA, WB
111* ..
112* .. External Subroutines ..
113 EXTERNAL xerbla, zgemv, zgerc, zlarnv, zscal
114* ..
115* .. Intrinsic Functions ..
116 INTRINSIC abs, dble, max
117* ..
118* .. External Functions ..
119 DOUBLE PRECISION DZNRM2
120 EXTERNAL dznrm2
121* ..
122* .. Executable Statements ..
123*
124* Test the input arguments
125*
126 info = 0
127 IF( n.LT.0 ) THEN
128 info = -1
129 ELSE IF( lda.LT.max( 1, n ) ) THEN
130 info = -3
131 END IF
132 IF( info.LT.0 ) THEN
133 CALL xerbla( 'ZLARGE', -info )
134 RETURN
135 END IF
136*
137* pre- and post-multiply A by random unitary matrix
138*
139 DO 10 i = n, 1, -1
140*
141* generate random reflection
142*
143 CALL zlarnv( 3, iseed, n-i+1, work )
144 wn = dznrm2( n-i+1, work, 1 )
145 wa = ( wn / abs( work( 1 ) ) )*work( 1 )
146 IF( wn.EQ.zero ) THEN
147 tau = zero
148 ELSE
149 wb = work( 1 ) + wa
150 CALL zscal( n-i, one / wb, work( 2 ), 1 )
151 work( 1 ) = one
152 tau = dble( wb / wa )
153 END IF
154*
155* multiply A(i:n,1:n) by random reflection from the left
156*
157 CALL zgemv( 'Conjugate transpose', n-i+1, n, one, a( i, 1 ),
158 $ lda, work, 1, zero, work( n+1 ), 1 )
159 CALL zgerc( n-i+1, n, -tau, work, 1, work( n+1 ), 1, a( i, 1 ),
160 $ lda )
161*
162* multiply A(1:n,i:n) by random reflection from the right
163*
164 CALL zgemv( 'No transpose', n, n-i+1, one, a( 1, i ), lda,
165 $ work, 1, zero, work( n+1 ), 1 )
166 CALL zgerc( n, n-i+1, -tau, work( n+1 ), 1, work, 1, a( 1, i ),
167 $ lda )
168 10 CONTINUE
169 RETURN
170*
171* End of ZLARGE
172*
173 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
subroutine zgerc(m, n, alpha, x, incx, y, incy, a, lda)
ZGERC
Definition zgerc.f:130
subroutine zlarnv(idist, iseed, n, x)
ZLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition zlarnv.f:99
subroutine zscal(n, za, zx, incx)
ZSCAL
Definition zscal.f:78
subroutine zlarge(n, a, lda, iseed, work, info)
ZLARGE
Definition zlarge.f:87