Integrating Doxygen in comments
[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 *  Definition
9 *  ==========
10 *
11 *       SUBROUTINE ZGEBAK( JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
12 *                          INFO )
13
14 *       .. Scalar Arguments ..
15 *       CHARACTER          JOB, SIDE
16 *       INTEGER            IHI, ILO, INFO, LDV, M, N
17 *       ..
18 *       .. Array Arguments ..
19 *       DOUBLE PRECISION   SCALE( * )
20 *       COMPLEX*16         V( LDV, * )
21 *       ..
22 *  
23 *  Purpose
24 *  =======
25 *
26 *>\details \b Purpose:
27 *>\verbatim
28 *>
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.
32 *>
33 *>\endverbatim
34 *
35 *  Arguments
36 *  =========
37 *
38 *> \param[in] JOB
39 *> \verbatim
40 *>          JOB is CHARACTER*1
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
46 *>                 scaling.
47 *>          JOB must be the same as the argument JOB supplied to ZGEBAL.
48 *> \endverbatim
49 *>
50 *> \param[in] SIDE
51 *> \verbatim
52 *>          SIDE is CHARACTER*1
53 *>          = 'R':  V contains right eigenvectors;
54 *>          = 'L':  V contains left eigenvectors.
55 *> \endverbatim
56 *>
57 *> \param[in] N
58 *> \verbatim
59 *>          N is INTEGER
60 *>          The number of rows of the matrix V.  N >= 0.
61 *> \endverbatim
62 *>
63 *> \param[in] ILO
64 *> \verbatim
65 *>          ILO is INTEGER
66 *> \endverbatim
67 *>
68 *> \param[in] IHI
69 *> \verbatim
70 *>          IHI is INTEGER
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.
73 *> \endverbatim
74 *>
75 *> \param[in] SCALE
76 *> \verbatim
77 *>          SCALE is DOUBLE PRECISION array, dimension (N)
78 *>          Details of the permutation and scaling factors, as returned
79 *>          by ZGEBAL.
80 *> \endverbatim
81 *>
82 *> \param[in] M
83 *> \verbatim
84 *>          M is INTEGER
85 *>          The number of columns of the matrix V.  M >= 0.
86 *> \endverbatim
87 *>
88 *> \param[in,out] V
89 *> \verbatim
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.
94 *> \endverbatim
95 *>
96 *> \param[in] LDV
97 *> \verbatim
98 *>          LDV is INTEGER
99 *>          The leading dimension of the array V. LDV >= max(1,N).
100 *> \endverbatim
101 *>
102 *> \param[out] INFO
103 *> \verbatim
104 *>          INFO is INTEGER
105 *>          = 0:  successful exit
106 *>          < 0:  if INFO = -i, the i-th argument had an illegal value.
107 *> \endverbatim
108 *>
109 *
110 *  Authors
111 *  =======
112 *
113 *> \author Univ. of Tennessee 
114 *> \author Univ. of California Berkeley 
115 *> \author Univ. of Colorado Denver 
116 *> \author NAG Ltd. 
117 *
118 *> \date November 2011
119 *
120 *> \ingroup complex16GEcomputational
121 *
122 *  =====================================================================
123       SUBROUTINE ZGEBAK( JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
124      $                   INFO )
125 *
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..--
129 *     November 2011
130 *
131 *     .. Scalar Arguments ..
132       CHARACTER          JOB, SIDE
133       INTEGER            IHI, ILO, INFO, LDV, M, N
134 *     ..
135 *     .. Array Arguments ..
136       DOUBLE PRECISION   SCALE( * )
137       COMPLEX*16         V( LDV, * )
138 *     ..
139 *
140 *  =====================================================================
141 *
142 *     .. Parameters ..
143       DOUBLE PRECISION   ONE
144       PARAMETER          ( ONE = 1.0D+0 )
145 *     ..
146 *     .. Local Scalars ..
147       LOGICAL            LEFTV, RIGHTV
148       INTEGER            I, II, K
149       DOUBLE PRECISION   S
150 *     ..
151 *     .. External Functions ..
152       LOGICAL            LSAME
153       EXTERNAL           LSAME
154 *     ..
155 *     .. External Subroutines ..
156       EXTERNAL           XERBLA, ZDSCAL, ZSWAP
157 *     ..
158 *     .. Intrinsic Functions ..
159       INTRINSIC          MAX, MIN
160 *     ..
161 *     .. Executable Statements ..
162 *
163 *     Decode and Test the input parameters
164 *
165       RIGHTV = LSAME( SIDE, 'R' )
166       LEFTV = LSAME( SIDE, 'L' )
167 *
168       INFO = 0
169       IF( .NOT.LSAME( JOB, 'N' ) .AND. .NOT.LSAME( JOB, 'P' ) .AND.
170      $    .NOT.LSAME( JOB, 'S' ) .AND. .NOT.LSAME( JOB, 'B' ) ) THEN
171          INFO = -1
172       ELSE IF( .NOT.RIGHTV .AND. .NOT.LEFTV ) THEN
173          INFO = -2
174       ELSE IF( N.LT.0 ) THEN
175          INFO = -3
176       ELSE IF( ILO.LT.1 .OR. ILO.GT.MAX( 1, N ) ) THEN
177          INFO = -4
178       ELSE IF( IHI.LT.MIN( ILO, N ) .OR. IHI.GT.N ) THEN
179          INFO = -5
180       ELSE IF( M.LT.0 ) THEN
181          INFO = -7
182       ELSE IF( LDV.LT.MAX( 1, N ) ) THEN
183          INFO = -9
184       END IF
185       IF( INFO.NE.0 ) THEN
186          CALL XERBLA( 'ZGEBAK', -INFO )
187          RETURN
188       END IF
189 *
190 *     Quick return if possible
191 *
192       IF( N.EQ.0 )
193      $   RETURN
194       IF( M.EQ.0 )
195      $   RETURN
196       IF( LSAME( JOB, 'N' ) )
197      $   RETURN
198 *
199       IF( ILO.EQ.IHI )
200      $   GO TO 30
201 *
202 *     Backward balance
203 *
204       IF( LSAME( JOB, 'S' ) .OR. LSAME( JOB, 'B' ) ) THEN
205 *
206          IF( RIGHTV ) THEN
207             DO 10 I = ILO, IHI
208                S = SCALE( I )
209                CALL ZDSCAL( M, S, V( I, 1 ), LDV )
210    10       CONTINUE
211          END IF
212 *
213          IF( LEFTV ) THEN
214             DO 20 I = ILO, IHI
215                S = ONE / SCALE( I )
216                CALL ZDSCAL( M, S, V( I, 1 ), LDV )
217    20       CONTINUE
218          END IF
219 *
220       END IF
221 *
222 *     Backward permutation
223 *
224 *     For  I = ILO-1 step -1 until 1,
225 *              IHI+1 step 1 until N do --
226 *
227    30 CONTINUE
228       IF( LSAME( JOB, 'P' ) .OR. LSAME( JOB, 'B' ) ) THEN
229          IF( RIGHTV ) THEN
230             DO 40 II = 1, N
231                I = II
232                IF( I.GE.ILO .AND. I.LE.IHI )
233      $            GO TO 40
234                IF( I.LT.ILO )
235      $            I = ILO - II
236                K = SCALE( I )
237                IF( K.EQ.I )
238      $            GO TO 40
239                CALL ZSWAP( M, V( I, 1 ), LDV, V( K, 1 ), LDV )
240    40       CONTINUE
241          END IF
242 *
243          IF( LEFTV ) THEN
244             DO 50 II = 1, N
245                I = II
246                IF( I.GE.ILO .AND. I.LE.IHI )
247      $            GO TO 50
248                IF( I.LT.ILO )
249      $            I = ILO - II
250                K = SCALE( I )
251                IF( K.EQ.I )
252      $            GO TO 50
253                CALL ZSWAP( M, V( I, 1 ), LDV, V( K, 1 ), LDV )
254    50       CONTINUE
255          END IF
256       END IF
257 *
258       RETURN
259 *
260 *     End of ZGEBAK
261 *
262       END