LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine sggbak ( character  JOB,
character  SIDE,
integer  N,
integer  ILO,
integer  IHI,
real, dimension( * )  LSCALE,
real, dimension( * )  RSCALE,
integer  M,
real, dimension( ldv, * )  V,
integer  LDV,
integer  INFO 
)

SGGBAK

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

Purpose:
 SGGBAK forms the right or left eigenvectors of a real generalized
 eigenvalue problem A*x = lambda*B*x, by backward transformation on
 the computed eigenvectors of the balanced pair of matrices output by
 SGGBAL.
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 SGGBAL.
[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 SGGBAL.
          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 SGGBAL.
[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 SGGBAL.
[in]M
          M is INTEGER
          The number of columns of the matrix V.  M >= 0.
[in,out]V
          V is REAL array, dimension (LDV,M)
          On entry, the matrix of right or left eigenvectors to be
          transformed, as returned by STGEVC.
          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.
Date
November 2011
Further Details:
  See R.C. Ward, Balancing the generalized eigenvalue problem,
                 SIAM J. Sci. Stat. Comp. 2 (1981), 141-152.

Definition at line 149 of file sggbak.f.

149 *
150 * -- LAPACK computational routine (version 3.4.0) --
151 * -- LAPACK is a software package provided by Univ. of Tennessee, --
152 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153 * November 2011
154 *
155 * .. Scalar Arguments ..
156  CHARACTER job, side
157  INTEGER ihi, ilo, info, ldv, m, n
158 * ..
159 * .. Array Arguments ..
160  REAL lscale( * ), rscale( * ), v( ldv, * )
161 * ..
162 *
163 * =====================================================================
164 *
165 * .. Local Scalars ..
166  LOGICAL leftv, rightv
167  INTEGER i, k
168 * ..
169 * .. External Functions ..
170  LOGICAL lsame
171  EXTERNAL lsame
172 * ..
173 * .. External Subroutines ..
174  EXTERNAL sscal, sswap, xerbla
175 * ..
176 * .. Intrinsic Functions ..
177  INTRINSIC max
178 * ..
179 * .. Executable Statements ..
180 *
181 * Test the input parameters
182 *
183  rightv = lsame( side, 'R' )
184  leftv = lsame( side, 'L' )
185 *
186  info = 0
187  IF( .NOT.lsame( job, 'N' ) .AND. .NOT.lsame( job, 'P' ) .AND.
188  $ .NOT.lsame( job, 'S' ) .AND. .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( 'SGGBAK', -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 sscal( 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 sscal( 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 *
257  DO 40 i = ilo - 1, 1, -1
258  k = rscale( i )
259  IF( k.EQ.i )
260  $ GO TO 40
261  CALL sswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
262  40 CONTINUE
263 *
264  50 CONTINUE
265  IF( ihi.EQ.n )
266  $ GO TO 70
267  DO 60 i = ihi + 1, n
268  k = rscale( i )
269  IF( k.EQ.i )
270  $ GO TO 60
271  CALL sswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
272  60 CONTINUE
273  END IF
274 *
275 * Backward permutation on left eigenvectors
276 *
277  70 CONTINUE
278  IF( leftv ) THEN
279  IF( ilo.EQ.1 )
280  $ GO TO 90
281  DO 80 i = ilo - 1, 1, -1
282  k = lscale( i )
283  IF( k.EQ.i )
284  $ GO TO 80
285  CALL sswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
286  80 CONTINUE
287 *
288  90 CONTINUE
289  IF( ihi.EQ.n )
290  $ GO TO 110
291  DO 100 i = ihi + 1, n
292  k = lscale( i )
293  IF( k.EQ.i )
294  $ GO TO 100
295  CALL sswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
296  100 CONTINUE
297  END IF
298  END IF
299 *
300  110 CONTINUE
301 *
302  RETURN
303 *
304 * End of SGGBAK
305 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine sscal(N, SA, SX, INCX)
SSCAL
Definition: sscal.f:55
subroutine sswap(N, SX, INCX, SY, INCY)
SSWAP
Definition: sswap.f:53
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: