LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dsyswapr.f
Go to the documentation of this file.
1*> \brief \b DSYSWAPR applies an elementary permutation on the rows and columns of a symmetric matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download DSYSWAPR + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dsyswapr.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dsyswapr.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsyswapr.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE DSYSWAPR( UPLO, N, A, LDA, I1, I2)
22*
23* .. Scalar Arguments ..
24* CHARACTER UPLO
25* INTEGER I1, I2, LDA, N
26* ..
27* .. Array Arguments ..
28* DOUBLE PRECISION A( LDA, N )
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> DSYSWAPR applies an elementary permutation on the rows and the columns of
37*> a symmetric 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 DOUBLE PRECISION array, dimension (LDA,*)
61*> On entry, the N-by-N matrix A. On exit, the permuted matrix
62*> where the rows I1 and I2 and columns I1 and I2 are interchanged.
63*> If UPLO = 'U', the interchanges are applied to the upper
64*> triangular part and the strictly lower triangular part of A is
65*> not referenced; if UPLO = 'L', the interchanges are applied to
66*> the lower triangular part and the part of A above the diagonal
67*> is 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 dsyswapr( 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 DOUBLE PRECISION A( LDA, * )
111*
112* =====================================================================
113*
114* ..
115* .. Local Scalars ..
116 LOGICAL UPPER
117 DOUBLE PRECISION TMP
118*
119* .. External Functions ..
120 LOGICAL LSAME
121 EXTERNAL lsame
122* ..
123* .. External Subroutines ..
124 EXTERNAL dswap
125* ..
126* .. Executable Statements ..
127*
128 upper = lsame( uplo, 'U' )
129 IF (upper) THEN
130*
131* UPPER
132* first swap
133* - swap column I1 and I2 from I1 to I1-1
134 CALL dswap( i1-1, a(1,i1), 1, a(1,i2), 1 )
135*
136* second swap :
137* - swap A(I1,I1) and A(I2,I2)
138* - swap row I1 from I1+1 to I2-1 with col I2 from I1+1 to I2-1
139 tmp=a(i1,i1)
140 a(i1,i1)=a(i2,i2)
141 a(i2,i2)=tmp
142*
143 CALL dswap( i2-i1-1, a(i1,i1+1), lda, a(i1+1,i2), 1 )
144*
145* third swap
146* - swap row I1 and I2 from I2+1 to N
147 IF ( i2.LT.n )
148 $ CALL dswap( n-i2, a(i1,i2+1), lda, a(i2,i2+1), lda )
149*
150 ELSE
151*
152* LOWER
153* first swap
154* - swap row I1 and I2 from I1 to I1-1
155 CALL dswap( i1-1, a(i1,1), lda, a(i2,1), lda )
156*
157* second swap :
158* - swap A(I1,I1) and A(I2,I2)
159* - swap col I1 from I1+1 to I2-1 with row I2 from I1+1 to I2-1
160 tmp=a(i1,i1)
161 a(i1,i1)=a(i2,i2)
162 a(i2,i2)=tmp
163*
164 CALL dswap( i2-i1-1, a(i1+1,i1), 1, a(i2,i1+1), lda )
165*
166* third swap
167* - swap col I1 and I2 from I2+1 to N
168 IF ( i2.LT.n )
169 $ CALL dswap( n-i2, a(i2+1,i1), 1, a(i2+1,i2), 1 )
170*
171 ENDIF
172 END SUBROUTINE dsyswapr
173
subroutine dsyswapr(uplo, n, a, lda, i1, i2)
DSYSWAPR applies an elementary permutation on the rows and columns of a symmetric matrix.
Definition dsyswapr.f:100
subroutine dswap(n, dx, incx, dy, incy)
DSWAP
Definition dswap.f:82