LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
csyswapr.f
Go to the documentation of this file.
1*> \brief \b CSYSWAPR
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CSYSWAPR + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/csyswapr.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/csyswapr.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/csyswapr.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CSYSWAPR( UPLO, N, A, LDA, I1, I2)
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER I1, I2, LDA, N
24* ..
25* .. Array Arguments ..
26* COMPLEX A( LDA, N )
27*
28*
29*> \par Purpose:
30* =============
31*>
32*> \verbatim
33*>
34*> CSYSWAPR applies an elementary permutation on the rows and the columns of
35*> a symmetric matrix.
36*> \endverbatim
37*
38* Arguments:
39* ==========
40*
41*> \param[in] UPLO
42*> \verbatim
43*> UPLO is CHARACTER*1
44*> Specifies whether the details of the factorization are stored
45*> as an upper or lower triangular matrix.
46*> = 'U': Upper triangular, form is A = U*D*U**T;
47*> = 'L': Lower triangular, form is A = L*D*L**T.
48*> \endverbatim
49*>
50*> \param[in] N
51*> \verbatim
52*> N is INTEGER
53*> The order of the matrix A. N >= 0.
54*> \endverbatim
55*>
56*> \param[in,out] A
57*> \verbatim
58*> A is COMPLEX array, dimension (LDA,N)
59*> On entry, the N-by-N matrix A. On exit, the permuted matrix
60*> where the rows I1 and I2 and columns I1 and I2 are interchanged.
61*> If UPLO = 'U', the interchanges are applied to the upper
62*> triangular part and the strictly lower triangular part of A is
63*> not referenced; if UPLO = 'L', the interchanges are applied to
64*> the lower triangular part and the part of A above the diagonal
65*> is not referenced.
66*> \endverbatim
67*>
68*> \param[in] LDA
69*> \verbatim
70*> LDA is INTEGER
71*> The leading dimension of the array A. LDA >= max(1,N).
72*> \endverbatim
73*>
74*> \param[in] I1
75*> \verbatim
76*> I1 is INTEGER
77*> Index of the first row to swap
78*> \endverbatim
79*>
80*> \param[in] I2
81*> \verbatim
82*> I2 is INTEGER
83*> Index of the second row to swap
84*> \endverbatim
85*
86* Authors:
87* ========
88*
89*> \author Univ. of Tennessee
90*> \author Univ. of California Berkeley
91*> \author Univ. of Colorado Denver
92*> \author NAG Ltd.
93*
94*> \ingroup heswapr
95*
96* =====================================================================
97 SUBROUTINE csyswapr( UPLO, N, A, LDA, I1, I2)
98*
99* -- LAPACK auxiliary routine --
100* -- LAPACK is a software package provided by Univ. of Tennessee, --
101* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
102*
103* .. Scalar Arguments ..
104 CHARACTER UPLO
105 INTEGER I1, I2, LDA, N
106* ..
107* .. Array Arguments ..
108 COMPLEX A( LDA, N )
109*
110* =====================================================================
111*
112* ..
113* .. Local Scalars ..
114 LOGICAL UPPER
115 COMPLEX TMP
116*
117* .. External Functions ..
118 LOGICAL LSAME
119 EXTERNAL lsame
120* ..
121* .. External Subroutines ..
122 EXTERNAL cswap
123* ..
124* .. Executable Statements ..
125*
126 upper = lsame( uplo, 'U' )
127 IF (upper) THEN
128*
129* UPPER
130* first swap
131* - swap column I1 and I2 from I1 to I1-1
132 CALL cswap( i1-1, a(1,i1), 1, a(1,i2), 1 )
133*
134* second swap :
135* - swap A(I1,I1) and A(I2,I2)
136* - swap row I1 from I1+1 to I2-1 with col I2 from I1+1 to I2-1
137 tmp=a(i1,i1)
138 a(i1,i1)=a(i2,i2)
139 a(i2,i2)=tmp
140*
141 CALL cswap( i2-i1-1, a(i1,i1+1), lda, a(i1+1,i2), 1 )
142*
143* third swap
144* - swap row I1 and I2 from I2+1 to N
145 IF ( i2.LT.n )
146 $ CALL cswap( n-i2, a(i1,i2+1), lda, a(i2,i2+1), lda )
147*
148 ELSE
149*
150* LOWER
151* first swap
152* - swap row I1 and I2 from I1 to I1-1
153 CALL cswap ( i1-1, a(i1,1), lda, a(i2,1), lda )
154*
155* second swap :
156* - swap A(I1,I1) and A(I2,I2)
157* - swap col I1 from I1+1 to I2-1 with row I2 from I1+1 to I2-1
158 tmp=a(i1,i1)
159 a(i1,i1)=a(i2,i2)
160 a(i2,i2)=tmp
161*
162 CALL cswap( i2-i1-1, a(i1+1,i1), 1, a(i2,i1+1), lda )
163*
164* third swap
165* - swap col I1 and I2 from I2+1 to N
166 IF ( i2.LT.n )
167 $ CALL cswap( n-i2, a(i2+1,i1), 1, a(i2+1,i2), 1 )
168*
169 ENDIF
170 END SUBROUTINE csyswapr
171
subroutine csyswapr(uplo, n, a, lda, i1, i2)
CSYSWAPR
Definition csyswapr.f:98
subroutine cswap(n, cx, incx, cy, incy)
CSWAP
Definition cswap.f:81