LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zggbak.f
Go to the documentation of this file.
1*> \brief \b ZGGBAK
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZGGBAK + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zggbak.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zggbak.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zggbak.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZGGBAK( JOB, SIDE, N, ILO, IHI, LSCALE, RSCALE, M, V,
20* LDV, INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER JOB, SIDE
24* INTEGER IHI, ILO, INFO, LDV, M, N
25* ..
26* .. Array Arguments ..
27* DOUBLE PRECISION LSCALE( * ), RSCALE( * )
28* COMPLEX*16 V( LDV, * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> ZGGBAK forms the right or left eigenvectors of a complex generalized
38*> eigenvalue problem A*x = lambda*B*x, by backward transformation on
39*> the computed eigenvectors of the balanced pair of matrices output by
40*> ZGGBAL.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] JOB
47*> \verbatim
48*> JOB is CHARACTER*1
49*> Specifies the type of backward transformation required:
50*> = 'N': do nothing, return immediately;
51*> = 'P': do backward transformation for permutation only;
52*> = 'S': do backward transformation for scaling only;
53*> = 'B': do backward transformations for both permutation and
54*> scaling.
55*> JOB must be the same as the argument JOB supplied to ZGGBAL.
56*> \endverbatim
57*>
58*> \param[in] SIDE
59*> \verbatim
60*> SIDE is CHARACTER*1
61*> = 'R': V contains right eigenvectors;
62*> = 'L': V contains left eigenvectors.
63*> \endverbatim
64*>
65*> \param[in] N
66*> \verbatim
67*> N is INTEGER
68*> The number of rows of the matrix V. N >= 0.
69*> \endverbatim
70*>
71*> \param[in] ILO
72*> \verbatim
73*> ILO is INTEGER
74*> \endverbatim
75*>
76*> \param[in] IHI
77*> \verbatim
78*> IHI is INTEGER
79*> The integers ILO and IHI determined by ZGGBAL.
80*> 1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
81*> \endverbatim
82*>
83*> \param[in] LSCALE
84*> \verbatim
85*> LSCALE is DOUBLE PRECISION array, dimension (N)
86*> Details of the permutations and/or scaling factors applied
87*> to the left side of A and B, as returned by ZGGBAL.
88*> \endverbatim
89*>
90*> \param[in] RSCALE
91*> \verbatim
92*> RSCALE is DOUBLE PRECISION array, dimension (N)
93*> Details of the permutations and/or scaling factors applied
94*> to the right side of A and B, as returned by ZGGBAL.
95*> \endverbatim
96*>
97*> \param[in] M
98*> \verbatim
99*> M is INTEGER
100*> The number of columns of the matrix V. M >= 0.
101*> \endverbatim
102*>
103*> \param[in,out] V
104*> \verbatim
105*> V is COMPLEX*16 array, dimension (LDV,M)
106*> On entry, the matrix of right or left eigenvectors to be
107*> transformed, as returned by ZTGEVC.
108*> On exit, V is overwritten by the transformed eigenvectors.
109*> \endverbatim
110*>
111*> \param[in] LDV
112*> \verbatim
113*> LDV is INTEGER
114*> The leading dimension of the matrix V. LDV >= max(1,N).
115*> \endverbatim
116*>
117*> \param[out] INFO
118*> \verbatim
119*> INFO is INTEGER
120*> = 0: successful exit.
121*> < 0: if INFO = -i, the i-th argument had an illegal value.
122*> \endverbatim
123*
124* Authors:
125* ========
126*
127*> \author Univ. of Tennessee
128*> \author Univ. of California Berkeley
129*> \author Univ. of Colorado Denver
130*> \author NAG Ltd.
131*
132*> \ingroup ggbak
133*
134*> \par Further Details:
135* =====================
136*>
137*> \verbatim
138*>
139*> See R.C. Ward, Balancing the generalized eigenvalue problem,
140*> SIAM J. Sci. Stat. Comp. 2 (1981), 141-152.
141*> \endverbatim
142*>
143* =====================================================================
144 SUBROUTINE zggbak( JOB, SIDE, N, ILO, IHI, LSCALE, RSCALE, M,
145 $ V,
146 $ LDV, INFO )
147*
148* -- LAPACK computational routine --
149* -- LAPACK is a software package provided by Univ. of Tennessee, --
150* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
151*
152* .. Scalar Arguments ..
153 CHARACTER JOB, SIDE
154 INTEGER IHI, ILO, INFO, LDV, M, N
155* ..
156* .. Array Arguments ..
157 DOUBLE PRECISION LSCALE( * ), RSCALE( * )
158 COMPLEX*16 V( LDV, * )
159* ..
160*
161* =====================================================================
162*
163* .. Local Scalars ..
164 LOGICAL LEFTV, RIGHTV
165 INTEGER I, K
166* ..
167* .. External Functions ..
168 LOGICAL LSAME
169 EXTERNAL LSAME
170* ..
171* .. External Subroutines ..
172 EXTERNAL xerbla, zdscal, zswap
173* ..
174* .. Intrinsic Functions ..
175 INTRINSIC max, int
176* ..
177* .. Executable Statements ..
178*
179* Test the input parameters
180*
181 rightv = lsame( side, 'R' )
182 leftv = lsame( side, 'L' )
183*
184 info = 0
185 IF( .NOT.lsame( job, 'N' ) .AND.
186 $ .NOT.lsame( job, 'P' ) .AND.
187 $ .NOT.lsame( job, 'S' ) .AND.
188 $ .NOT.lsame( job, 'B' ) ) THEN
189 info = -1
190 ELSE IF( .NOT.rightv .AND. .NOT.leftv ) THEN
191 info = -2
192 ELSE IF( n.LT.0 ) THEN
193 info = -3
194 ELSE IF( ilo.LT.1 ) THEN
195 info = -4
196 ELSE IF( n.EQ.0 .AND. ihi.EQ.0 .AND. ilo.NE.1 ) THEN
197 info = -4
198 ELSE IF( n.GT.0 .AND. ( ihi.LT.ilo .OR. ihi.GT.max( 1, n ) ) )
199 $ THEN
200 info = -5
201 ELSE IF( n.EQ.0 .AND. ilo.EQ.1 .AND. ihi.NE.0 ) THEN
202 info = -5
203 ELSE IF( m.LT.0 ) THEN
204 info = -8
205 ELSE IF( ldv.LT.max( 1, n ) ) THEN
206 info = -10
207 END IF
208 IF( info.NE.0 ) THEN
209 CALL xerbla( 'ZGGBAK', -info )
210 RETURN
211 END IF
212*
213* Quick return if possible
214*
215 IF( n.EQ.0 )
216 $ RETURN
217 IF( m.EQ.0 )
218 $ RETURN
219 IF( lsame( job, 'N' ) )
220 $ RETURN
221*
222 IF( ilo.EQ.ihi )
223 $ GO TO 30
224*
225* Backward balance
226*
227 IF( lsame( job, 'S' ) .OR. lsame( job, 'B' ) ) THEN
228*
229* Backward transformation on right eigenvectors
230*
231 IF( rightv ) THEN
232 DO 10 i = ilo, ihi
233 CALL zdscal( m, rscale( i ), v( i, 1 ), ldv )
234 10 CONTINUE
235 END IF
236*
237* Backward transformation on left eigenvectors
238*
239 IF( leftv ) THEN
240 DO 20 i = ilo, ihi
241 CALL zdscal( m, lscale( i ), v( i, 1 ), ldv )
242 20 CONTINUE
243 END IF
244 END IF
245*
246* Backward permutation
247*
248 30 CONTINUE
249 IF( lsame( job, 'P' ) .OR. lsame( job, 'B' ) ) THEN
250*
251* Backward permutation on right eigenvectors
252*
253 IF( rightv ) THEN
254 IF( ilo.EQ.1 )
255 $ GO TO 50
256 DO 40 i = ilo - 1, 1, -1
257 k = int(rscale( i ))
258 IF( k.EQ.i )
259 $ GO TO 40
260 CALL zswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
261 40 CONTINUE
262*
263 50 CONTINUE
264 IF( ihi.EQ.n )
265 $ GO TO 70
266 DO 60 i = ihi + 1, n
267 k = int(rscale( i ))
268 IF( k.EQ.i )
269 $ GO TO 60
270 CALL zswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
271 60 CONTINUE
272 END IF
273*
274* Backward permutation on left eigenvectors
275*
276 70 CONTINUE
277 IF( leftv ) THEN
278 IF( ilo.EQ.1 )
279 $ GO TO 90
280 DO 80 i = ilo - 1, 1, -1
281 k = int(lscale( i ))
282 IF( k.EQ.i )
283 $ GO TO 80
284 CALL zswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
285 80 CONTINUE
286*
287 90 CONTINUE
288 IF( ihi.EQ.n )
289 $ GO TO 110
290 DO 100 i = ihi + 1, n
291 k = int(lscale( i ))
292 IF( k.EQ.i )
293 $ GO TO 100
294 CALL zswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
295 100 CONTINUE
296 END IF
297 END IF
298*
299 110 CONTINUE
300*
301 RETURN
302*
303* End of ZGGBAK
304*
305 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zggbak(job, side, n, ilo, ihi, lscale, rscale, m, v, ldv, info)
ZGGBAK
Definition zggbak.f:147
subroutine zdscal(n, da, zx, incx)
ZDSCAL
Definition zdscal.f:78
subroutine zswap(n, zx, incx, zy, incy)
ZSWAP
Definition zswap.f:81