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

◆ sggbak()

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.
Further Details:
  See R.C. Ward, Balancing the generalized eigenvalue problem,
                 SIAM J. Sci. Stat. Comp. 2 (1981), 141-152.

Definition at line 145 of file sggbak.f.

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