LAPACK 3.12.1
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*> Download CHESWAPR + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cheswapr.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cheswapr.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cheswapr.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CHESWAPR( 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*> CHESWAPR applies an elementary permutation on the rows and the columns of
35*> a hermitian 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 NB diagonal matrix D and the multipliers
60*> used to obtain the factor U or L as computed by CSYTRF.
61*>
62*> On exit, if INFO = 0, the (symmetric) inverse of the original
63*> matrix. If UPLO = 'U', the upper triangular part of the
64*> inverse is formed and the part of A below the diagonal is not
65*> referenced; if UPLO = 'L' the lower triangular part of the
66*> inverse is formed and the part of A above the diagonal is
67*> not referenced.
68*> \endverbatim
69*>
70*> \param[in] LDA
71*> \verbatim
72*> LDA is INTEGER
73*> The leading dimension of the array A. LDA >= max(1,N).
74*> \endverbatim
75*>
76*> \param[in] I1
77*> \verbatim
78*> I1 is INTEGER
79*> Index of the first row to swap
80*> \endverbatim
81*>
82*> \param[in] I2
83*> \verbatim
84*> I2 is INTEGER
85*> Index of the second row to swap
86*> \endverbatim
87*
88* Authors:
89* ========
90*
91*> \author Univ. of Tennessee
92*> \author Univ. of California Berkeley
93*> \author Univ. of Colorado Denver
94*> \author NAG Ltd.
95*
96*> \ingroup heswapr
97*
98* =====================================================================
99 SUBROUTINE cheswapr( UPLO, N, A, LDA, I1, I2)
100*
101* -- LAPACK auxiliary routine --
102* -- LAPACK is a software package provided by Univ. of Tennessee, --
103* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
104*
105* .. Scalar Arguments ..
106 CHARACTER UPLO
107 INTEGER I1, I2, LDA, N
108* ..
109* .. Array Arguments ..
110 COMPLEX A( LDA, N )
111*
112* =====================================================================
113*
114* ..
115* .. Local Scalars ..
116 LOGICAL UPPER
117 INTEGER I
118 COMPLEX TMP
119*
120* .. External Functions ..
121 LOGICAL LSAME
122 EXTERNAL lsame
123* ..
124* .. External Subroutines ..
125 EXTERNAL cswap
126* ..
127* .. Executable Statements ..
128*
129 upper = lsame( uplo, 'U' )
130 IF (upper) THEN
131*
132* UPPER
133* first swap
134* - swap column I1 and I2 from I1 to I1-1
135 CALL cswap( i1-1, a(1,i1), 1, a(1,i2), 1 )
136*
137* second swap :
138* - swap A(I1,I1) and A(I2,I2)
139* - swap row I1 from I1+1 to I2-1 with col I2 from I1+1 to I2-1
140* - swap A(I2,I1) and A(I1,I2)
141
142 tmp=a(i1,i1)
143 a(i1,i1)=a(i2,i2)
144 a(i2,i2)=tmp
145*
146 DO i=1,i2-i1-1
147 tmp=a(i1,i1+i)
148 a(i1,i1+i)=conjg(a(i1+i,i2))
149 a(i1+i,i2)=conjg(tmp)
150 END DO
151*
152 a(i1,i2)=conjg(a(i1,i2))
153
154*
155* third swap
156* - swap row I1 and I2 from I2+1 to N
157 DO i=i2+1,n
158 tmp=a(i1,i)
159 a(i1,i)=a(i2,i)
160 a(i2,i)=tmp
161 END DO
162*
163 ELSE
164*
165* LOWER
166* first swap
167* - swap row I1 and I2 from 1 to I1-1
168 CALL cswap ( i1-1, a(i1,1), lda, a(i2,1), lda )
169*
170* second swap :
171* - swap A(I1,I1) and A(I2,I2)
172* - swap col I1 from I1+1 to I2-1 with row I2 from I1+1 to I2-1
173* - swap A(I2,I1) and A(I1,I2)
174
175 tmp=a(i1,i1)
176 a(i1,i1)=a(i2,i2)
177 a(i2,i2)=tmp
178*
179 DO i=1,i2-i1-1
180 tmp=a(i1+i,i1)
181 a(i1+i,i1)=conjg(a(i2,i1+i))
182 a(i2,i1+i)=conjg(tmp)
183 END DO
184*
185 a(i2,i1)=conjg(a(i2,i1))
186*
187* third swap
188* - swap col I1 and I2 from I2+1 to N
189 DO i=i2+1,n
190 tmp=a(i,i1)
191 a(i,i1)=a(i,i2)
192 a(i,i2)=tmp
193 END DO
194*
195 ENDIF
196
197 END SUBROUTINE cheswapr
198
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:100
subroutine cswap(n, cx, incx, cy, incy)
CSWAP
Definition cswap.f:81