LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
claset.f
Go to the documentation of this file.
1*> \brief \b CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CLASET + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/claset.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/claset.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/claset.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CLASET( UPLO, M, N, ALPHA, BETA, A, LDA )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER LDA, M, N
24* COMPLEX ALPHA, BETA
25* ..
26* .. Array Arguments ..
27* COMPLEX A( LDA, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> CLASET initializes a 2-D array A to BETA on the diagonal and
37*> ALPHA on the offdiagonals.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] UPLO
44*> \verbatim
45*> UPLO is CHARACTER*1
46*> Specifies the part of the matrix A to be set.
47*> = 'U': Upper triangular part is set. The lower triangle
48*> is unchanged.
49*> = 'L': Lower triangular part is set. The upper triangle
50*> is unchanged.
51*> Otherwise: All of the matrix A is set.
52*> \endverbatim
53*>
54*> \param[in] M
55*> \verbatim
56*> M is INTEGER
57*> On entry, M specifies the number of rows of A.
58*> \endverbatim
59*>
60*> \param[in] N
61*> \verbatim
62*> N is INTEGER
63*> On entry, N specifies the number of columns of A.
64*> \endverbatim
65*>
66*> \param[in] ALPHA
67*> \verbatim
68*> ALPHA is COMPLEX
69*> All the offdiagonal array elements are set to ALPHA.
70*> \endverbatim
71*>
72*> \param[in] BETA
73*> \verbatim
74*> BETA is COMPLEX
75*> All the diagonal array elements are set to BETA.
76*> \endverbatim
77*>
78*> \param[out] A
79*> \verbatim
80*> A is COMPLEX array, dimension (LDA,N)
81*> On entry, the m by n matrix A.
82*> On exit, A(i,j) = ALPHA, 1 <= i <= m, 1 <= j <= n, i.ne.j;
83*> A(i,i) = BETA , 1 <= i <= min(m,n)
84*> \endverbatim
85*>
86*> \param[in] LDA
87*> \verbatim
88*> LDA is INTEGER
89*> The leading dimension of the array A. LDA >= max(1,M).
90*> \endverbatim
91*
92* Authors:
93* ========
94*
95*> \author Univ. of Tennessee
96*> \author Univ. of California Berkeley
97*> \author Univ. of Colorado Denver
98*> \author NAG Ltd.
99*
100*> \ingroup laset
101*
102* =====================================================================
103 SUBROUTINE claset( UPLO, M, N, ALPHA, BETA, A, LDA )
104*
105* -- LAPACK auxiliary routine --
106* -- LAPACK is a software package provided by Univ. of Tennessee, --
107* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
108*
109* .. Scalar Arguments ..
110 CHARACTER UPLO
111 INTEGER LDA, M, N
112 COMPLEX ALPHA, BETA
113* ..
114* .. Array Arguments ..
115 COMPLEX A( LDA, * )
116* ..
117*
118* =====================================================================
119*
120* .. Local Scalars ..
121 INTEGER I, J
122* ..
123* .. External Functions ..
124 LOGICAL LSAME
125 EXTERNAL lsame
126* ..
127* .. Intrinsic Functions ..
128 INTRINSIC min
129* ..
130* .. Executable Statements ..
131*
132 IF( lsame( uplo, 'U' ) ) THEN
133*
134* Set the diagonal to BETA and the strictly upper triangular
135* part of the array to ALPHA.
136*
137 DO 20 j = 2, n
138 DO 10 i = 1, min( j-1, m )
139 a( i, j ) = alpha
140 10 CONTINUE
141 20 CONTINUE
142 DO 30 i = 1, min( n, m )
143 a( i, i ) = beta
144 30 CONTINUE
145*
146 ELSE IF( lsame( uplo, 'L' ) ) THEN
147*
148* Set the diagonal to BETA and the strictly lower triangular
149* part of the array to ALPHA.
150*
151 DO 50 j = 1, min( m, n )
152 DO 40 i = j + 1, m
153 a( i, j ) = alpha
154 40 CONTINUE
155 50 CONTINUE
156 DO 60 i = 1, min( n, m )
157 a( i, i ) = beta
158 60 CONTINUE
159*
160 ELSE
161*
162* Set the array to BETA on the diagonal and ALPHA on the
163* offdiagonal.
164*
165 DO 80 j = 1, n
166 DO 70 i = 1, m
167 a( i, j ) = alpha
168 70 CONTINUE
169 80 CONTINUE
170 DO 90 i = 1, min( m, n )
171 a( i, i ) = beta
172 90 CONTINUE
173 END IF
174*
175 RETURN
176*
177* End of CLASET
178*
179 END
subroutine claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition claset.f:104