3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
11 * SUBROUTINE ZGEBAK( JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
14 * .. Scalar Arguments ..
16 * INTEGER IHI, ILO, INFO, LDV, M, N
18 * .. Array Arguments ..
19 * DOUBLE PRECISION SCALE( * )
20 * COMPLEX*16 V( LDV, * )
26 *>\details \b Purpose:
29 *> ZGEBAK forms the right or left eigenvectors of a complex general
30 *> matrix by backward transformation on the computed eigenvectors of the
31 *> balanced matrix output by ZGEBAL.
41 *> Specifies the type of backward transformation required:
42 *> = 'N', do nothing, return immediately;
43 *> = 'P', do backward transformation for permutation only;
44 *> = 'S', do backward transformation for scaling only;
45 *> = 'B', do backward transformations for both permutation and
47 *> JOB must be the same as the argument JOB supplied to ZGEBAL.
52 *> SIDE is CHARACTER*1
53 *> = 'R': V contains right eigenvectors;
54 *> = 'L': V contains left eigenvectors.
60 *> The number of rows of the matrix V. N >= 0.
71 *> The integers ILO and IHI determined by ZGEBAL.
72 *> 1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
77 *> SCALE is DOUBLE PRECISION array, dimension (N)
78 *> Details of the permutation and scaling factors, as returned
85 *> The number of columns of the matrix V. M >= 0.
90 *> V is COMPLEX*16 array, dimension (LDV,M)
91 *> On entry, the matrix of right or left eigenvectors to be
92 *> transformed, as returned by ZHSEIN or ZTREVC.
93 *> On exit, V is overwritten by the transformed eigenvectors.
99 *> The leading dimension of the array V. LDV >= max(1,N).
105 *> = 0: successful exit
106 *> < 0: if INFO = -i, the i-th argument had an illegal value.
113 *> \author Univ. of Tennessee
114 *> \author Univ. of California Berkeley
115 *> \author Univ. of Colorado Denver
118 *> \date November 2011
120 *> \ingroup complex16GEcomputational
122 * =====================================================================
123 SUBROUTINE ZGEBAK( JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
126 * -- LAPACK computational routine (version 3.2) --
127 * -- LAPACK is a software package provided by Univ. of Tennessee, --
128 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131 * .. Scalar Arguments ..
133 INTEGER IHI, ILO, INFO, LDV, M, N
135 * .. Array Arguments ..
136 DOUBLE PRECISION SCALE( * )
137 COMPLEX*16 V( LDV, * )
140 * =====================================================================
144 PARAMETER ( ONE = 1.0D+0 )
146 * .. Local Scalars ..
147 LOGICAL LEFTV, RIGHTV
151 * .. External Functions ..
155 * .. External Subroutines ..
156 EXTERNAL XERBLA, ZDSCAL, ZSWAP
158 * .. Intrinsic Functions ..
161 * .. Executable Statements ..
163 * Decode and Test the input parameters
165 RIGHTV = LSAME( SIDE, 'R' )
166 LEFTV = LSAME( SIDE, 'L' )
169 IF( .NOT.LSAME( JOB, 'N' ) .AND. .NOT.LSAME( JOB, 'P' ) .AND.
170 $ .NOT.LSAME( JOB, 'S' ) .AND. .NOT.LSAME( JOB, 'B' ) ) THEN
172 ELSE IF( .NOT.RIGHTV .AND. .NOT.LEFTV ) THEN
174 ELSE IF( N.LT.0 ) THEN
176 ELSE IF( ILO.LT.1 .OR. ILO.GT.MAX( 1, N ) ) THEN
178 ELSE IF( IHI.LT.MIN( ILO, N ) .OR. IHI.GT.N ) THEN
180 ELSE IF( M.LT.0 ) THEN
182 ELSE IF( LDV.LT.MAX( 1, N ) ) THEN
186 CALL XERBLA( 'ZGEBAK', -INFO )
190 * Quick return if possible
196 IF( LSAME( JOB, 'N' ) )
204 IF( LSAME( JOB, 'S' ) .OR. LSAME( JOB, 'B' ) ) THEN
209 CALL ZDSCAL( M, S, V( I, 1 ), LDV )
216 CALL ZDSCAL( M, S, V( I, 1 ), LDV )
222 * Backward permutation
224 * For I = ILO-1 step -1 until 1,
225 * IHI+1 step 1 until N do --
228 IF( LSAME( JOB, 'P' ) .OR. LSAME( JOB, 'B' ) ) THEN
232 IF( I.GE.ILO .AND. I.LE.IHI )
239 CALL ZSWAP( M, V( I, 1 ), LDV, V( K, 1 ), LDV )
246 IF( I.GE.ILO .AND. I.LE.IHI )
253 CALL ZSWAP( M, V( I, 1 ), LDV, V( K, 1 ), LDV )