Skip to content

Commit

Permalink
Improve input arg check lamtsqr
Browse files Browse the repository at this point in the history
  • Loading branch information
angsch committed Mar 9, 2022
1 parent 2a39774 commit 201353b
Show file tree
Hide file tree
Showing 7 changed files with 56 additions and 40 deletions.
20 changes: 12 additions & 8 deletions SRC/clamtsqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@
*> \verbatim
*> MB is INTEGER
*> The block size to be used in the blocked QR.
*> MB > N. (must be the same as DLATSQR)
*> MB > N. (must be the same as CLATSQR)
*> \endverbatim
*>
*> \param[in] NB
Expand All @@ -87,7 +87,7 @@
*> A is COMPLEX array, dimension (LDA,K)
*> The i-th column must contain the vector which defines the
*> blockedelementary reflector H(i), for i = 1,2,...,k, as
*> returned by DLATSQR in the first k columns of
*> returned by CLATSQR in the first k columns of
*> its array argument A.
*> \endverbatim
*>
Expand Down Expand Up @@ -214,7 +214,7 @@ SUBROUTINE CLAMTSQR( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN, LQUERY
INTEGER I, II, KK, LW, CTR
INTEGER I, II, KK, LW, CTR, Q
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -233,22 +233,26 @@ SUBROUTINE CLAMTSQR( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
RIGHT = LSAME( SIDE, 'R' )
IF (LEFT) THEN
LW = N * NB
Q = M
ELSE
LW = M * NB
Q = N
END IF
*
INFO = 0
IF( .NOT.LEFT .AND. .NOT.RIGHT ) THEN
INFO = -1
ELSE IF( .NOT.TRAN .AND. .NOT.NOTRAN ) THEN
INFO = -2
ELSE IF( M.LT.0 ) THEN
INFO = -3
ELSE IF( N.LT.0 ) THEN
INFO = -4
ELSE IF( K.LT.0 ) THEN
INFO = -5
ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
ELSE IF( N.LT.K ) THEN
INFO = -4
ELSE IF( M.LT.N ) THEN
INFO = -3
ELSE IF( K.LT.NB .OR. NB.LT.1 ) THEN
INFO = -7
ELSE IF( LDA.LT.MAX( 1, Q ) ) THEN
INFO = -9
ELSE IF( LDT.LT.MAX( 1, NB) ) THEN
INFO = -11
Expand Down
6 changes: 3 additions & 3 deletions SRC/dgemqrt.f
Original file line number Diff line number Diff line change
Expand Up @@ -94,15 +94,15 @@
*> NB is INTEGER
*> The block size used for the storage of T. K >= NB >= 1.
*> This must be the same value of NB used to generate T
*> in CGEQRT.
*> in DGEQRT.
*> \endverbatim
*>
*> \param[in] V
*> \verbatim
*> V is DOUBLE PRECISION array, dimension (LDV,K)
*> The i-th column must contain the vector which defines the
*> elementary reflector H(i), for i = 1,2,...,k, as returned by
*> CGEQRT in the first K columns of its array argument A.
*> DGEQRT in the first K columns of its array argument A.
*> \endverbatim
*>
*> \param[in] LDV
Expand All @@ -117,7 +117,7 @@
*> \verbatim
*> T is DOUBLE PRECISION array, dimension (LDT,K)
*> The upper triangular factors of the block reflectors
*> as returned by CGEQRT, stored as a NB-by-N matrix.
*> as returned by DGEQRT, stored as a NB-by-N matrix.
*> \endverbatim
*>
*> \param[in] LDT
Expand Down
16 changes: 10 additions & 6 deletions SRC/dlamtsqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -214,7 +214,7 @@ SUBROUTINE DLAMTSQR( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN, LQUERY
INTEGER I, II, KK, LW, CTR
INTEGER I, II, KK, LW, CTR, Q
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -233,22 +233,26 @@ SUBROUTINE DLAMTSQR( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
RIGHT = LSAME( SIDE, 'R' )
IF (LEFT) THEN
LW = N * NB
Q = M
ELSE
LW = MB * NB
Q = N
END IF
*
INFO = 0
IF( .NOT.LEFT .AND. .NOT.RIGHT ) THEN
INFO = -1
ELSE IF( .NOT.TRAN .AND. .NOT.NOTRAN ) THEN
INFO = -2
ELSE IF( M.LT.0 ) THEN
INFO = -3
ELSE IF( N.LT.0 ) THEN
INFO = -4
ELSE IF( K.LT.0 ) THEN
INFO = -5
ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
ELSE IF( N.LT.K ) THEN
INFO = -4
ELSE IF( M.LT.N ) THEN
INFO = -3
ELSE IF( K.LT.NB .OR. NB.LT.1 ) THEN
INFO = -7
ELSE IF( LDA.LT.MAX( 1, Q ) ) THEN
INFO = -9
ELSE IF( LDT.LT.MAX( 1, NB) ) THEN
INFO = -11
Expand Down
6 changes: 3 additions & 3 deletions SRC/sgemqrt.f
Original file line number Diff line number Diff line change
Expand Up @@ -94,15 +94,15 @@
*> NB is INTEGER
*> The block size used for the storage of T. K >= NB >= 1.
*> This must be the same value of NB used to generate T
*> in CGEQRT.
*> in SGEQRT.
*> \endverbatim
*>
*> \param[in] V
*> \verbatim
*> V is REAL array, dimension (LDV,K)
*> The i-th column must contain the vector which defines the
*> elementary reflector H(i), for i = 1,2,...,k, as returned by
*> CGEQRT in the first K columns of its array argument A.
*> SGEQRT in the first K columns of its array argument A.
*> \endverbatim
*>
*> \param[in] LDV
Expand All @@ -117,7 +117,7 @@
*> \verbatim
*> T is REAL array, dimension (LDT,K)
*> The upper triangular factors of the block reflectors
*> as returned by CGEQRT, stored as a NB-by-N matrix.
*> as returned by SGEQRT, stored as a NB-by-N matrix.
*> \endverbatim
*>
*> \param[in] LDT
Expand Down
22 changes: 13 additions & 9 deletions SRC/slamtsqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@
*> TRANS = 'T': Q**T * C C * Q**T
*> where Q is a real orthogonal matrix defined as the product
*> of blocked elementary reflectors computed by tall skinny
*> QR factorization (DLATSQR)
*> QR factorization (SLATSQR)
*> \endverbatim
*
* Arguments:
Expand Down Expand Up @@ -72,7 +72,7 @@
*> \verbatim
*> MB is INTEGER
*> The block size to be used in the blocked QR.
*> MB > N. (must be the same as DLATSQR)
*> MB > N. (must be the same as SLATSQR)
*> \endverbatim
*>
*> \param[in] NB
Expand All @@ -87,7 +87,7 @@
*> A is REAL array, dimension (LDA,K)
*> The i-th column must contain the vector which defines the
*> blockedelementary reflector H(i), for i = 1,2,...,k, as
*> returned by DLATSQR in the first k columns of
*> returned by SLATSQR in the first k columns of
*> its array argument A.
*> \endverbatim
*>
Expand Down Expand Up @@ -214,7 +214,7 @@ SUBROUTINE SLAMTSQR( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN, LQUERY
INTEGER I, II, KK, LW, CTR
INTEGER I, II, KK, LW, CTR, Q
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -233,22 +233,26 @@ SUBROUTINE SLAMTSQR( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
RIGHT = LSAME( SIDE, 'R' )
IF (LEFT) THEN
LW = N * NB
Q = M
ELSE
LW = MB * NB
Q = N
END IF
*
INFO = 0
IF( .NOT.LEFT .AND. .NOT.RIGHT ) THEN
INFO = -1
ELSE IF( .NOT.TRAN .AND. .NOT.NOTRAN ) THEN
INFO = -2
ELSE IF( M.LT.0 ) THEN
INFO = -3
ELSE IF( N.LT.0 ) THEN
INFO = -4
ELSE IF( K.LT.0 ) THEN
INFO = -5
ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
ELSE IF( N.LT.K ) THEN
INFO = -4
ELSE IF( M.LT.N ) THEN
INFO = -3
ELSE IF( K.LT.NB .OR. NB.LT.1 ) THEN
INFO = -7
ELSE IF( LDA.LT.MAX( 1, Q ) ) THEN
INFO = -9
ELSE IF( LDT.LT.MAX( 1, NB) ) THEN
INFO = -11
Expand Down
6 changes: 3 additions & 3 deletions SRC/zgemqrt.f
Original file line number Diff line number Diff line change
Expand Up @@ -94,15 +94,15 @@
*> NB is INTEGER
*> The block size used for the storage of T. K >= NB >= 1.
*> This must be the same value of NB used to generate T
*> in CGEQRT.
*> in ZGEQRT.
*> \endverbatim
*>
*> \param[in] V
*> \verbatim
*> V is COMPLEX*16 array, dimension (LDV,K)
*> The i-th column must contain the vector which defines the
*> elementary reflector H(i), for i = 1,2,...,k, as returned by
*> CGEQRT in the first K columns of its array argument A.
*> ZGEQRT in the first K columns of its array argument A.
*> \endverbatim
*>
*> \param[in] LDV
Expand All @@ -117,7 +117,7 @@
*> \verbatim
*> T is COMPLEX*16 array, dimension (LDT,K)
*> The upper triangular factors of the block reflectors
*> as returned by CGEQRT, stored as a NB-by-N matrix.
*> as returned by ZGEQRT, stored as a NB-by-N matrix.
*> \endverbatim
*>
*> \param[in] LDT
Expand Down
20 changes: 12 additions & 8 deletions SRC/zlamtsqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@
*> \verbatim
*> MB is INTEGER
*> The block size to be used in the blocked QR.
*> MB > N. (must be the same as DLATSQR)
*> MB > N. (must be the same as ZLATSQR)
*> \endverbatim
*>
*> \param[in] NB
Expand All @@ -87,7 +87,7 @@
*> A is COMPLEX*16 array, dimension (LDA,K)
*> The i-th column must contain the vector which defines the
*> blockedelementary reflector H(i), for i = 1,2,...,k, as
*> returned by DLATSQR in the first k columns of
*> returned by ZLATSQR in the first k columns of
*> its array argument A.
*> \endverbatim
*>
Expand Down Expand Up @@ -214,7 +214,7 @@ SUBROUTINE ZLAMTSQR( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN, LQUERY
INTEGER I, II, KK, LW, CTR
INTEGER I, II, KK, LW, CTR, Q
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -233,22 +233,26 @@ SUBROUTINE ZLAMTSQR( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
RIGHT = LSAME( SIDE, 'R' )
IF (LEFT) THEN
LW = N * NB
Q = M
ELSE
LW = M * NB
Q = N
END IF
*
INFO = 0
IF( .NOT.LEFT .AND. .NOT.RIGHT ) THEN
INFO = -1
ELSE IF( .NOT.TRAN .AND. .NOT.NOTRAN ) THEN
INFO = -2
ELSE IF( M.LT.0 ) THEN
INFO = -3
ELSE IF( N.LT.0 ) THEN
INFO = -4
ELSE IF( K.LT.0 ) THEN
INFO = -5
ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
ELSE IF( N.LT.K ) THEN
INFO = -4
ELSE IF( M.LT.N ) THEN
INFO = -3
ELSE IF( K.LT.NB .OR. NB.LT.1 ) THEN
INFO = -7
ELSE IF( LDA.LT.MAX( 1, Q ) ) THEN
INFO = -9
ELSE IF( LDT.LT.MAX( 1, NB) ) THEN
INFO = -11
Expand Down

0 comments on commit 201353b

Please sign in to comment.