LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ cggbak()

subroutine cggbak ( character  job,
character  side,
integer  n,
integer  ilo,
integer  ihi,
real, dimension( * )  lscale,
real, dimension( * )  rscale,
integer  m,
complex, dimension( ldv, * )  v,
integer  ldv,
integer  info 
)

CGGBAK

Download CGGBAK + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 CGGBAK forms the right or left eigenvectors of a complex generalized
 eigenvalue problem A*x = lambda*B*x, by backward transformation on
 the computed eigenvectors of the balanced pair of matrices output by
 CGGBAL.
Parameters
[in]JOB
          JOB is CHARACTER*1
          Specifies the type of backward transformation required:
          = 'N':  do nothing, return immediately;
          = 'P':  do backward transformation for permutation only;
          = 'S':  do backward transformation for scaling only;
          = 'B':  do backward transformations for both permutation and
                  scaling.
          JOB must be the same as the argument JOB supplied to CGGBAL.
[in]SIDE
          SIDE is CHARACTER*1
          = 'R':  V contains right eigenvectors;
          = 'L':  V contains left eigenvectors.
[in]N
          N is INTEGER
          The number of rows of the matrix V.  N >= 0.
[in]ILO
          ILO is INTEGER
[in]IHI
          IHI is INTEGER
          The integers ILO and IHI determined by CGGBAL.
          1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
[in]LSCALE
          LSCALE is REAL array, dimension (N)
          Details of the permutations and/or scaling factors applied
          to the left side of A and B, as returned by CGGBAL.
[in]RSCALE
          RSCALE is REAL array, dimension (N)
          Details of the permutations and/or scaling factors applied
          to the right side of A and B, as returned by CGGBAL.
[in]M
          M is INTEGER
          The number of columns of the matrix V.  M >= 0.
[in,out]V
          V is COMPLEX array, dimension (LDV,M)
          On entry, the matrix of right or left eigenvectors to be
          transformed, as returned by CTGEVC.
          On exit, V is overwritten by the transformed eigenvectors.
[in]LDV
          LDV is INTEGER
          The leading dimension of the matrix V. LDV >= max(1,N).
[out]INFO
          INFO is INTEGER
          = 0:  successful exit.
          < 0:  if INFO = -i, the i-th argument had an illegal value.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  See R.C. Ward, Balancing the generalized eigenvalue problem,
                 SIAM J. Sci. Stat. Comp. 2 (1981), 141-152.

Definition at line 146 of file cggbak.f.

148*
149* -- LAPACK computational routine --
150* -- LAPACK is a software package provided by Univ. of Tennessee, --
151* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
152*
153* .. Scalar Arguments ..
154 CHARACTER JOB, SIDE
155 INTEGER IHI, ILO, INFO, LDV, M, N
156* ..
157* .. Array Arguments ..
158 REAL LSCALE( * ), RSCALE( * )
159 COMPLEX V( LDV, * )
160* ..
161*
162* =====================================================================
163*
164* .. Local Scalars ..
165 LOGICAL LEFTV, RIGHTV
166 INTEGER I, K
167* ..
168* .. External Functions ..
169 LOGICAL LSAME
170 EXTERNAL lsame
171* ..
172* .. External Subroutines ..
173 EXTERNAL csscal, cswap, xerbla
174* ..
175* .. Intrinsic Functions ..
176 INTRINSIC max
177* ..
178* .. Executable Statements ..
179*
180* Test the input parameters
181*
182 rightv = lsame( side, 'R' )
183 leftv = lsame( side, 'L' )
184*
185 info = 0
186 IF( .NOT.lsame( job, 'N' ) .AND. .NOT.lsame( job, 'P' ) .AND.
187 $ .NOT.lsame( job, 'S' ) .AND. .NOT.lsame( job, 'B' ) ) THEN
188 info = -1
189 ELSE IF( .NOT.rightv .AND. .NOT.leftv ) THEN
190 info = -2
191 ELSE IF( n.LT.0 ) THEN
192 info = -3
193 ELSE IF( ilo.LT.1 ) THEN
194 info = -4
195 ELSE IF( n.EQ.0 .AND. ihi.EQ.0 .AND. ilo.NE.1 ) THEN
196 info = -4
197 ELSE IF( n.GT.0 .AND. ( ihi.LT.ilo .OR. ihi.GT.max( 1, n ) ) )
198 $ THEN
199 info = -5
200 ELSE IF( n.EQ.0 .AND. ilo.EQ.1 .AND. ihi.NE.0 ) THEN
201 info = -5
202 ELSE IF( m.LT.0 ) THEN
203 info = -8
204 ELSE IF( ldv.LT.max( 1, n ) ) THEN
205 info = -10
206 END IF
207 IF( info.NE.0 ) THEN
208 CALL xerbla( 'CGGBAK', -info )
209 RETURN
210 END IF
211*
212* Quick return if possible
213*
214 IF( n.EQ.0 )
215 $ RETURN
216 IF( m.EQ.0 )
217 $ RETURN
218 IF( lsame( job, 'N' ) )
219 $ RETURN
220*
221 IF( ilo.EQ.ihi )
222 $ GO TO 30
223*
224* Backward balance
225*
226 IF( lsame( job, 'S' ) .OR. lsame( job, 'B' ) ) THEN
227*
228* Backward transformation on right eigenvectors
229*
230 IF( rightv ) THEN
231 DO 10 i = ilo, ihi
232 CALL csscal( m, rscale( i ), v( i, 1 ), ldv )
233 10 CONTINUE
234 END IF
235*
236* Backward transformation on left eigenvectors
237*
238 IF( leftv ) THEN
239 DO 20 i = ilo, ihi
240 CALL csscal( m, lscale( i ), v( i, 1 ), ldv )
241 20 CONTINUE
242 END IF
243 END IF
244*
245* Backward permutation
246*
247 30 CONTINUE
248 IF( lsame( job, 'P' ) .OR. lsame( job, 'B' ) ) THEN
249*
250* Backward permutation on right eigenvectors
251*
252 IF( rightv ) THEN
253 IF( ilo.EQ.1 )
254 $ GO TO 50
255 DO 40 i = ilo - 1, 1, -1
256 k = int( rscale( i ) )
257 IF( k.EQ.i )
258 $ GO TO 40
259 CALL cswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
260 40 CONTINUE
261*
262 50 CONTINUE
263 IF( ihi.EQ.n )
264 $ GO TO 70
265 DO 60 i = ihi + 1, n
266 k = int( rscale( i ) )
267 IF( k.EQ.i )
268 $ GO TO 60
269 CALL cswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
270 60 CONTINUE
271 END IF
272*
273* Backward permutation on left eigenvectors
274*
275 70 CONTINUE
276 IF( leftv ) THEN
277 IF( ilo.EQ.1 )
278 $ GO TO 90
279 DO 80 i = ilo - 1, 1, -1
280 k = int( lscale( i ) )
281 IF( k.EQ.i )
282 $ GO TO 80
283 CALL cswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
284 80 CONTINUE
285*
286 90 CONTINUE
287 IF( ihi.EQ.n )
288 $ GO TO 110
289 DO 100 i = ihi + 1, n
290 k = int( lscale( i ) )
291 IF( k.EQ.i )
292 $ GO TO 100
293 CALL cswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
294 100 CONTINUE
295 END IF
296 END IF
297*
298 110 CONTINUE
299*
300 RETURN
301*
302* End of CGGBAK
303*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78
subroutine cswap(n, cx, incx, cy, incy)
CSWAP
Definition cswap.f:81
Here is the call graph for this function:
Here is the caller graph for this function: