LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
slarge.f
Go to the documentation of this file.
1 *> \brief \b SLARGE
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 SLARGE( N, A, LDA, ISEED, WORK, INFO )
12 *
13 * .. Scalar Arguments ..
14 * INTEGER INFO, LDA, N
15 * ..
16 * .. Array Arguments ..
17 * INTEGER ISEED( 4 )
18 * REAL A( LDA, * ), WORK( * )
19 * ..
20 *
21 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> SLARGE 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 REAL 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 REAL 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 real_matgen
86 *
87 * =====================================================================
88  SUBROUTINE slarge( 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  REAL a( lda, * ), work( * )
101 * ..
102 *
103 * =====================================================================
104 *
105 * .. Parameters ..
106  REAL zero, one
107  parameter( zero = 0.0e+0, one = 1.0e+0 )
108 * ..
109 * .. Local Scalars ..
110  INTEGER i
111  REAL tau, wa, wb, wn
112 * ..
113 * .. External Subroutines ..
114  EXTERNAL sgemv, sger, slarnv, sscal, xerbla
115 * ..
116 * .. Intrinsic Functions ..
117  INTRINSIC max, sign
118 * ..
119 * .. External Functions ..
120  REAL snrm2
121  EXTERNAL snrm2
122 * ..
123 * .. Executable Statements ..
124 *
125 * Test the input arguments
126 *
127  info = 0
128  IF( n.LT.0 ) THEN
129  info = -1
130  ELSE IF( lda.LT.max( 1, n ) ) THEN
131  info = -3
132  END IF
133  IF( info.LT.0 ) THEN
134  CALL xerbla( 'SLARGE', -info )
135  return
136  END IF
137 *
138 * pre- and post-multiply A by random orthogonal matrix
139 *
140  DO 10 i = n, 1, -1
141 *
142 * generate random reflection
143 *
144  CALL slarnv( 3, iseed, n-i+1, work )
145  wn = snrm2( n-i+1, work, 1 )
146  wa = sign( wn, work( 1 ) )
147  IF( wn.EQ.zero ) THEN
148  tau = zero
149  ELSE
150  wb = work( 1 ) + wa
151  CALL sscal( n-i, one / wb, work( 2 ), 1 )
152  work( 1 ) = one
153  tau = wb / wa
154  END IF
155 *
156 * multiply A(i:n,1:n) by random reflection from the left
157 *
158  CALL sgemv( 'Transpose', n-i+1, n, one, a( i, 1 ), lda, work,
159  $ 1, zero, work( n+1 ), 1 )
160  CALL sger( n-i+1, n, -tau, work, 1, work( n+1 ), 1, a( i, 1 ),
161  $ lda )
162 *
163 * multiply A(1:n,i:n) by random reflection from the right
164 *
165  CALL sgemv( 'No transpose', n, n-i+1, one, a( 1, i ), lda,
166  $ work, 1, zero, work( n+1 ), 1 )
167  CALL sger( n, n-i+1, -tau, work( n+1 ), 1, work, 1, a( 1, i ),
168  $ lda )
169  10 continue
170  return
171 *
172 * End of SLARGE
173 *
174  END