LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zla_porpvgrw()

double precision function zla_porpvgrw ( character*1 uplo,
integer ncols,
complex*16, dimension( lda, * ) a,
integer lda,
complex*16, dimension( ldaf, * ) af,
integer ldaf,
double precision, dimension( * ) work )

ZLA_PORPVGRW computes the reciprocal pivot growth factor norm(A)/norm(U) for a symmetric or Hermitian positive-definite matrix.

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

Purpose:
!>
!>
!> ZLA_PORPVGRW computes the reciprocal pivot growth factor
!> norm(A)/norm(U). The  norm is used. If this is
!> much less than 1, the stability of the LU factorization of the
!> (equilibrated) matrix A could be poor. This also means that the
!> solution X, estimated condition numbers, and error bounds could be
!> unreliable.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>       = 'U':  Upper triangle of A is stored;
!>       = 'L':  Lower triangle of A is stored.
!> 
[in]NCOLS
!>          NCOLS is INTEGER
!>     The number of columns of the matrix A. NCOLS >= 0.
!> 
[in]A
!>          A is COMPLEX*16 array, dimension (LDA,N)
!>     On entry, the N-by-N matrix A.
!> 
[in]LDA
!>          LDA is INTEGER
!>     The leading dimension of the array A.  LDA >= max(1,N).
!> 
[in]AF
!>          AF is COMPLEX*16 array, dimension (LDAF,N)
!>     The triangular factor U or L from the Cholesky factorization
!>     A = U**T*U or A = L*L**T, as computed by ZPOTRF.
!> 
[in]LDAF
!>          LDAF is INTEGER
!>     The leading dimension of the array AF.  LDAF >= max(1,N).
!> 
[out]WORK
!>          WORK is DOUBLE PRECISION array, dimension (2*N)
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 103 of file zla_porpvgrw.f.

106*
107* -- LAPACK computational routine --
108* -- LAPACK is a software package provided by Univ. of Tennessee, --
109* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
110*
111* .. Scalar Arguments ..
112 CHARACTER*1 UPLO
113 INTEGER NCOLS, LDA, LDAF
114* ..
115* .. Array Arguments ..
116 COMPLEX*16 A( LDA, * ), AF( LDAF, * )
117 DOUBLE PRECISION WORK( * )
118* ..
119*
120* =====================================================================
121*
122* .. Local Scalars ..
123 INTEGER I, J
124 DOUBLE PRECISION AMAX, UMAX, RPVGRW
125 LOGICAL UPPER
126 COMPLEX*16 ZDUM
127* ..
128* .. External Functions ..
129 EXTERNAL lsame
130 LOGICAL LSAME
131* ..
132* .. Intrinsic Functions ..
133 INTRINSIC abs, max, min, real, dimag
134* ..
135* .. Statement Functions ..
136 DOUBLE PRECISION CABS1
137* ..
138* .. Statement Function Definitions ..
139 cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
140* ..
141* .. Executable Statements ..
142 upper = lsame( 'Upper', uplo )
143*
144* DPOTRF will have factored only the NCOLSxNCOLS leading submatrix,
145* so we restrict the growth search to that submatrix and use only
146* the first 2*NCOLS workspace entries.
147*
148 rpvgrw = 1.0d+0
149 DO i = 1, 2*ncols
150 work( i ) = 0.0d+0
151 END DO
152*
153* Find the max magnitude entry of each column.
154*
155 IF ( upper ) THEN
156 DO j = 1, ncols
157 DO i = 1, j
158 work( ncols+j ) =
159 $ max( cabs1( a( i, j ) ), work( ncols+j ) )
160 END DO
161 END DO
162 ELSE
163 DO j = 1, ncols
164 DO i = j, ncols
165 work( ncols+j ) =
166 $ max( cabs1( a( i, j ) ), work( ncols+j ) )
167 END DO
168 END DO
169 END IF
170*
171* Now find the max magnitude entry of each column of the factor in
172* AF. No pivoting, so no permutations.
173*
174 IF ( lsame( 'Upper', uplo ) ) THEN
175 DO j = 1, ncols
176 DO i = 1, j
177 work( j ) = max( cabs1( af( i, j ) ), work( j ) )
178 END DO
179 END DO
180 ELSE
181 DO j = 1, ncols
182 DO i = j, ncols
183 work( j ) = max( cabs1( af( i, j ) ), work( j ) )
184 END DO
185 END DO
186 END IF
187*
188* Compute the *inverse* of the max element growth factor. Dividing
189* by zero would imply the largest entry of the factor's column is
190* zero. Than can happen when either the column of A is zero or
191* massive pivots made the factor underflow to zero. Neither counts
192* as growth in itself, so simply ignore terms with zero
193* denominators.
194*
195 IF ( lsame( 'Upper', uplo ) ) THEN
196 DO i = 1, ncols
197 umax = work( i )
198 amax = work( ncols+i )
199 IF ( umax /= 0.0d+0 ) THEN
200 rpvgrw = min( amax / umax, rpvgrw )
201 END IF
202 END DO
203 ELSE
204 DO i = 1, ncols
205 umax = work( i )
206 amax = work( ncols+i )
207 IF ( umax /= 0.0d+0 ) THEN
208 rpvgrw = min( amax / umax, rpvgrw )
209 END IF
210 END DO
211 END IF
212
213 zla_porpvgrw = rpvgrw
214*
215* End of ZLA_PORPVGRW
216*
double precision function zla_porpvgrw(uplo, ncols, a, lda, af, ldaf, work)
ZLA_PORPVGRW computes the reciprocal pivot growth factor norm(A)/norm(U) for a symmetric or Hermitian...
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: