OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
zgetrf.f
Go to the documentation of this file.
1C> \brief \b ZGETRF VARIANT: left-looking Level 3 BLAS version of the algorithm.
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 ZGETRF ( M, N, A, LDA, IPIV, INFO)
12*
13* .. Scalar Arguments ..
14* INTEGER INFO, LDA, M, N
15* ..
16* .. Array Arguments ..
17* INTEGER IPIV( * )
18* COMPLEX*16 A( LDA, * )
19* ..
20*
21* Purpose
22* =======
23*
24C>\details \b Purpose:
25C>\verbatim
26C>
27C> ZGETRF computes an LU factorization of a general M-by-N matrix A
28C> using partial pivoting with row interchanges.
29C>
30C> The factorization has the form
31C> A = P * L * U
32C> where P is a permutation matrix, L is lower triangular with unit
33C> diagonal elements (lower trapezoidal if m > n), and U is upper
34C> triangular (upper trapezoidal if m < n).
35C>
36C> This is the left-looking Level 3 BLAS version of the algorithm.
37C>
38C>\endverbatim
39*
40* Arguments:
41* ==========
42*
43C> \param[in] M
44C> \verbatim
45C> M is INTEGER
46C> The number of rows of the matrix A. M >= 0.
47C> \endverbatim
48C>
49C> \param[in] N
50C> \verbatim
51C> N is INTEGER
52C> The number of columns of the matrix A. N >= 0.
53C> \endverbatim
54C>
55C> \param[in,out] A
56C> \verbatim
57C> A is COMPLEX*16 array, dimension (LDA,N)
58C> On entry, the M-by-N matrix to be factored.
59C> On exit, the factors L and U from the factorization
60C> A = P*L*U; the unit diagonal elements of L are not stored.
61C> \endverbatim
62C>
63C> \param[in] LDA
64C> \verbatim
65C> LDA is INTEGER
66C> The leading dimension of the array A. LDA >= max(1,M).
67C> \endverbatim
68C>
69C> \param[out] IPIV
70C> \verbatim
71C> IPIV is INTEGER array, dimension (min(M,N))
72C> The pivot indices; for 1 <= i <= min(M,N), row i of the
73C> matrix was interchanged with row IPIV(i).
74C> \endverbatim
75C>
76C> \param[out] INFO
77C> \verbatim
78C> INFO is INTEGER
79C> = 0: successful exit
80C> < 0: if INFO = -i, the i-th argument had an illegal value
81C> > 0: if INFO = i, U(i,i) is exactly zero. The factorization
82C> has been completed, but the factor U is exactly
83C> singular, and division by zero will occur if it is used
84C> to solve a system of equations.
85C> \endverbatim
86C>
87*
88* Authors:
89* ========
90*
91C> \author Univ. of Tennessee
92C> \author Univ. of California Berkeley
93C> \author Univ. of Colorado Denver
94C> \author NAG Ltd.
95*
96C> \date December 2016
97*
98C> \ingroup variantsGEcomputational
99*
100* =====================================================================
101 SUBROUTINE zgetrf ( M, N, A, LDA, IPIV, INFO)
102*
103* -- LAPACK computational routine --
104* -- LAPACK is a software package provided by Univ. of Tennessee, --
105* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106*
107* .. Scalar Arguments ..
108 INTEGER INFO, LDA, M, N
109* ..
110* .. Array Arguments ..
111 INTEGER IPIV( * )
112 COMPLEX*16 A( LDA, * )
113* ..
114*
115* =====================================================================
116*
117* .. Parameters ..
118 COMPLEX*16 ONE
119 parameter( one = (1.0d+0, 0.0d+0) )
120* ..
121* .. Local Scalars ..
122 INTEGER I, IINFO, J, JB, K, NB
123* ..
124* .. External Subroutines ..
125 EXTERNAL zgemm, zgetf2, zlaswp, ztrsm, xerbla
126* ..
127* .. External Functions ..
128 INTEGER ILAENV
129 EXTERNAL ilaenv
130* ..
131* .. Intrinsic Functions ..
132 INTRINSIC max, min
133* ..
134* .. Executable Statements ..
135*
136* Test the input parameters.
137*
138 info = 0
139 IF( m.LT.0 ) THEN
140 info = -1
141 ELSE IF( n.LT.0 ) THEN
142 info = -2
143 ELSE IF( lda.LT.max( 1, m ) ) THEN
144 info = -4
145 END IF
146 IF( info.NE.0 ) THEN
147 CALL xerbla( 'zgetrf', -INFO )
148 RETURN
149 END IF
150*
151* Quick return if possible
152*
153.EQ..OR..EQ. IF( M0 N0 )
154 $ RETURN
155*
156* Determine the block size for this environment.
157*
158 NB = ILAENV( 1, 'zgetrf', ' ', M, N, -1, -1 )
159.LE..OR..GE. IF( NB1 NBMIN( M, N ) ) THEN
160*
161* Use unblocked code.
162*
163 CALL ZGETF2( M, N, A, LDA, IPIV, INFO )
164
165 ELSE
166*
167* Use blocked code.
168*
169 DO 20 J = 1, MIN( M, N ), NB
170 JB = MIN( MIN( M, N )-J+1, NB )
171*
172*
173* Update before factoring the current panel
174*
175 DO 30 K = 1, J-NB, NB
176*
177* Apply interchanges to rows K:K+NB-1.
178*
179 CALL ZLASWP( JB, A(1, J), LDA, K, K+NB-1, IPIV, 1 )
180*
181* Compute block row of U.
182*
183 CALL ZTRSM( 'left', 'lower', 'no transpose', 'unit',
184 $ NB, JB, ONE, A( K, K ), LDA,
185 $ A( K, J ), LDA )
186*
187* Update trailing submatrix.
188*
189 CALL ZGEMM( 'no transpose', 'no transpose',
190 $ M-K-NB+1, JB, NB, -ONE,
191 $ A( K+NB, K ), LDA, A( K, J ), LDA, ONE,
192 $ A( K+NB, J ), LDA )
193 30 CONTINUE
194*
195* Factor diagonal and subdiagonal blocks and test for exact
196* singularity.
197*
198 CALL ZGETF2( M-J+1, JB, A( J, J ), LDA, IPIV( J ), IINFO )
199*
200* Adjust INFO and the pivot indices.
201*
202.EQ..AND..GT. IF( INFO0 IINFO0 )
203 $ INFO = IINFO + J - 1
204 DO 10 I = J, MIN( M, J+JB-1 )
205 IPIV( I ) = J - 1 + IPIV( I )
206 10 CONTINUE
207*
208 20 CONTINUE
209
210*
211* Apply interchanges to the left-overs
212*
213 DO 40 K = 1, MIN( M, N ), NB
214 CALL ZLASWP( K-1, A( 1, 1 ), LDA, K,
215 $ MIN (K+NB-1, MIN ( M, N )), IPIV, 1 )
216 40 CONTINUE
217*
218* Apply update to the M+1:N columns when N > M
219*
220.GT. IF ( NM ) THEN
221
222 CALL ZLASWP( N-M, A(1, M+1), LDA, 1, M, IPIV, 1 )
223
224 DO 50 K = 1, M, NB
225
226 JB = MIN( M-K+1, NB )
227*
228 CALL ZTRSM( 'left', 'lower', 'no transpose', 'unit',
229 $ JB, N-M, ONE, A( K, K ), LDA,
230 $ A( K, M+1 ), LDA )
231
232*
233.LE. IF ( K+NBM ) THEN
234 CALL ZGEMM( 'no transpose', 'no transpose',
235 $ M-K-NB+1, N-M, NB, -ONE,
236 $ A( K+NB, K ), LDA, A( K, M+1 ), LDA, ONE,
237 $ A( K+NB, M+1 ), LDA )
238 END IF
239 50 CONTINUE
240 END IF
241*
242 END IF
243 RETURN
244*
245* End of ZGETRF
246*
247 END
subroutine xerbla(srname, info)
XERBLA
Definition xerbla.f:60
subroutine zgetf2(m, n, a, lda, ipiv, info)
ZGETF2 computes the LU factorization of a general m-by-n matrix using partial pivoting with row inter...
Definition zgetf2.f:108
subroutine zlaswp(n, a, lda, k1, k2, ipiv, incx)
ZLASWP performs a series of row interchanges on a general rectangular matrix.
Definition zlaswp.f:115
subroutine zgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
ZGEMM
Definition zgemm.f:187
subroutine ztrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
ZTRSM
Definition ztrsm.f:180
subroutine zgetrf(m, n, a, lda, ipiv, info)
ZGETRF VARIANT: Crout Level 3 BLAS version of the algorithm.
Definition zgetrf.f:102
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21