LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zgttrf ( integer  N,
complex*16, dimension( * )  DL,
complex*16, dimension( * )  D,
complex*16, dimension( * )  DU,
complex*16, dimension( * )  DU2,
integer, dimension( * )  IPIV,
integer  INFO 
)

ZGTTRF

Download ZGTTRF + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 ZGTTRF computes an LU factorization of a complex tridiagonal matrix A
 using elimination with partial pivoting and row interchanges.

 The factorization has the form
    A = L * U
 where L is a product of permutation and unit lower bidiagonal
 matrices and U is upper triangular with nonzeros in only the main
 diagonal and first two superdiagonals.
Parameters
[in]N
          N is INTEGER
          The order of the matrix A.
[in,out]DL
          DL is COMPLEX*16 array, dimension (N-1)
          On entry, DL must contain the (n-1) sub-diagonal elements of
          A.

          On exit, DL is overwritten by the (n-1) multipliers that
          define the matrix L from the LU factorization of A.
[in,out]D
          D is COMPLEX*16 array, dimension (N)
          On entry, D must contain the diagonal elements of A.

          On exit, D is overwritten by the n diagonal elements of the
          upper triangular matrix U from the LU factorization of A.
[in,out]DU
          DU is COMPLEX*16 array, dimension (N-1)
          On entry, DU must contain the (n-1) super-diagonal elements
          of A.

          On exit, DU is overwritten by the (n-1) elements of the first
          super-diagonal of U.
[out]DU2
          DU2 is COMPLEX*16 array, dimension (N-2)
          On exit, DU2 is overwritten by the (n-2) elements of the
          second super-diagonal of U.
[out]IPIV
          IPIV is INTEGER array, dimension (N)
          The pivot indices; for 1 <= i <= n, row i of the matrix was
          interchanged with row IPIV(i).  IPIV(i) will always be either
          i or i+1; IPIV(i) = i indicates a row interchange was not
          required.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -k, the k-th argument had an illegal value
          > 0:  if INFO = k, U(k,k) is exactly zero. The factorization
                has been completed, but the factor U is exactly
                singular, and division by zero will occur if it is used
                to solve a system of equations.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012

Definition at line 126 of file zgttrf.f.

126 *
127 * -- LAPACK computational routine (version 3.4.2) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130 * September 2012
131 *
132 * .. Scalar Arguments ..
133  INTEGER info, n
134 * ..
135 * .. Array Arguments ..
136  INTEGER ipiv( * )
137  COMPLEX*16 d( * ), dl( * ), du( * ), du2( * )
138 * ..
139 *
140 * =====================================================================
141 *
142 * .. Parameters ..
143  DOUBLE PRECISION zero
144  parameter ( zero = 0.0d+0 )
145 * ..
146 * .. Local Scalars ..
147  INTEGER i
148  COMPLEX*16 fact, temp, zdum
149 * ..
150 * .. External Subroutines ..
151  EXTERNAL xerbla
152 * ..
153 * .. Intrinsic Functions ..
154  INTRINSIC abs, dble, dimag
155 * ..
156 * .. Statement Functions ..
157  DOUBLE PRECISION cabs1
158 * ..
159 * .. Statement Function definitions ..
160  cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
161 * ..
162 * .. Executable Statements ..
163 *
164  info = 0
165  IF( n.LT.0 ) THEN
166  info = -1
167  CALL xerbla( 'ZGTTRF', -info )
168  RETURN
169  END IF
170 *
171 * Quick return if possible
172 *
173  IF( n.EQ.0 )
174  $ RETURN
175 *
176 * Initialize IPIV(i) = i and DU2(i) = 0
177 *
178  DO 10 i = 1, n
179  ipiv( i ) = i
180  10 CONTINUE
181  DO 20 i = 1, n - 2
182  du2( i ) = zero
183  20 CONTINUE
184 *
185  DO 30 i = 1, n - 2
186  IF( cabs1( d( i ) ).GE.cabs1( dl( i ) ) ) THEN
187 *
188 * No row interchange required, eliminate DL(I)
189 *
190  IF( cabs1( d( i ) ).NE.zero ) THEN
191  fact = dl( i ) / d( i )
192  dl( i ) = fact
193  d( i+1 ) = d( i+1 ) - fact*du( i )
194  END IF
195  ELSE
196 *
197 * Interchange rows I and I+1, eliminate DL(I)
198 *
199  fact = d( i ) / dl( i )
200  d( i ) = dl( i )
201  dl( i ) = fact
202  temp = du( i )
203  du( i ) = d( i+1 )
204  d( i+1 ) = temp - fact*d( i+1 )
205  du2( i ) = du( i+1 )
206  du( i+1 ) = -fact*du( i+1 )
207  ipiv( i ) = i + 1
208  END IF
209  30 CONTINUE
210  IF( n.GT.1 ) THEN
211  i = n - 1
212  IF( cabs1( d( i ) ).GE.cabs1( dl( i ) ) ) THEN
213  IF( cabs1( d( i ) ).NE.zero ) THEN
214  fact = dl( i ) / d( i )
215  dl( i ) = fact
216  d( i+1 ) = d( i+1 ) - fact*du( i )
217  END IF
218  ELSE
219  fact = d( i ) / dl( i )
220  d( i ) = dl( i )
221  dl( i ) = fact
222  temp = du( i )
223  du( i ) = d( i+1 )
224  d( i+1 ) = temp - fact*d( i+1 )
225  ipiv( i ) = i + 1
226  END IF
227  END IF
228 *
229 * Check for a zero on the diagonal of U.
230 *
231  DO 40 i = 1, n
232  IF( cabs1( d( i ) ).EQ.zero ) THEN
233  info = i
234  GO TO 50
235  END IF
236  40 CONTINUE
237  50 CONTINUE
238 *
239  RETURN
240 *
241 * End of ZGTTRF
242 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62

Here is the call graph for this function:

Here is the caller graph for this function: