Skip to content

Commit

Permalink
Fix leading dimension check
Browse files Browse the repository at this point in the history
* TPMLQT, GEMLQT: Revert check of ldv and correct docs
* Add input parameter checks for LASWLQ
* LAMSWLQ: Fix mixed up column count of rhs (n) and original matrix (m)
  • Loading branch information
angsch committed Apr 3, 2022
1 parent 11d3fa9 commit c137eb1
Show file tree
Hide file tree
Showing 20 changed files with 176 additions and 92 deletions.
6 changes: 2 additions & 4 deletions SRC/cgemlqt.f
Original file line number Diff line number Diff line change
Expand Up @@ -95,9 +95,7 @@
*> \param[in] LDV
*> \verbatim
*> LDV is INTEGER
*> The leading dimension of the array V.
*> If SIDE = 'L', M >= K >= 0;
*> if SIDE = 'R', N >= K >= 0.
*> The leading dimension of the array V. LDV >= max(1,K).
*> \endverbatim
*>
*> \param[in] T
Expand Down Expand Up @@ -211,7 +209,7 @@ SUBROUTINE CGEMLQT( SIDE, TRANS, M, N, K, MB, V, LDV, T, LDT,
INFO = -5
ELSE IF( MB.LT.1 .OR. (MB.GT.K .AND. K.GT.0)) THEN
INFO = -6
ELSE IF( LDV.LT.MAX( 1, Q ) ) THEN
ELSE IF( LDV.LT.MAX( 1, K ) ) THEN
INFO = -8
ELSE IF( LDT.LT.MB ) THEN
INFO = -10
Expand Down
14 changes: 5 additions & 9 deletions SRC/clamswlq.f
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@
*> \param[in] N
*> \verbatim
*> N is INTEGER
*> The number of columns of the matrix C. N >= M.
*> The number of columns of the matrix C. N >= 0.
*> \endverbatim
*>
*> \param[in] K
Expand Down Expand Up @@ -94,9 +94,7 @@
*> \param[in] LDA
*> \verbatim
*> LDA is INTEGER
*> The leading dimension of the array A.
*> If SIDE = 'L', LDA >= max(1,M);
*> if SIDE = 'R', LDA >= max(1,N).
*> The leading dimension of the array A. LDA => max(1,K).
*> \endverbatim
*>
*> \param[in] T
Expand Down Expand Up @@ -213,7 +211,7 @@ SUBROUTINE CLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN, LQUERY
INTEGER I, II, KK, LW, CTR, Q
INTEGER I, II, KK, LW, CTR
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -232,10 +230,8 @@ SUBROUTINE CLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
RIGHT = LSAME( SIDE, 'R' )
IF (LEFT) THEN
LW = N * MB
Q = M
ELSE
LW = M * MB
Q = N
END IF
*
INFO = 0
Expand All @@ -247,11 +243,11 @@ SUBROUTINE CLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
INFO = -5
ELSE IF( M.LT.K ) THEN
INFO = -3
ELSE IF( N.LT.M ) THEN
ELSE IF( N.LT.0 ) THEN
INFO = -4
ELSE IF( K.LT.MB .OR. MB.LT.1) THEN
INFO = -6
ELSE IF( LDA.LT.MAX( 1, Q ) ) THEN
ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
INFO = -9
ELSE IF( LDT.LT.MAX( 1, MB) ) THEN
INFO = -11
Expand Down
6 changes: 3 additions & 3 deletions SRC/claswlq.f
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@
*> \verbatim
*> NB is INTEGER
*> The column block size to be used in the blocked QR.
*> NB > M.
*> NB > 0.
*> \endverbatim
*>
*> \param[in,out] A
Expand Down Expand Up @@ -206,10 +206,10 @@ SUBROUTINE CLASWLQ( M, N, MB, NB, A, LDA, T, LDT, WORK, LWORK,
INFO = -2
ELSE IF( MB.LT.1 .OR. ( MB.GT.M .AND. M.GT.0 )) THEN
INFO = -3
ELSE IF( NB.LE.M ) THEN
ELSE IF( NB.LE.0 ) THEN
INFO = -4
ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
INFO = -5
INFO = -6
ELSE IF( LDT.LT.MB ) THEN
INFO = -8
ELSE IF( ( LWORK.LT.M*MB) .AND. (.NOT.LQUERY) ) THEN
Expand Down
10 changes: 3 additions & 7 deletions SRC/ctpmlqt.f
Original file line number Diff line number Diff line change
Expand Up @@ -88,9 +88,7 @@
*> \param[in] LDV
*> \verbatim
*> LDV is INTEGER
*> The leading dimension of the array V.
*> If SIDE = 'L', LDV >= max(1,M);
*> if SIDE = 'R', LDV >= max(1,N).
*> The leading dimension of the array V. LDV >= K.
*> \endverbatim
*>
*> \param[in] T
Expand Down Expand Up @@ -217,7 +215,7 @@ SUBROUTINE CTPMLQT( SIDE, TRANS, M, N, K, L, MB, V, LDV, T, LDT,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN
INTEGER I, IB, NB, LB, KF, LDAQ, LDVQ
INTEGER I, IB, NB, LB, KF, LDAQ
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -240,10 +238,8 @@ SUBROUTINE CTPMLQT( SIDE, TRANS, M, N, K, L, MB, V, LDV, T, LDT,
NOTRAN = LSAME( TRANS, 'N' )
*
IF ( LEFT ) THEN
LDVQ = MAX( 1, M )
LDAQ = MAX( 1, K )
ELSE IF ( RIGHT ) THEN
LDVQ = MAX( 1, N )
LDAQ = MAX( 1, M )
END IF
IF( .NOT.LEFT .AND. .NOT.RIGHT ) THEN
Expand All @@ -260,7 +256,7 @@ SUBROUTINE CTPMLQT( SIDE, TRANS, M, N, K, L, MB, V, LDV, T, LDT,
INFO = -6
ELSE IF( MB.LT.1 .OR. (MB.GT.K .AND. K.GT.0) ) THEN
INFO = -7
ELSE IF( LDV.LT.LDVQ ) THEN
ELSE IF( LDV.LT.K ) THEN
INFO = -9
ELSE IF( LDT.LT.MB ) THEN
INFO = -11
Expand Down
6 changes: 2 additions & 4 deletions SRC/dgemlqt.f
Original file line number Diff line number Diff line change
Expand Up @@ -110,9 +110,7 @@
*> \param[in] LDV
*> \verbatim
*> LDV is INTEGER
*> The leading dimension of the array V.
*> If SIDE = 'L', LDV >= max(1,M);
*> if SIDE = 'R', LDV >= max(1,N).
*> The leading dimension of the array V. LDV >= max(1,K).
*> \endverbatim
*>
*> \param[in] T
Expand Down Expand Up @@ -226,7 +224,7 @@ SUBROUTINE DGEMLQT( SIDE, TRANS, M, N, K, MB, V, LDV, T, LDT,
INFO = -5
ELSE IF( MB.LT.1 .OR. (MB.GT.K .AND. K.GT.0)) THEN
INFO = -6
ELSE IF( LDV.LT.MAX( 1, Q ) ) THEN
ELSE IF( LDV.LT.MAX( 1, K ) ) THEN
INFO = -8
ELSE IF( LDT.LT.MB ) THEN
INFO = -10
Expand Down
14 changes: 5 additions & 9 deletions SRC/dlamswlq.f
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@
*> \param[in] N
*> \verbatim
*> N is INTEGER
*> The number of columns of the matrix C. N >= M.
*> The number of columns of the matrix C. N >= 0.
*> \endverbatim
*>
*> \param[in] K
Expand Down Expand Up @@ -94,9 +94,7 @@
*> \param[in] LDA
*> \verbatim
*> LDA is INTEGER
*> The leading dimension of the array A.
*> If SIDE = 'L', LDA >= max(1,M);
*> if SIDE = 'R', LDA >= max(1,N).
*> The leading dimension of the array A. LDA >= max(1,K).
*> \endverbatim
*>
*> \param[in] T
Expand Down Expand Up @@ -213,7 +211,7 @@ SUBROUTINE DLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN, LQUERY
INTEGER I, II, KK, CTR, LW, Q
INTEGER I, II, KK, CTR, LW
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -232,10 +230,8 @@ SUBROUTINE DLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
RIGHT = LSAME( SIDE, 'R' )
IF (LEFT) THEN
LW = N * MB
Q = M
ELSE
LW = M * MB
Q = N
END IF
*
INFO = 0
Expand All @@ -247,11 +243,11 @@ SUBROUTINE DLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
INFO = -5
ELSE IF( M.LT.K ) THEN
INFO = -3
ELSE IF( N.LT.M ) THEN
ELSE IF( N.LT.0 ) THEN
INFO = -4
ELSE IF( K.LT.MB .OR. MB.LT.1) THEN
INFO = -6
ELSE IF( LDA.LT.MAX( 1, Q ) ) THEN
ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
INFO = -9
ELSE IF( LDT.LT.MAX( 1, MB) ) THEN
INFO = -11
Expand Down
6 changes: 3 additions & 3 deletions SRC/dlaswlq.f
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@
*> \verbatim
*> NB is INTEGER
*> The column block size to be used in the blocked QR.
*> NB > M.
*> NB > 0.
*> \endverbatim
*>
*> \param[in,out] A
Expand Down Expand Up @@ -202,10 +202,10 @@ SUBROUTINE DLASWLQ( M, N, MB, NB, A, LDA, T, LDT, WORK, LWORK,
INFO = -2
ELSE IF( MB.LT.1 .OR. ( MB.GT.M .AND. M.GT.0 )) THEN
INFO = -3
ELSE IF( NB.LE.M ) THEN
ELSE IF( NB.LT.0 ) THEN
INFO = -4
ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
INFO = -5
INFO = -6
ELSE IF( LDT.LT.MB ) THEN
INFO = -8
ELSE IF( ( LWORK.LT.M*MB) .AND. (.NOT.LQUERY) ) THEN
Expand Down
10 changes: 3 additions & 7 deletions SRC/dtpmlqt.f
Original file line number Diff line number Diff line change
Expand Up @@ -103,9 +103,7 @@
*> \param[in] LDV
*> \verbatim
*> LDV is INTEGER
*> The leading dimension of the array V.
*> If SIDE = 'L', LDV >= max(1,M);
*> if SIDE = 'R', LDV >= max(1,N).
*> The leading dimension of the array V. LDV >= K.
*> \endverbatim
*>
*> \param[in] T
Expand Down Expand Up @@ -232,7 +230,7 @@ SUBROUTINE DTPMLQT( SIDE, TRANS, M, N, K, L, MB, V, LDV, T, LDT,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN
INTEGER I, IB, NB, LB, KF, LDAQ, LDVQ
INTEGER I, IB, NB, LB, KF, LDAQ
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -255,10 +253,8 @@ SUBROUTINE DTPMLQT( SIDE, TRANS, M, N, K, L, MB, V, LDV, T, LDT,
NOTRAN = LSAME( TRANS, 'N' )
*
IF ( LEFT ) THEN
LDVQ = MAX( 1, M )
LDAQ = MAX( 1, K )
ELSE IF ( RIGHT ) THEN
LDVQ = MAX( 1, N )
LDAQ = MAX( 1, M )
END IF
IF( .NOT.LEFT .AND. .NOT.RIGHT ) THEN
Expand All @@ -275,7 +271,7 @@ SUBROUTINE DTPMLQT( SIDE, TRANS, M, N, K, L, MB, V, LDV, T, LDT,
INFO = -6
ELSE IF( MB.LT.1 .OR. (MB.GT.K .AND. K.GT.0) ) THEN
INFO = -7
ELSE IF( LDV.LT.LDVQ ) THEN
ELSE IF( LDV.LT.K ) THEN
INFO = -9
ELSE IF( LDT.LT.MB ) THEN
INFO = -11
Expand Down
6 changes: 2 additions & 4 deletions SRC/sgemlqt.f
Original file line number Diff line number Diff line change
Expand Up @@ -95,9 +95,7 @@
*> \param[in] LDV
*> \verbatim
*> LDV is INTEGER
*> The leading dimension of the array V.
*> If SIDE = 'L', LDV >= max(1,M);
*> if SIDE = 'R', LDV >= max(1,N).
*> The leading dimension of the array V. LDV >= max(1,K).
*> \endverbatim
*>
*> \param[in] T
Expand Down Expand Up @@ -211,7 +209,7 @@ SUBROUTINE SGEMLQT( SIDE, TRANS, M, N, K, MB, V, LDV, T, LDT,
INFO = -5
ELSE IF( MB.LT.1 .OR. (MB.GT.K .AND. K.GT.0)) THEN
INFO = -6
ELSE IF( LDV.LT.MAX( 1, Q ) ) THEN
ELSE IF( LDV.LT.MAX( 1, K ) ) THEN
INFO = -8
ELSE IF( LDT.LT.MB ) THEN
INFO = -10
Expand Down
14 changes: 5 additions & 9 deletions SRC/slamswlq.f
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@
*> \param[in] N
*> \verbatim
*> N is INTEGER
*> The number of columns of the matrix C. N >= M.
*> The number of columns of the matrix C. N >= 0.
*> \endverbatim
*>
*> \param[in] K
Expand Down Expand Up @@ -94,9 +94,7 @@
*> \param[in] LDA
*> \verbatim
*> LDA is INTEGER
*> The leading dimension of the array A.
*> If SIDE = 'L', LDA >= max(1,M);
*> if SIDE = 'R', LDA >= max(1,N).
*> The leading dimension of the array A. LDA >= max(1,K).
*> \endverbatim
*>
*> \param[in] T
Expand Down Expand Up @@ -213,7 +211,7 @@ SUBROUTINE SLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN, LQUERY
INTEGER I, II, KK, LW, CTR, Q
INTEGER I, II, KK, LW, CTR
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -232,10 +230,8 @@ SUBROUTINE SLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
RIGHT = LSAME( SIDE, 'R' )
IF (LEFT) THEN
LW = N * MB
Q = M
ELSE
LW = M * MB
Q = N
END IF
*
INFO = 0
Expand All @@ -247,11 +243,11 @@ SUBROUTINE SLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
INFO = -5
ELSE IF( M.LT.K ) THEN
INFO = -3
ELSE IF( N.LT.M ) THEN
ELSE IF( N.LT.0 ) THEN
INFO = -4
ELSE IF( K.LT.MB .OR. MB.LT.1) THEN
INFO = -6
ELSE IF( LDA.LT.MAX( 1, Q ) ) THEN
ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
INFO = -9
ELSE IF( LDT.LT.MAX( 1, MB) ) THEN
INFO = -11
Expand Down
6 changes: 3 additions & 3 deletions SRC/slaswlq.f
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@
*> \verbatim
*> NB is INTEGER
*> The column block size to be used in the blocked QR.
*> NB > M.
*> NB > 0.
*> \endverbatim
*>
*> \param[in,out] A
Expand Down Expand Up @@ -202,10 +202,10 @@ SUBROUTINE SLASWLQ( M, N, MB, NB, A, LDA, T, LDT, WORK, LWORK,
INFO = -2
ELSE IF( MB.LT.1 .OR. ( MB.GT.M .AND. M.GT.0 )) THEN
INFO = -3
ELSE IF( NB.LE.M ) THEN
ELSE IF( NB.LE.0 ) THEN
INFO = -4
ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
INFO = -5
INFO = -6
ELSE IF( LDT.LT.MB ) THEN
INFO = -8
ELSE IF( ( LWORK.LT.M*MB) .AND. (.NOT.LQUERY) ) THEN
Expand Down
Loading

0 comments on commit c137eb1

Please sign in to comment.