LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
clapmr.f
Go to the documentation of this file.
1*> \brief \b CLAPMR rearranges rows of a matrix as specified by a permutation vector.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CLAPMR + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clapmr.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clapmr.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clapmr.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CLAPMR( FORWRD, M, N, X, LDX, K )
20*
21* .. Scalar Arguments ..
22* LOGICAL FORWRD
23* INTEGER LDX, M, N
24* ..
25* .. Array Arguments ..
26* INTEGER K( * )
27* COMPLEX X( LDX, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> CLAPMR rearranges the rows of the M by N matrix X as specified
37*> by the permutation K(1),K(2),...,K(M) of the integers 1,...,M.
38*> If FORWRD = .TRUE., forward permutation:
39*>
40*> X(K(I),*) is moved X(I,*) for I = 1,2,...,M.
41*>
42*> If FORWRD = .FALSE., backward permutation:
43*>
44*> X(I,*) is moved to X(K(I),*) for I = 1,2,...,M.
45*> \endverbatim
46*
47* Arguments:
48* ==========
49*
50*> \param[in] FORWRD
51*> \verbatim
52*> FORWRD is LOGICAL
53*> = .TRUE., forward permutation
54*> = .FALSE., backward permutation
55*> \endverbatim
56*>
57*> \param[in] M
58*> \verbatim
59*> M is INTEGER
60*> The number of rows of the matrix X. M >= 0.
61*> \endverbatim
62*>
63*> \param[in] N
64*> \verbatim
65*> N is INTEGER
66*> The number of columns of the matrix X. N >= 0.
67*> \endverbatim
68*>
69*> \param[in,out] X
70*> \verbatim
71*> X is COMPLEX array, dimension (LDX,N)
72*> On entry, the M by N matrix X.
73*> On exit, X contains the permuted matrix X.
74*> \endverbatim
75*>
76*> \param[in] LDX
77*> \verbatim
78*> LDX is INTEGER
79*> The leading dimension of the array X, LDX >= MAX(1,M).
80*> \endverbatim
81*>
82*> \param[in,out] K
83*> \verbatim
84*> K is INTEGER array, dimension (M)
85*> On entry, K contains the permutation vector. K is used as
86*> internal workspace, but reset to its original value on
87*> output.
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 lapmr
99*
100* =====================================================================
101 SUBROUTINE clapmr( FORWRD, M, N, X, LDX, K )
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 LOGICAL FORWRD
109 INTEGER LDX, M, N
110* ..
111* .. Array Arguments ..
112 INTEGER K( * )
113 COMPLEX X( LDX, * )
114* ..
115*
116* =====================================================================
117*
118* .. Local Scalars ..
119 INTEGER I, IN, J, JJ
120 COMPLEX TEMP
121* ..
122* .. Executable Statements ..
123*
124 IF( m.LE.1 )
125 $ RETURN
126*
127 DO 10 i = 1, m
128 k( i ) = -k( i )
129 10 CONTINUE
130*
131 IF( forwrd ) THEN
132*
133* Forward permutation
134*
135 DO 50 i = 1, m
136*
137 IF( k( i ).GT.0 )
138 $ GO TO 40
139*
140 j = i
141 k( j ) = -k( j )
142 in = k( j )
143*
144 20 CONTINUE
145 IF( k( in ).GT.0 )
146 $ GO TO 40
147*
148 DO 30 jj = 1, n
149 temp = x( j, jj )
150 x( j, jj ) = x( in, jj )
151 x( in, jj ) = temp
152 30 CONTINUE
153*
154 k( in ) = -k( in )
155 j = in
156 in = k( in )
157 GO TO 20
158*
159 40 CONTINUE
160*
161 50 CONTINUE
162*
163 ELSE
164*
165* Backward permutation
166*
167 DO 90 i = 1, m
168*
169 IF( k( i ).GT.0 )
170 $ GO TO 80
171*
172 k( i ) = -k( i )
173 j = k( i )
174 60 CONTINUE
175 IF( j.EQ.i )
176 $ GO TO 80
177*
178 DO 70 jj = 1, n
179 temp = x( i, jj )
180 x( i, jj ) = x( j, jj )
181 x( j, jj ) = temp
182 70 CONTINUE
183*
184 k( j ) = -k( j )
185 j = k( j )
186 GO TO 60
187*
188 80 CONTINUE
189*
190 90 CONTINUE
191*
192 END IF
193*
194 RETURN
195*
196* End of CLAPMR
197*
198 END
199
subroutine clapmr(forwrd, m, n, x, ldx, k)
CLAPMR rearranges rows of a matrix as specified by a permutation vector.
Definition clapmr.f:102