LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zgesc2.f
Go to the documentation of this file.
1 *> \brief \b ZGESC2 solves a system of linear equations using the LU factorization with complete pivoting computed by sgetc2.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZGESC2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgesc2.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgesc2.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgesc2.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZGESC2( N, A, LDA, RHS, IPIV, JPIV, SCALE )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER LDA, N
25 * DOUBLE PRECISION SCALE
26 * ..
27 * .. Array Arguments ..
28 * INTEGER IPIV( * ), JPIV( * )
29 * COMPLEX*16 A( LDA, * ), RHS( * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> ZGESC2 solves a system of linear equations
39 *>
40 *> A * X = scale* RHS
41 *>
42 *> with a general N-by-N matrix A using the LU factorization with
43 *> complete pivoting computed by ZGETC2.
44 *>
45 *> \endverbatim
46 *
47 * Arguments:
48 * ==========
49 *
50 *> \param[in] N
51 *> \verbatim
52 *> N is INTEGER
53 *> The number of columns of the matrix A.
54 *> \endverbatim
55 *>
56 *> \param[in] A
57 *> \verbatim
58 *> A is COMPLEX*16 array, dimension (LDA, N)
59 *> On entry, the LU part of the factorization of the n-by-n
60 *> matrix A computed by ZGETC2: A = P * L * U * Q
61 *> \endverbatim
62 *>
63 *> \param[in] LDA
64 *> \verbatim
65 *> LDA is INTEGER
66 *> The leading dimension of the array A. LDA >= max(1, N).
67 *> \endverbatim
68 *>
69 *> \param[in,out] RHS
70 *> \verbatim
71 *> RHS is COMPLEX*16 array, dimension N.
72 *> On entry, the right hand side vector b.
73 *> On exit, the solution vector X.
74 *> \endverbatim
75 *>
76 *> \param[in] IPIV
77 *> \verbatim
78 *> IPIV is INTEGER array, dimension (N).
79 *> The pivot indices; for 1 <= i <= N, row i of the
80 *> matrix has been interchanged with row IPIV(i).
81 *> \endverbatim
82 *>
83 *> \param[in] JPIV
84 *> \verbatim
85 *> JPIV is INTEGER array, dimension (N).
86 *> The pivot indices; for 1 <= j <= N, column j of the
87 *> matrix has been interchanged with column JPIV(j).
88 *> \endverbatim
89 *>
90 *> \param[out] SCALE
91 *> \verbatim
92 *> SCALE is DOUBLE PRECISION
93 *> On exit, SCALE contains the scale factor. SCALE is chosen
94 *> 0 <= SCALE <= 1 to prevent owerflow in the solution.
95 *> \endverbatim
96 *
97 * Authors:
98 * ========
99 *
100 *> \author Univ. of Tennessee
101 *> \author Univ. of California Berkeley
102 *> \author Univ. of Colorado Denver
103 *> \author NAG Ltd.
104 *
105 *> \date September 2012
106 *
107 *> \ingroup complex16GEauxiliary
108 *
109 *> \par Contributors:
110 * ==================
111 *>
112 *> Bo Kagstrom and Peter Poromaa, Department of Computing Science,
113 *> Umea University, S-901 87 Umea, Sweden.
114 *
115 * =====================================================================
116  SUBROUTINE zgesc2( N, A, LDA, RHS, IPIV, JPIV, SCALE )
117 *
118 * -- LAPACK auxiliary routine (version 3.4.2) --
119 * -- LAPACK is a software package provided by Univ. of Tennessee, --
120 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
121 * September 2012
122 *
123 * .. Scalar Arguments ..
124  INTEGER lda, n
125  DOUBLE PRECISION scale
126 * ..
127 * .. Array Arguments ..
128  INTEGER ipiv( * ), jpiv( * )
129  COMPLEX*16 a( lda, * ), rhs( * )
130 * ..
131 *
132 * =====================================================================
133 *
134 * .. Parameters ..
135  DOUBLE PRECISION zero, one, two
136  parameter( zero = 0.0d+0, one = 1.0d+0, two = 2.0d+0 )
137 * ..
138 * .. Local Scalars ..
139  INTEGER i, j
140  DOUBLE PRECISION bignum, eps, smlnum
141  COMPLEX*16 temp
142 * ..
143 * .. External Subroutines ..
144  EXTERNAL zlaswp, zscal
145 * ..
146 * .. External Functions ..
147  INTEGER izamax
148  DOUBLE PRECISION dlamch
149  EXTERNAL izamax, dlamch
150 * ..
151 * .. Intrinsic Functions ..
152  INTRINSIC abs, dble, dcmplx
153 * ..
154 * .. Executable Statements ..
155 *
156 * Set constant to control overflow
157 *
158  eps = dlamch( 'P' )
159  smlnum = dlamch( 'S' ) / eps
160  bignum = one / smlnum
161  CALL dlabad( smlnum, bignum )
162 *
163 * Apply permutations IPIV to RHS
164 *
165  CALL zlaswp( 1, rhs, lda, 1, n-1, ipiv, 1 )
166 *
167 * Solve for L part
168 *
169  DO 20 i = 1, n - 1
170  DO 10 j = i + 1, n
171  rhs( j ) = rhs( j ) - a( j, i )*rhs( i )
172  10 continue
173  20 continue
174 *
175 * Solve for U part
176 *
177  scale = one
178 *
179 * Check for scaling
180 *
181  i = izamax( n, rhs, 1 )
182  IF( two*smlnum*abs( rhs( i ) ).GT.abs( a( n, n ) ) ) THEN
183  temp = dcmplx( one / two, zero ) / abs( rhs( i ) )
184  CALL zscal( n, temp, rhs( 1 ), 1 )
185  scale = scale*dble( temp )
186  END IF
187  DO 40 i = n, 1, -1
188  temp = dcmplx( one, zero ) / a( i, i )
189  rhs( i ) = rhs( i )*temp
190  DO 30 j = i + 1, n
191  rhs( i ) = rhs( i ) - rhs( j )*( a( i, j )*temp )
192  30 continue
193  40 continue
194 *
195 * Apply permutations JPIV to the solution (RHS)
196 *
197  CALL zlaswp( 1, rhs, lda, 1, n-1, jpiv, -1 )
198  return
199 *
200 * End of ZGESC2
201 *
202  END