LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
clarge.f
Go to the documentation of this file.
1 *> \brief \b CLARGE
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 CLARGE( 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 A( LDA, * ), WORK( * )
19 * ..
20 *
21 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> CLARGE 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 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 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 *> \date November 2011
84 *
85 *> \ingroup complex_matgen
86 *
87 * =====================================================================
88  SUBROUTINE clarge( N, A, LDA, ISEED, WORK, INFO )
89 *
90 * -- LAPACK auxiliary routine (version 3.4.0) --
91 * -- LAPACK is a software package provided by Univ. of Tennessee, --
92 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
93 * November 2011
94 *
95 * .. Scalar Arguments ..
96  INTEGER INFO, LDA, N
97 * ..
98 * .. Array Arguments ..
99  INTEGER ISEED( 4 )
100  COMPLEX A( lda, * ), WORK( * )
101 * ..
102 *
103 * =====================================================================
104 *
105 * .. Parameters ..
106  COMPLEX ZERO, ONE
107  parameter ( zero = ( 0.0e+0, 0.0e+0 ),
108  $ one = ( 1.0e+0, 0.0e+0 ) )
109 * ..
110 * .. Local Scalars ..
111  INTEGER I
112  REAL WN
113  COMPLEX TAU, WA, WB
114 * ..
115 * .. External Subroutines ..
116  EXTERNAL cgemv, cgerc, clarnv, cscal, xerbla
117 * ..
118 * .. Intrinsic Functions ..
119  INTRINSIC abs, max, real
120 * ..
121 * .. External Functions ..
122  REAL SCNRM2
123  EXTERNAL scnrm2
124 * ..
125 * .. Executable Statements ..
126 *
127 * Test the input arguments
128 *
129  info = 0
130  IF( n.LT.0 ) THEN
131  info = -1
132  ELSE IF( lda.LT.max( 1, n ) ) THEN
133  info = -3
134  END IF
135  IF( info.LT.0 ) THEN
136  CALL xerbla( 'CLARGE', -info )
137  RETURN
138  END IF
139 *
140 * pre- and post-multiply A by random unitary matrix
141 *
142  DO 10 i = n, 1, -1
143 *
144 * generate random reflection
145 *
146  CALL clarnv( 3, iseed, n-i+1, work )
147  wn = scnrm2( n-i+1, work, 1 )
148  wa = ( wn / abs( work( 1 ) ) )*work( 1 )
149  IF( wn.EQ.zero ) THEN
150  tau = zero
151  ELSE
152  wb = work( 1 ) + wa
153  CALL cscal( n-i, one / wb, work( 2 ), 1 )
154  work( 1 ) = one
155  tau = REAL( wb / wa )
156  END IF
157 *
158 * multiply A(i:n,1:n) by random reflection from the left
159 *
160  CALL cgemv( 'Conjugate transpose', n-i+1, n, one, a( i, 1 ),
161  $ lda, work, 1, zero, work( n+1 ), 1 )
162  CALL cgerc( n-i+1, n, -tau, work, 1, work( n+1 ), 1, a( i, 1 ),
163  $ lda )
164 *
165 * multiply A(1:n,i:n) by random reflection from the right
166 *
167  CALL cgemv( 'No transpose', n, n-i+1, one, a( 1, i ), lda,
168  $ work, 1, zero, work( n+1 ), 1 )
169  CALL cgerc( n, n-i+1, -tau, work( n+1 ), 1, work, 1, a( 1, i ),
170  $ lda )
171  10 CONTINUE
172  RETURN
173 *
174 * End of CLARGE
175 *
176  END
subroutine clarge(N, A, LDA, ISEED, WORK, INFO)
CLARGE
Definition: clarge.f:89
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine cscal(N, CA, CX, INCX)
CSCAL
Definition: cscal.f:54
subroutine cgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
CGEMV
Definition: cgemv.f:160
subroutine clarnv(IDIST, ISEED, N, X)
CLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition: clarnv.f:101
subroutine cgerc(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
CGERC
Definition: cgerc.f:132