2329
|
1 SUBROUTINE DGETF2( M, N, A, LDA, IPIV, INFO ) |
|
2 * |
3333
|
3 * -- LAPACK routine (version 3.0) -- |
2329
|
4 * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd., |
|
5 * Courant Institute, Argonne National Lab, and Rice University |
|
6 * June 30, 1992 |
|
7 * |
|
8 * .. Scalar Arguments .. |
|
9 INTEGER INFO, LDA, M, N |
|
10 * .. |
|
11 * .. Array Arguments .. |
|
12 INTEGER IPIV( * ) |
|
13 DOUBLE PRECISION A( LDA, * ) |
|
14 * .. |
|
15 * |
|
16 * Purpose |
|
17 * ======= |
|
18 * |
|
19 * DGETF2 computes an LU factorization of a general m-by-n matrix A |
|
20 * using partial pivoting with row interchanges. |
|
21 * |
|
22 * The factorization has the form |
|
23 * A = P * L * U |
|
24 * where P is a permutation matrix, L is lower triangular with unit |
|
25 * diagonal elements (lower trapezoidal if m > n), and U is upper |
|
26 * triangular (upper trapezoidal if m < n). |
|
27 * |
|
28 * This is the right-looking Level 2 BLAS version of the algorithm. |
|
29 * |
|
30 * Arguments |
|
31 * ========= |
|
32 * |
|
33 * M (input) INTEGER |
|
34 * The number of rows of the matrix A. M >= 0. |
|
35 * |
|
36 * N (input) INTEGER |
|
37 * The number of columns of the matrix A. N >= 0. |
|
38 * |
|
39 * A (input/output) DOUBLE PRECISION array, dimension (LDA,N) |
|
40 * On entry, the m by n matrix to be factored. |
|
41 * On exit, the factors L and U from the factorization |
|
42 * A = P*L*U; the unit diagonal elements of L are not stored. |
|
43 * |
|
44 * LDA (input) INTEGER |
|
45 * The leading dimension of the array A. LDA >= max(1,M). |
|
46 * |
|
47 * IPIV (output) INTEGER array, dimension (min(M,N)) |
|
48 * The pivot indices; for 1 <= i <= min(M,N), row i of the |
|
49 * matrix was interchanged with row IPIV(i). |
|
50 * |
|
51 * INFO (output) INTEGER |
|
52 * = 0: successful exit |
|
53 * < 0: if INFO = -k, the k-th argument had an illegal value |
|
54 * > 0: if INFO = k, U(k,k) is exactly zero. The factorization |
|
55 * has been completed, but the factor U is exactly |
|
56 * singular, and division by zero will occur if it is used |
|
57 * to solve a system of equations. |
|
58 * |
|
59 * ===================================================================== |
|
60 * |
|
61 * .. Parameters .. |
|
62 DOUBLE PRECISION ONE, ZERO |
|
63 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 ) |
|
64 * .. |
|
65 * .. Local Scalars .. |
|
66 INTEGER J, JP |
|
67 * .. |
|
68 * .. External Functions .. |
|
69 INTEGER IDAMAX |
|
70 EXTERNAL IDAMAX |
|
71 * .. |
|
72 * .. External Subroutines .. |
|
73 EXTERNAL DGER, DSCAL, DSWAP, XERBLA |
|
74 * .. |
|
75 * .. Intrinsic Functions .. |
|
76 INTRINSIC MAX, MIN |
|
77 * .. |
|
78 * .. Executable Statements .. |
|
79 * |
|
80 * Test the input parameters. |
|
81 * |
|
82 INFO = 0 |
|
83 IF( M.LT.0 ) THEN |
|
84 INFO = -1 |
|
85 ELSE IF( N.LT.0 ) THEN |
|
86 INFO = -2 |
|
87 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN |
|
88 INFO = -4 |
|
89 END IF |
|
90 IF( INFO.NE.0 ) THEN |
|
91 CALL XERBLA( 'DGETF2', -INFO ) |
|
92 RETURN |
|
93 END IF |
|
94 * |
|
95 * Quick return if possible |
|
96 * |
|
97 IF( M.EQ.0 .OR. N.EQ.0 ) |
|
98 $ RETURN |
|
99 * |
|
100 DO 10 J = 1, MIN( M, N ) |
|
101 * |
|
102 * Find pivot and test for singularity. |
|
103 * |
|
104 JP = J - 1 + IDAMAX( M-J+1, A( J, J ), 1 ) |
|
105 IPIV( J ) = JP |
|
106 IF( A( JP, J ).NE.ZERO ) THEN |
|
107 * |
|
108 * Apply the interchange to columns 1:N. |
|
109 * |
|
110 IF( JP.NE.J ) |
|
111 $ CALL DSWAP( N, A( J, 1 ), LDA, A( JP, 1 ), LDA ) |
|
112 * |
|
113 * Compute elements J+1:M of J-th column. |
|
114 * |
|
115 IF( J.LT.M ) |
|
116 $ CALL DSCAL( M-J, ONE / A( J, J ), A( J+1, J ), 1 ) |
|
117 * |
|
118 ELSE IF( INFO.EQ.0 ) THEN |
|
119 * |
|
120 INFO = J |
|
121 END IF |
|
122 * |
|
123 IF( J.LT.MIN( M, N ) ) THEN |
|
124 * |
|
125 * Update trailing submatrix. |
|
126 * |
|
127 CALL DGER( M-J, N-J, -ONE, A( J+1, J ), 1, A( J, J+1 ), LDA, |
|
128 $ A( J+1, J+1 ), LDA ) |
|
129 END IF |
|
130 10 CONTINUE |
|
131 RETURN |
|
132 * |
|
133 * End of DGETF2 |
|
134 * |
|
135 END |