LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dgebak ( character  JOB,
character  SIDE,
integer  N,
integer  ILO,
integer  IHI,
double precision, dimension( * )  SCALE,
integer  M,
double precision, dimension( ldv, * )  V,
integer  LDV,
integer  INFO 
)

DGEBAK

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

Purpose:
 DGEBAK forms the right or left eigenvectors of a real general matrix
 by backward transformation on the computed eigenvectors of the
 balanced matrix output by DGEBAL.
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 DGEBAL.
[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 DGEBAL.
          1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
[in]SCALE
          SCALE is DOUBLE PRECISION array, dimension (N)
          Details of the permutation and scaling factors, as returned
          by DGEBAL.
[in]M
          M is INTEGER
          The number of columns of the matrix V.  M >= 0.
[in,out]V
          V is DOUBLE PRECISION array, dimension (LDV,M)
          On entry, the matrix of right or left eigenvectors to be
          transformed, as returned by DHSEIN or DTREVC.
          On exit, V is overwritten by the transformed eigenvectors.
[in]LDV
          LDV is INTEGER
          The leading dimension of the array 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

Definition at line 132 of file dgebak.f.

132 *
133 * -- LAPACK computational routine (version 3.4.0) --
134 * -- LAPACK is a software package provided by Univ. of Tennessee, --
135 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
136 * November 2011
137 *
138 * .. Scalar Arguments ..
139  CHARACTER job, side
140  INTEGER ihi, ilo, info, ldv, m, n
141 * ..
142 * .. Array Arguments ..
143  DOUBLE PRECISION scale( * ), v( ldv, * )
144 * ..
145 *
146 * =====================================================================
147 *
148 * .. Parameters ..
149  DOUBLE PRECISION one
150  parameter ( one = 1.0d+0 )
151 * ..
152 * .. Local Scalars ..
153  LOGICAL leftv, rightv
154  INTEGER i, ii, k
155  DOUBLE PRECISION s
156 * ..
157 * .. External Functions ..
158  LOGICAL lsame
159  EXTERNAL lsame
160 * ..
161 * .. External Subroutines ..
162  EXTERNAL dscal, dswap, xerbla
163 * ..
164 * .. Intrinsic Functions ..
165  INTRINSIC max, min
166 * ..
167 * .. Executable Statements ..
168 *
169 * Decode and Test the input parameters
170 *
171  rightv = lsame( side, 'R' )
172  leftv = lsame( side, 'L' )
173 *
174  info = 0
175  IF( .NOT.lsame( job, 'N' ) .AND. .NOT.lsame( job, 'P' ) .AND.
176  $ .NOT.lsame( job, 'S' ) .AND. .NOT.lsame( job, 'B' ) ) THEN
177  info = -1
178  ELSE IF( .NOT.rightv .AND. .NOT.leftv ) THEN
179  info = -2
180  ELSE IF( n.LT.0 ) THEN
181  info = -3
182  ELSE IF( ilo.LT.1 .OR. ilo.GT.max( 1, n ) ) THEN
183  info = -4
184  ELSE IF( ihi.LT.min( ilo, n ) .OR. ihi.GT.n ) THEN
185  info = -5
186  ELSE IF( m.LT.0 ) THEN
187  info = -7
188  ELSE IF( ldv.LT.max( 1, n ) ) THEN
189  info = -9
190  END IF
191  IF( info.NE.0 ) THEN
192  CALL xerbla( 'DGEBAK', -info )
193  RETURN
194  END IF
195 *
196 * Quick return if possible
197 *
198  IF( n.EQ.0 )
199  $ RETURN
200  IF( m.EQ.0 )
201  $ RETURN
202  IF( lsame( job, 'N' ) )
203  $ RETURN
204 *
205  IF( ilo.EQ.ihi )
206  $ GO TO 30
207 *
208 * Backward balance
209 *
210  IF( lsame( job, 'S' ) .OR. lsame( job, 'B' ) ) THEN
211 *
212  IF( rightv ) THEN
213  DO 10 i = ilo, ihi
214  s = scale( i )
215  CALL dscal( m, s, v( i, 1 ), ldv )
216  10 CONTINUE
217  END IF
218 *
219  IF( leftv ) THEN
220  DO 20 i = ilo, ihi
221  s = one / scale( i )
222  CALL dscal( m, s, v( i, 1 ), ldv )
223  20 CONTINUE
224  END IF
225 *
226  END IF
227 *
228 * Backward permutation
229 *
230 * For I = ILO-1 step -1 until 1,
231 * IHI+1 step 1 until N do --
232 *
233  30 CONTINUE
234  IF( lsame( job, 'P' ) .OR. lsame( job, 'B' ) ) THEN
235  IF( rightv ) THEN
236  DO 40 ii = 1, n
237  i = ii
238  IF( i.GE.ilo .AND. i.LE.ihi )
239  $ GO TO 40
240  IF( i.LT.ilo )
241  $ i = ilo - ii
242  k = scale( i )
243  IF( k.EQ.i )
244  $ GO TO 40
245  CALL dswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
246  40 CONTINUE
247  END IF
248 *
249  IF( leftv ) THEN
250  DO 50 ii = 1, n
251  i = ii
252  IF( i.GE.ilo .AND. i.LE.ihi )
253  $ GO TO 50
254  IF( i.LT.ilo )
255  $ i = ilo - ii
256  k = scale( i )
257  IF( k.EQ.i )
258  $ GO TO 50
259  CALL dswap( m, v( i, 1 ), ldv, v( k, 1 ), ldv )
260  50 CONTINUE
261  END IF
262  END IF
263 *
264  RETURN
265 *
266 * End of DGEBAK
267 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine dswap(N, DX, INCX, DY, INCY)
DSWAP
Definition: dswap.f:53
subroutine dscal(N, DA, DX, INCX)
DSCAL
Definition: dscal.f:55
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: