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