Skip to content

Commit ea30393

Browse files
author
scr2016
committed
Modified comments in new REAL Householder reconstruction routines,
S and D precisions: modified: SRC/dgetsqrhrt.f modified: SRC/dlarfb_gett.f modified: SRC/dorgtsqr_row.f modified: SRC/sgetsqrhrt.f modified: SRC/slarfb_gett.f modified: SRC/sorgtsqr_row.f
1 parent 8e8c025 commit ea30393

File tree

6 files changed

+126
-116
lines changed

6 files changed

+126
-116
lines changed

SRC/dgetsqrhrt.f

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@
2323
* IMPLICIT NONE
2424
*
2525
* .. Scalar Arguments ..
26-
* INTEGER INFO, LDA, LDT, LWORK, M, N, NB1, NB2, MB1
26+
* INTEGER INFO, LDA, LDT, LWORK, M, N, NB1, NB2, MB1
2727
* ..
2828
* .. Array Arguments ..
2929
* DOUBLE PRECISION A( LDA, * ), T( LDT, * ), WORK( * )
@@ -35,22 +35,22 @@
3535
*>
3636
*> \verbatim
3737
*>
38-
*> DGETSQRHRT computes an NB-size column blocked QR-factorization
38+
*> DGETSQRHRT computes a NB2-sized column blocked QR-factorization
3939
*> of a real M-by-N matrix A with M >= N,
4040
*>
4141
*> A = Q * R.
4242
*>
4343
*> The routine uses internally a NB1-sized column blocked and MB1-sized
44-
*> row blocked TSQR-factorization and performing the reconstruction
44+
*> row blocked TSQR-factorization and perfors the reconstruction
4545
*> of the Householder vectors from the TSQR output. The routine also
4646
*> converts the R_tsqr factor from the TSQR-factorization output into
4747
*> the R factor that corresponds to the Householder QR-factorization,
4848
*>
4949
*> A = Q_tsqr * R_tsqr = Q * R.
5050
*>
5151
*> The output Q and R factors are stored in the same format as in DGEQRT
52-
*> (Q is in compact WY-representation). See the documentation of DGEQRT
53-
*> for more details on the format.
52+
*> (Q is in blocked compact WY-representation). See the documentation
53+
*> of DGEQRT for more details on the format.
5454
*> \endverbatim
5555
*
5656
* Arguments:
@@ -300,8 +300,8 @@ SUBROUTINE DGETSQRHRT( M, N, MB1, NB1, NB2, A, LDA, T, LDT, WORK,
300300
$ WORK(LWT+1), LW1, IINFO )
301301
*
302302
* (2) Copy the factor R_tsqr stored in the upper-triangular part
303-
* of A into the square matrix in the work array WORK(LWT+1:LWT+N*N)
304-
* column-by-column.
303+
* of A into the square matrix in the work array
304+
* WORK(LWT+1:LWT+N*N) column-by-column.
305305
*
306306
DO J = 1, N
307307
CALL DCOPY( J, A( 1, J ), 1, WORK( LWT + N*(J-1)+1 ), 1 )
@@ -325,7 +325,7 @@ SUBROUTINE DGETSQRHRT( M, N, MB1, NB1, NB2, A, LDA, T, LDT, WORK,
325325
* part of A.
326326
*
327327
* (6) Compute from R_tsqr the factor R_hr corresponding to
328-
* the reconstructed Householder vectors, i.e. R_hr = R_tsqr * S.
328+
* the reconstructed Householder vectors, i.e. R_hr = S * R_tsqr.
329329
* This multiplication by the sign matrix S on the left means
330330
* changing the sign of I-th row of the matrix R_tsqr according
331331
* to sign of the I-th diagonal element DIAG(I) of the matrix S.

SRC/dlarfb_gett.f

Lines changed: 44 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@
3636
*> \verbatim
3737
*>
3838
*> DLARFB_GETT applies a real Householder block reflector H from the
39-
*> left to a real (K+M)-by-N "triangular-pentagonal" matrix, which is
39+
*> left to a real (K+M)-by-N "triangular-pentagonal" matrix
4040
*> composed of two block matrices: an upper trapezoidal K-by-N matrix A
4141
*> stored in the array A, and a rectangular M-by-(N-K) matrix B, stored
4242
*> in the array B. The block reflector H is stored in a compact
@@ -50,9 +50,11 @@
5050
*> \param[in] IDENT
5151
*> \verbatim
5252
*> IDENT is CHARACTER*1
53-
*> = 'I': V1 is an identity matrix and not stored.
54-
*> = 'N': V1 is unit lower-triangular and
55-
*> stored in the left K-by-K block of A.
53+
*> If IDENT = not 'I', or not 'i', then V1 is unit
54+
*> lower-triangular and stored in the left K-by-K block of
55+
*> the input matrix A,
56+
*> If IDENT = 'I' or 'i', then V1 is an identity matrix and
57+
*> not stored.
5658
*> See Further Details section.
5759
*> \endverbatim
5860
*>
@@ -98,8 +100,8 @@
98100
*>
99101
*> On entry:
100102
*> a) In the K-by-N upper-trapezoidal part A: input matrix A.
101-
*> b) In the columns below the diagonal: columns of V1,
102-
*> (Ones are not stored on the diagonal).
103+
*> b) In the columns below the diagonal: columns of V1
104+
*> (ones are not stored on the diagonal).
103105
*>
104106
*> On exit:
105107
*> A is overwritten by rectangular K-by-N product H*A.
@@ -174,7 +176,7 @@
174176
*>
175177
*> \verbatim
176178
*>
177-
*> (1) Description of an Algebraic Operation.
179+
*> (1) Description of the Algebraic Operation.
178180
*>
179181
*> The matrix A is a K-by-N matrix composed of two column block
180182
*> matrices, A1, which is K-by-K, and A2, which is K-by-(N-K):
@@ -194,32 +196,32 @@
194196
*> a) ( A_in ) consists of two block columns:
195197
*> ( B_in )
196198
*>
197-
*> ( A_in ) = (( A1_in ) ( A2_in ))
198-
*> ( B_in ) (( 0 ) ( B2_in )),
199+
*> ( A_in ) = (( A1_in ) ( A2_in )) = (( A1_in ) ( A2_in ))
200+
*> ( B_in ) (( B1_in ) ( B2_in )) (( 0 ) ( B2_in )),
199201
*>
200202
*> where the column blocks are:
201203
*>
202204
*> ( A1_in ) is a K-by-K upper-triangular matrix stored in the
203-
*> upper triangular part of the array A(1:K,1:K),
204-
*> ( B1_in ) is an M-by-K rectangular ZERO matrix and not stored;
205+
*> upper triangular part of the array A(1:K,1:K).
206+
*> ( B1_in ) is an M-by-K rectangular ZERO matrix and not stored.
205207
*>
206208
*> ( A2_in ) is a K-by-(N-K) rectangular matrix stored
207-
*> in the array A(1:K,K+1:N),
209+
*> in the array A(1:K,K+1:N).
208210
*> ( B2_in ) is an M-by-(N-K) rectangular matrix stored
209-
*> in the array B(1:M,K+1:N),
211+
*> in the array B(1:M,K+1:N).
210212
*>
211213
*> b) V = ( V1 )
212214
*> ( V2 )
213215
*>
214-
*> where V1:
215-
*> 1) if IDENT == 'I', is a K-by-K identity matrix, not stored;
216-
*> 2) if IDENT != 'I', is a K-by-K unit lower-triangular matrix,
217-
*> stored in the lower-triangular part of the array
218-
*> A(1:K,1:K) (ones are not stored),
219-
*> and V2 is an M-by-K rectangular stored the array B(1:M,1:K),
220-
*> (because on input B1_in is a rectangular zero
221-
*> matrix that is not stored and the space is
222-
*> used to store V2),
216+
*> where:
217+
*> 1) if IDENT == 'I',V1 is a K-by-K identity matrix, not stored;
218+
*> 2) if IDENT != 'I',V1 is a K-by-K unit lower-triangular matrix,
219+
*> stored in the lower-triangular part of the array
220+
*> A(1:K,1:K) (ones are not stored),
221+
*> and V2 is an M-by-K rectangular stored the array B(1:M,1:K),
222+
*> (because on input B1_in is a rectangular zero
223+
*> matrix that is not stored and the space is
224+
*> used to store V2).
223225
*>
224226
*> c) T is a K-by-K upper-triangular matrix stored
225227
*> in the array T(1:K,1:K).
@@ -234,13 +236,15 @@
234236
*>
235237
*> where the column blocks are:
236238
*>
237-
*> ( A1_out ) is a K-by-K square matrix stored in the array
238-
*> A(1:K,1:K) (upper-triangular if V1 is ZERO matrix)
239+
*> ( A1_out ) is a K-by-K square matrix, or a K-by-K
240+
*> upper-triangular matrix, if V1 is an
241+
*> identity matrix. AiOut is stored in
242+
*> the array A(1:K,1:K).
239243
*> ( B1_out ) is an M-by-K rectangular matrix stored
240244
*> in the array B(1:M,K:N).
241245
*>
242246
*> ( A2_out ) is a K-by-(N-K) rectangular matrix stored
243-
*> in the array A(1:K,K+1:N),
247+
*> in the array A(1:K,K+1:N).
244248
*> ( B2_out ) is an M-by-(N-K) rectangular matrix stored
245249
*> in the array B(1:M,K+1:N).
246250
*>
@@ -258,31 +262,31 @@
258262
*>
259263
*> The computation for column block 1:
260264
*>
261-
*> A1: = A1 - V1*T*(V1**T)*A1
265+
*> A1_out: = A1_in - V1*T*(V1**T)*A1_in
262266
*>
263-
*> B1: = - V2*T*(V1**T)*A1
267+
*> B1_out: = - V2*T*(V1**T)*A1_in
264268
*>
265269
*> The computation for column block 2, which exists if N > K:
266270
*>
267-
*> A2: = A2 - V1*T*( (V1**T)*A2 + (V2**T)*B2 )
271+
*> A2_out: = A2_in - V1*T*( (V1**T)*A2_in + (V2**T)*B2_in )
268272
*>
269-
*> B2: = B2 - V2*T*( (V1**T)*A2 + (V2**T)*B2 )
273+
*> B2_out: = B2_in - V2*T*( (V1**T)*A2_in + (V2**T)*B2_in )
270274
*>
271275
*> If IDENT == 'I':
272276
*>
273277
*> The operation for column block 1:
274278
*>
275-
*> A1: = A1 - V1*T**A1
279+
*> A1_out: = A1_in - V1*T**A1_in
276280
*>
277-
*> B1: = - V2*T**A1
281+
*> B1_out: = - V2*T**A1_in
278282
*>
279283
*> The computation for column block 2, which exists if N > K:
280284
*>
281-
*> A2: = A2 - T*( A2 + (V2**T)*B2 )
285+
*> A2_out: = A2_in - T*( A2_in + (V2**T)*B2_in )
282286
*>
283-
*> B2: = B2 - V2*T*( A2 + (V2**T)*B2 )
287+
*> B2_out: = B2_in - V2*T*( A2_in + (V2**T)*B2_in )
284288
*>
285-
*> (2) Description of an Algorithmic Computation.
289+
*> (2) Description of the Algorithmic Computation.
286290
*>
287291
*> In the first step, we compute column block 2, i.e. A2 and B2.
288292
*> Here, we need to use the K-by-(N-K) rectangular workspace
@@ -409,7 +413,7 @@ SUBROUTINE DLARFB_GETT( IDENT, M, N, K, T, LDT, A, LDA, B, LDB,
409413
PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
410414
* ..
411415
* .. Local Scalars ..
412-
LOGICAL LIDENT
416+
LOGICAL LNOTIDENT
413417
INTEGER I, J
414418
* ..
415419
* .. EXTERNAL FUNCTIONS ..
@@ -426,7 +430,7 @@ SUBROUTINE DLARFB_GETT( IDENT, M, N, K, T, LDT, A, LDA, B, LDB,
426430
IF( M.LT.0 .OR. N.LE.0 .OR. K.EQ.0 .OR. K.GT.N )
427431
$ RETURN
428432
*
429-
LIDENT = LSAME( IDENT, 'I' )
433+
LNOTIDENT = .NOT.LSAME( IDENT, 'I' )
430434
*
431435
* ------------------------------------------------------------------
432436
*
@@ -446,7 +450,7 @@ SUBROUTINE DLARFB_GETT( IDENT, M, N, K, T, LDT, A, LDA, B, LDB,
446450
CALL DCOPY( K, A( 1, K+J ), 1, WORK( 1, J ), 1 )
447451
END DO
448452

449-
IF( .NOT.LIDENT ) THEN
453+
IF( LNOTIDENT ) THEN
450454
*
451455
* col2_(2) Compute W2: = (V1**T) * W2 = (A1**T) * W2,
452456
* V1 is not an identy matrix, but unit lower-triangular
@@ -479,7 +483,7 @@ SUBROUTINE DLARFB_GETT( IDENT, M, N, K, T, LDT, A, LDA, B, LDB,
479483
$ WORK, LDWORK, ONE, B( 1, K+1 ), LDB )
480484
END IF
481485
*
482-
IF( .NOT.LIDENT ) THEN
486+
IF( LNOTIDENT ) THEN
483487
*
484488
* col2_(6) Compute W2: = V1 * W2 = A1 * W2,
485489
* V1 is not an identity matrix, but unit lower-triangular,
@@ -526,7 +530,7 @@ SUBROUTINE DLARFB_GETT( IDENT, M, N, K, T, LDT, A, LDA, B, LDB,
526530
END DO
527531
END DO
528532
*
529-
IF( .NOT.LIDENT ) THEN
533+
IF( LNOTIDENT ) THEN
530534
*
531535
* col1_(2) Compute W1: = (V1**T) * W1 = (A1**T) * W1,
532536
* V1 is not an identity matrix, but unit lower-triangular
@@ -552,7 +556,7 @@ SUBROUTINE DLARFB_GETT( IDENT, M, N, K, T, LDT, A, LDA, B, LDB,
552556
$ B, LDB )
553557
END IF
554558
*
555-
IF( .NOT.LIDENT ) THEN
559+
IF( LNOTIDENT ) THEN
556560
*
557561
* col1_(5) Compute W1: = V1 * W1 = A1 * W1,
558562
* V1 is not an identity matrix, but unit lower-triangular

SRC/dorgtsqr_row.f

Lines changed: 11 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@
1818
* ===========
1919
*
2020
* SUBROUTINE DORGTSQR_ROW( M, N, MB, NB, A, LDA, T, LDT, WORK,
21-
* $ LWORK, INFO )
21+
* $ LWORK, INFO )
2222
* IMPLICIT NONE
2323
*
2424
* .. Scalar Arguments ..
@@ -33,10 +33,11 @@
3333
*>
3434
*> \verbatim
3535
*>
36-
*> DORGTSQR_ROW generates an M-by-N real matrix Q_out with orthonormal
37-
*> columns from the output of DLATSQR. These N orthonormal columns are
38-
*> the first N columns of a product of real orthogonal matrices Q(k)_in
39-
*> of order M, which are returned by DLATSQR in a special format.
36+
*> DORGTSQR_ROW generates an M-by-N real matrix Q_out with
37+
*> orthonormal columns from the output of DLATSQR. These N orthonormal
38+
*> columns are the first N columns of a product of complex unitary
39+
*> matrices Q(k)_in of order M, which are returned by DLATSQR in
40+
*> a special format.
4041
*>
4142
*> Q_out = first_N_columns_of( Q(1)_in * Q(2)_in * ... * Q(k)_in ).
4243
*>
@@ -47,7 +48,7 @@
4748
*> where the computation is performed on each individual block. The
4849
*> algorithm first sweeps NB-sized column blocks from the right to left
4950
*> starting in the bottom row block and continues to the top row block
50-
*> (Hence _ROW in the routine name). This sweep is in reverse order of
51+
*> (hence _ROW in the routine name). This sweep is in reverse order of
5152
*> the order in which DLATSQR generates the output blocks.
5253
*> \endverbatim
5354
*
@@ -90,11 +91,11 @@
9091
*>
9192
*> On entry:
9293
*>
93-
*> The elements on and above the diagonal are not accessed.
94-
*> The elements below the diagonal represent the unit
94+
*> The elements on and above the diagonal are not used as
95+
*> input. The elements below the diagonal represent the unit
9596
*> lower-trapezoidal blocked matrix V computed by DLATSQR
9697
*> that defines the input matrices Q_in(k) (ones on the
97-
*> diagonal are not stored) See DLATSQR for more details.
98+
*> diagonal are not stored). See DLATSQR for more details.
9899
*>
99100
*> On exit:
100101
*>
@@ -184,7 +185,7 @@
184185
*>
185186
* =====================================================================
186187
SUBROUTINE DORGTSQR_ROW( M, N, MB, NB, A, LDA, T, LDT, WORK,
187-
$ LWORK, INFO )
188+
$ LWORK, INFO )
188189
IMPLICIT NONE
189190
*
190191
* -- LAPACK computational routine (version 3.10.0) --

SRC/sgetsqrhrt.f

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -35,22 +35,22 @@
3535
*>
3636
*> \verbatim
3737
*>
38-
*> SGETSQRHRT computes an NB-size column blocked QR-factorization
39-
*> of a real M-by-N matrix A with M >= N,
38+
*> SGETSQRHRT computes a NB2-sized column blocked QR-factorization
39+
*> of a complex M-by-N matrix A with M >= N,
4040
*>
4141
*> A = Q * R.
4242
*>
4343
*> The routine uses internally a NB1-sized column blocked and MB1-sized
44-
*> row blocked TSQR-factorization and performing the reconstruction
44+
*> row blocked TSQR-factorization and perfors the reconstruction
4545
*> of the Householder vectors from the TSQR output. The routine also
4646
*> converts the R_tsqr factor from the TSQR-factorization output into
4747
*> the R factor that corresponds to the Householder QR-factorization,
4848
*>
4949
*> A = Q_tsqr * R_tsqr = Q * R.
5050
*>
5151
*> The output Q and R factors are stored in the same format as in SGEQRT
52-
*> (Q is in compact WY-representation). See the documentation of SGEQRT
53-
*> for more details on the format.
52+
*> (Q is in blocked compact WY-representation). See the documentation
53+
*> of SGEQRT for more details on the format.
5454
*> \endverbatim
5555
*
5656
* Arguments:
@@ -300,8 +300,8 @@ SUBROUTINE SGETSQRHRT( M, N, MB1, NB1, NB2, A, LDA, T, LDT, WORK,
300300
$ WORK(LWT+1), LW1, IINFO )
301301
*
302302
* (2) Copy the factor R_tsqr stored in the upper-triangular part
303-
* of A into the square matrix in the work array WORK(LWT+1:LWT+N*N)
304-
* column-by-column.
303+
* of A into the square matrix in the work array
304+
* WORK(LWT+1:LWT+N*N) column-by-column.
305305
*
306306
DO J = 1, N
307307
CALL SCOPY( J, A( 1, J ), 1, WORK( LWT + N*(J-1)+1 ), 1 )
@@ -325,7 +325,7 @@ SUBROUTINE SGETSQRHRT( M, N, MB1, NB1, NB2, A, LDA, T, LDT, WORK,
325325
* part of A.
326326
*
327327
* (6) Compute from R_tsqr the factor R_hr corresponding to
328-
* the reconstructed Householder vectors, i.e. R_hr = R_tsqr * S.
328+
* the reconstructed Householder vectors, i.e. R_hr = S * R_tsqr.
329329
* This multiplication by the sign matrix S on the left means
330330
* changing the sign of I-th row of the matrix R_tsqr according
331331
* to sign of the I-th diagonal element DIAG(I) of the matrix S.

0 commit comments

Comments
 (0)