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