LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlarge.f
Go to the documentation of this file.
1*> \brief \b DLARGE
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 DLARGE( N, A, LDA, ISEED, WORK, INFO )
12*
13* .. Scalar Arguments ..
14* INTEGER INFO, LDA, N
15* ..
16* .. Array Arguments ..
17* INTEGER ISEED( 4 )
18* DOUBLE PRECISION A( LDA, * ), WORK( * )
19* ..
20*
21*
22*> \par Purpose:
23* =============
24*>
25*> \verbatim
26*>
27*> DLARGE pre- and post-multiplies a real general n by n matrix A
28*> with a random orthogonal 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 DOUBLE PRECISION 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*> orthogonal 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 DOUBLE PRECISION 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 double_matgen
84*
85* =====================================================================
86 SUBROUTINE dlarge( 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 DOUBLE PRECISION A( LDA, * ), WORK( * )
98* ..
99*
100* =====================================================================
101*
102* .. Parameters ..
103 DOUBLE PRECISION ZERO, ONE
104 parameter( zero = 0.0d+0, one = 1.0d+0 )
105* ..
106* .. Local Scalars ..
107 INTEGER I
108 DOUBLE PRECISION TAU, WA, WB, WN
109* ..
110* .. External Subroutines ..
111 EXTERNAL dgemv, dger, dlarnv, dscal, xerbla
112* ..
113* .. Intrinsic Functions ..
114 INTRINSIC max, sign
115* ..
116* .. External Functions ..
117 DOUBLE PRECISION DNRM2
118 EXTERNAL dnrm2
119* ..
120* .. Executable Statements ..
121*
122* Test the input arguments
123*
124 info = 0
125 IF( n.LT.0 ) THEN
126 info = -1
127 ELSE IF( lda.LT.max( 1, n ) ) THEN
128 info = -3
129 END IF
130 IF( info.LT.0 ) THEN
131 CALL xerbla( 'DLARGE', -info )
132 RETURN
133 END IF
134*
135* pre- and post-multiply A by random orthogonal matrix
136*
137 DO 10 i = n, 1, -1
138*
139* generate random reflection
140*
141 CALL dlarnv( 3, iseed, n-i+1, work )
142 wn = dnrm2( n-i+1, work, 1 )
143 wa = sign( wn, work( 1 ) )
144 IF( wn.EQ.zero ) THEN
145 tau = zero
146 ELSE
147 wb = work( 1 ) + wa
148 CALL dscal( n-i, one / wb, work( 2 ), 1 )
149 work( 1 ) = one
150 tau = wb / wa
151 END IF
152*
153* multiply A(i:n,1:n) by random reflection from the left
154*
155 CALL dgemv( 'Transpose', n-i+1, n, one, a( i, 1 ), lda, work,
156 $ 1, zero, work( n+1 ), 1 )
157 CALL dger( n-i+1, n, -tau, work, 1, work( n+1 ), 1, a( i, 1 ),
158 $ lda )
159*
160* multiply A(1:n,i:n) by random reflection from the right
161*
162 CALL dgemv( 'No transpose', n, n-i+1, one, a( 1, i ), lda,
163 $ work, 1, zero, work( n+1 ), 1 )
164 CALL dger( n, n-i+1, -tau, work( n+1 ), 1, work, 1, a( 1, i ),
165 $ lda )
166 10 CONTINUE
167 RETURN
168*
169* End of DLARGE
170*
171 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dlarge(n, a, lda, iseed, work, info)
DLARGE
Definition dlarge.f:87
subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
DGEMV
Definition dgemv.f:158
subroutine dger(m, n, alpha, x, incx, y, incy, a, lda)
DGER
Definition dger.f:130
subroutine dlarnv(idist, iseed, n, x)
DLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition dlarnv.f:97
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79