1
- * > \brief \b DLAORHR_GETRFNP
1
+ * > \brief \b DLAORHR_COL_GETRFNP
2
2
*
3
3
* =========== DOCUMENTATION ===========
4
4
*
5
5
* Online html documentation available at
6
6
* http://www.netlib.org/lapack/explore-html/
7
7
*
8
8
* > \htmlonly
9
- * > Download DLAORHR_GETRFNP + dependencies
10
- * > <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlaorhr_getrfnp .f">
9
+ * > Download DLAORHR_COL_GETRFNP + dependencies
10
+ * > <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlaorhr_col_getrfnp .f">
11
11
* > [TGZ]</a>
12
- * > <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlaorhr_getrfnp .f">
12
+ * > <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlaorhr_col_getrfnp .f">
13
13
* > [ZIP]</a>
14
- * > <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaorhr_getrfnp .f">
14
+ * > <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaorhr_col_getrfnp .f">
15
15
* > [TXT]</a>
16
16
* > \endhtmlonly
17
17
*
18
18
* Definition:
19
19
* ===========
20
20
*
21
- * SUBROUTINE DLAORHR_GETRFNP ( M, N, A, LDA, D, INFO )
21
+ * SUBROUTINE DLAORHR_COL_GETRFNP ( M, N, A, LDA, D, INFO )
22
22
*
23
23
* .. Scalar Arguments ..
24
24
* INTEGER INFO, LDA, M, N
33
33
* >
34
34
* > \verbatim
35
35
* >
36
- * > DLAORHR_GETRFNP computes the modified LU factorization without
37
- * > pivoting of a general M-by-N matrix A. The factorization has
36
+ * > DLAORHR_COL_GETRFNP computes the modified LU factorization without
37
+ * > pivoting of a real general M-by-N matrix A. The factorization has
38
38
* > the form:
39
39
* >
40
40
* > A - S = L * U,
48
48
* > at least one in absolute value (so that division-by-zero not
49
49
* > not possible during the division by the diagonal element);
50
50
* >
51
- * > L is a m -by-n lower triangular matrix with unit diagonal elements
52
- * > (lower trapezoidal if m > n );
51
+ * > L is a M -by-N lower triangular matrix with unit diagonal elements
52
+ * > (lower trapezoidal if M > N );
53
53
* >
54
- * > and U is a m -by-n upper triangular matrix
55
- * > (upper trapezoidal if m < n ).
54
+ * > and U is a M -by-N upper triangular matrix
55
+ * > (upper trapezoidal if M < N ).
56
56
* >
57
57
* > This routine is an auxiliary routine used in the Householder
58
- * > reconstruction routine DORHR . In DORHR , this routine is applied
59
- * > to an orthonormal M-by-N matrix A, where each element is bounded
60
- * > by one in absolute value. With the choice of the matrix S above,
61
- * > one can show that the diagonal element at each step of Gaussian
62
- * > elimination is the largest (in absolute value) in the column
63
- * > on or below the diagonal, so that no pivoting is required for
64
- * > numerical stability [1].
58
+ * > reconstruction routine DORHR_COL . In DORHR_COL , this routine is
59
+ * > applied to an M-by-N matrix A with orthonormal columns, where each
60
+ * > element is bounded by one in absolute value. With the choice of
61
+ * > the matrix S above, one can show that the diagonal element at each
62
+ * > step of Gaussian elimination is the largest (in absolute value) in
63
+ * > the column on or below the diagonal, so that no pivoting is required
64
+ * > for numerical stability [1].
65
65
* >
66
66
* > For more details on the Householder reconstruction algorithm,
67
67
* > including the modified LU factorization, see [1].
68
68
* >
69
69
* > This is the blocked right-looking version of the algorithm,
70
70
* > calling Level 3 BLAS to update the submatrix. To factorize a block,
71
- * > this routine calls the recursive routine DLAORHR_GETRFNP2 .
71
+ * > this routine calls the recursive routine DLAORHR_COL_GETRFNP2 .
72
72
* >
73
73
* > [1] "Reconstructing Householder vectors from tall-skinny QR",
74
74
* > G. Ballard, J. Demmel, L. Grigori, M. Jacquelin, H.D. Nguyen,
128
128
* > \author Univ. of Colorado Denver
129
129
* > \author NAG Ltd.
130
130
*
131
- * > \date June 2019
131
+ * > \date November 2019
132
132
*
133
133
* > \ingroup doubleGEcomputational
134
134
*
137
137
* >
138
138
* > \verbatim
139
139
* >
140
- * > June 2019, Igor Kozachenko,
141
- * > Computer Science Division,
142
- * > University of California, Berkeley
140
+ * > November 2019, Igor Kozachenko,
141
+ * > Computer Science Division,
142
+ * > University of California, Berkeley
143
143
* >
144
144
* > \endverbatim
145
145
*
146
146
* =====================================================================
147
- SUBROUTINE DLAORHR_GETRFNP ( M , N , A , LDA , D , INFO )
147
+ SUBROUTINE DLAORHR_COL_GETRFNP ( M , N , A , LDA , D , INFO )
148
148
IMPLICIT NONE
149
149
*
150
150
* -- LAPACK computational routine (version 3.9.0) --
151
151
* -- LAPACK is a software package provided by Univ. of Tennessee, --
152
152
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153
- * June 2019
153
+ * November 2019
154
154
*
155
155
* .. Scalar Arguments ..
156
156
INTEGER INFO, LDA, M, N
@@ -169,7 +169,7 @@ SUBROUTINE DLAORHR_GETRFNP( M, N, A, LDA, D, INFO )
169
169
INTEGER IINFO, J, JB, NB
170
170
* ..
171
171
* .. External Subroutines ..
172
- EXTERNAL DGEMM, DLAORHR_GETRFNP2 , DTRSM, XERBLA
172
+ EXTERNAL DGEMM, DLAORHR_COL_GETRFNP2 , DTRSM, XERBLA
173
173
* ..
174
174
* .. External Functions ..
175
175
INTEGER ILAENV
@@ -191,7 +191,7 @@ SUBROUTINE DLAORHR_GETRFNP( M, N, A, LDA, D, INFO )
191
191
INFO = - 4
192
192
END IF
193
193
IF ( INFO.NE. 0 ) THEN
194
- CALL XERBLA( ' DLAORHR_GETRFNP ' , - INFO )
194
+ CALL XERBLA( ' DLAORHR_COL_GETRFNP ' , - INFO )
195
195
RETURN
196
196
END IF
197
197
*
@@ -203,13 +203,13 @@ SUBROUTINE DLAORHR_GETRFNP( M, N, A, LDA, D, INFO )
203
203
* Determine the block size for this environment.
204
204
*
205
205
206
- NB = ILAENV( 1 , ' DLAORHR_GETRFNP ' , ' ' , M, N, - 1 , - 1 )
206
+ NB = ILAENV( 1 , ' DLAORHR_COL_GETRFNP ' , ' ' , M, N, - 1 , - 1 )
207
207
208
208
IF ( NB.LE. 1 .OR. NB.GE. MIN ( M, N ) ) THEN
209
209
*
210
210
* Use unblocked code.
211
211
*
212
- CALL DLAORHR_GETRFNP2 ( M, N, A, LDA, D, INFO )
212
+ CALL DLAORHR_COL_GETRFNP2 ( M, N, A, LDA, D, INFO )
213
213
ELSE
214
214
*
215
215
* Use blocked code.
@@ -219,8 +219,8 @@ SUBROUTINE DLAORHR_GETRFNP( M, N, A, LDA, D, INFO )
219
219
*
220
220
* Factor diagonal and subdiagonal blocks.
221
221
*
222
- CALL DLAORHR_GETRFNP2 ( M- J+1 , JB, A( J, J ), LDA, D( J ) ,
223
- $ IINFO )
222
+ CALL DLAORHR_COL_GETRFNP2 ( M- J+1 , JB, A( J, J ), LDA,
223
+ $ D( J ), IINFO )
224
224
*
225
225
IF ( J+ JB.LE. N ) THEN
226
226
*
@@ -243,6 +243,6 @@ SUBROUTINE DLAORHR_GETRFNP( M, N, A, LDA, D, INFO )
243
243
END IF
244
244
RETURN
245
245
*
246
- * End of DLAORHR_GETRFNP
246
+ * End of DLAORHR_COL_GETRFNP
247
247
*
248
248
END
0 commit comments