STYLE: Remove trailing whitespace in Fortran files
[platform/upstream/lapack.git] / SRC / zgebak.f
1 *> \brief \b ZGEBAK
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZGEBAK + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgebak.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgebak.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgebak.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE ZGEBAK( JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
22 *                          INFO )
23 *
24 *       .. Scalar Arguments ..
25 *       CHARACTER          JOB, SIDE
26 *       INTEGER            IHI, ILO, INFO, LDV, M, N
27 *       ..
28 *       .. Array Arguments ..
29 *       DOUBLE PRECISION   SCALE( * )
30 *       COMPLEX*16         V( LDV, * )
31 *       ..
32 *
33 *
34 *> \par Purpose:
35 *  =============
36 *>
37 *> \verbatim
38 *>
39 *> ZGEBAK forms the right or left eigenvectors of a complex general
40 *> matrix by backward transformation on the computed eigenvectors of the
41 *> balanced matrix output by ZGEBAL.
42 *> \endverbatim
43 *
44 *  Arguments:
45 *  ==========
46 *
47 *> \param[in] JOB
48 *> \verbatim
49 *>          JOB is CHARACTER*1
50 *>          Specifies the type of backward transformation required:
51 *>          = 'N', do nothing, return immediately;
52 *>          = 'P', do backward transformation for permutation only;
53 *>          = 'S', do backward transformation for scaling only;
54 *>          = 'B', do backward transformations for both permutation and
55 *>                 scaling.
56 *>          JOB must be the same as the argument JOB supplied to ZGEBAL.
57 *> \endverbatim
58 *>
59 *> \param[in] SIDE
60 *> \verbatim
61 *>          SIDE is CHARACTER*1
62 *>          = 'R':  V contains right eigenvectors;
63 *>          = 'L':  V contains left eigenvectors.
64 *> \endverbatim
65 *>
66 *> \param[in] N
67 *> \verbatim
68 *>          N is INTEGER
69 *>          The number of rows of the matrix V.  N >= 0.
70 *> \endverbatim
71 *>
72 *> \param[in] ILO
73 *> \verbatim
74 *>          ILO is INTEGER
75 *> \endverbatim
76 *>
77 *> \param[in] IHI
78 *> \verbatim
79 *>          IHI is INTEGER
80 *>          The integers ILO and IHI determined by ZGEBAL.
81 *>          1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
82 *> \endverbatim
83 *>
84 *> \param[in] SCALE
85 *> \verbatim
86 *>          SCALE is DOUBLE PRECISION array, dimension (N)
87 *>          Details of the permutation and scaling factors, as returned
88 *>          by ZGEBAL.
89 *> \endverbatim
90 *>
91 *> \param[in] M
92 *> \verbatim
93 *>          M is INTEGER
94 *>          The number of columns of the matrix V.  M >= 0.
95 *> \endverbatim
96 *>
97 *> \param[in,out] V
98 *> \verbatim
99 *>          V is COMPLEX*16 array, dimension (LDV,M)
100 *>          On entry, the matrix of right or left eigenvectors to be
101 *>          transformed, as returned by ZHSEIN or ZTREVC.
102 *>          On exit, V is overwritten by the transformed eigenvectors.
103 *> \endverbatim
104 *>
105 *> \param[in] LDV
106 *> \verbatim
107 *>          LDV is INTEGER
108 *>          The leading dimension of the array V. LDV >= max(1,N).
109 *> \endverbatim
110 *>
111 *> \param[out] INFO
112 *> \verbatim
113 *>          INFO is INTEGER
114 *>          = 0:  successful exit
115 *>          < 0:  if INFO = -i, the i-th argument had an illegal value.
116 *> \endverbatim
117 *
118 *  Authors:
119 *  ========
120 *
121 *> \author Univ. of Tennessee
122 *> \author Univ. of California Berkeley
123 *> \author Univ. of Colorado Denver
124 *> \author NAG Ltd.
125 *
126 *> \date November 2011
127 *
128 *> \ingroup complex16GEcomputational
129 *
130 *  =====================================================================
131       SUBROUTINE ZGEBAK( JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
132      $                   INFO )
133 *
134 *  -- LAPACK computational routine (version 3.4.0) --
135 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
136 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
137 *     November 2011
138 *
139 *     .. Scalar Arguments ..
140       CHARACTER          JOB, SIDE
141       INTEGER            IHI, ILO, INFO, LDV, M, N
142 *     ..
143 *     .. Array Arguments ..
144       DOUBLE PRECISION   SCALE( * )
145       COMPLEX*16         V( LDV, * )
146 *     ..
147 *
148 *  =====================================================================
149 *
150 *     .. Parameters ..
151       DOUBLE PRECISION   ONE
152       PARAMETER          ( ONE = 1.0D+0 )
153 *     ..
154 *     .. Local Scalars ..
155       LOGICAL            LEFTV, RIGHTV
156       INTEGER            I, II, K
157       DOUBLE PRECISION   S
158 *     ..
159 *     .. External Functions ..
160       LOGICAL            LSAME
161       EXTERNAL           LSAME
162 *     ..
163 *     .. External Subroutines ..
164       EXTERNAL           XERBLA, ZDSCAL, ZSWAP
165 *     ..
166 *     .. Intrinsic Functions ..
167       INTRINSIC          MAX, MIN
168 *     ..
169 *     .. Executable Statements ..
170 *
171 *     Decode and Test the input parameters
172 *
173       RIGHTV = LSAME( SIDE, 'R' )
174       LEFTV = LSAME( SIDE, 'L' )
175 *
176       INFO = 0
177       IF( .NOT.LSAME( JOB, 'N' ) .AND. .NOT.LSAME( JOB, 'P' ) .AND.
178      $    .NOT.LSAME( JOB, 'S' ) .AND. .NOT.LSAME( JOB, 'B' ) ) THEN
179          INFO = -1
180       ELSE IF( .NOT.RIGHTV .AND. .NOT.LEFTV ) THEN
181          INFO = -2
182       ELSE IF( N.LT.0 ) THEN
183          INFO = -3
184       ELSE IF( ILO.LT.1 .OR. ILO.GT.MAX( 1, N ) ) THEN
185          INFO = -4
186       ELSE IF( IHI.LT.MIN( ILO, N ) .OR. IHI.GT.N ) THEN
187          INFO = -5
188       ELSE IF( M.LT.0 ) THEN
189          INFO = -7
190       ELSE IF( LDV.LT.MAX( 1, N ) ) THEN
191          INFO = -9
192       END IF
193       IF( INFO.NE.0 ) THEN
194          CALL XERBLA( 'ZGEBAK', -INFO )
195          RETURN
196       END IF
197 *
198 *     Quick return if possible
199 *
200       IF( N.EQ.0 )
201      $   RETURN
202       IF( M.EQ.0 )
203      $   RETURN
204       IF( LSAME( JOB, 'N' ) )
205      $   RETURN
206 *
207       IF( ILO.EQ.IHI )
208      $   GO TO 30
209 *
210 *     Backward balance
211 *
212       IF( LSAME( JOB, 'S' ) .OR. LSAME( JOB, 'B' ) ) THEN
213 *
214          IF( RIGHTV ) THEN
215             DO 10 I = ILO, IHI
216                S = SCALE( I )
217                CALL ZDSCAL( M, S, V( I, 1 ), LDV )
218    10       CONTINUE
219          END IF
220 *
221          IF( LEFTV ) THEN
222             DO 20 I = ILO, IHI
223                S = ONE / SCALE( I )
224                CALL ZDSCAL( M, S, V( I, 1 ), LDV )
225    20       CONTINUE
226          END IF
227 *
228       END IF
229 *
230 *     Backward permutation
231 *
232 *     For  I = ILO-1 step -1 until 1,
233 *              IHI+1 step 1 until N do --
234 *
235    30 CONTINUE
236       IF( LSAME( JOB, 'P' ) .OR. LSAME( JOB, 'B' ) ) THEN
237          IF( RIGHTV ) THEN
238             DO 40 II = 1, N
239                I = II
240                IF( I.GE.ILO .AND. I.LE.IHI )
241      $            GO TO 40
242                IF( I.LT.ILO )
243      $            I = ILO - II
244                K = SCALE( I )
245                IF( K.EQ.I )
246      $            GO TO 40
247                CALL ZSWAP( M, V( I, 1 ), LDV, V( K, 1 ), LDV )
248    40       CONTINUE
249          END IF
250 *
251          IF( LEFTV ) THEN
252             DO 50 II = 1, N
253                I = II
254                IF( I.GE.ILO .AND. I.LE.IHI )
255      $            GO TO 50
256                IF( I.LT.ILO )
257      $            I = ILO - II
258                K = SCALE( I )
259                IF( K.EQ.I )
260      $            GO TO 50
261                CALL ZSWAP( M, V( I, 1 ), LDV, V( K, 1 ), LDV )
262    50       CONTINUE
263          END IF
264       END IF
265 *
266       RETURN
267 *
268 *     End of ZGEBAK
269 *
270       END