LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dgebak.f
Go to the documentation of this file.
1 *> \brief \b DGEBAK
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DGEBAK + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgebak.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgebak.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgebak.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DGEBAK( 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( * ), V( LDV, * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> DGEBAK forms the right or left eigenvectors of a real general matrix
39 *> by backward transformation on the computed eigenvectors of the
40 *> balanced matrix output by DGEBAL.
41 *> \endverbatim
42 *
43 * Arguments:
44 * ==========
45 *
46 *> \param[in] JOB
47 *> \verbatim
48 *> JOB is CHARACTER*1
49 *> Specifies the type of backward transformation required:
50 *> = 'N', do nothing, return immediately;
51 *> = 'P', do backward transformation for permutation only;
52 *> = 'S', do backward transformation for scaling only;
53 *> = 'B', do backward transformations for both permutation and
54 *> scaling.
55 *> JOB must be the same as the argument JOB supplied to DGEBAL.
56 *> \endverbatim
57 *>
58 *> \param[in] SIDE
59 *> \verbatim
60 *> SIDE is CHARACTER*1
61 *> = 'R': V contains right eigenvectors;
62 *> = 'L': V contains left eigenvectors.
63 *> \endverbatim
64 *>
65 *> \param[in] N
66 *> \verbatim
67 *> N is INTEGER
68 *> The number of rows of the matrix V. N >= 0.
69 *> \endverbatim
70 *>
71 *> \param[in] ILO
72 *> \verbatim
73 *> ILO is INTEGER
74 *> \endverbatim
75 *>
76 *> \param[in] IHI
77 *> \verbatim
78 *> IHI is INTEGER
79 *> The integers ILO and IHI determined by DGEBAL.
80 *> 1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
81 *> \endverbatim
82 *>
83 *> \param[in] SCALE
84 *> \verbatim
85 *> SCALE is DOUBLE PRECISION array, dimension (N)
86 *> Details of the permutation and scaling factors, as returned
87 *> by DGEBAL.
88 *> \endverbatim
89 *>
90 *> \param[in] M
91 *> \verbatim
92 *> M is INTEGER
93 *> The number of columns of the matrix V. M >= 0.
94 *> \endverbatim
95 *>
96 *> \param[in,out] V
97 *> \verbatim
98 *> V is DOUBLE PRECISION array, dimension (LDV,M)
99 *> On entry, the matrix of right or left eigenvectors to be
100 *> transformed, as returned by DHSEIN or DTREVC.
101 *> On exit, V is overwritten by the transformed eigenvectors.
102 *> \endverbatim
103 *>
104 *> \param[in] LDV
105 *> \verbatim
106 *> LDV is INTEGER
107 *> The leading dimension of the array V. LDV >= max(1,N).
108 *> \endverbatim
109 *>
110 *> \param[out] INFO
111 *> \verbatim
112 *> INFO is INTEGER
113 *> = 0: successful exit
114 *> < 0: if INFO = -i, the i-th argument had an illegal value.
115 *> \endverbatim
116 *
117 * Authors:
118 * ========
119 *
120 *> \author Univ. of Tennessee
121 *> \author Univ. of California Berkeley
122 *> \author Univ. of Colorado Denver
123 *> \author NAG Ltd.
124 *
125 *> \date November 2011
126 *
127 *> \ingroup doubleGEcomputational
128 *
129 * =====================================================================
130  SUBROUTINE dgebak( JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
131  $ info )
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 *
268  END