Skip to content

Commit

Permalink
handle and document corner cases of lwork in lapack, double complex p…
Browse files Browse the repository at this point in the history
…recision
  • Loading branch information
kleineLi committed Nov 30, 2023
1 parent 0f5cc87 commit 4d3d130
Show file tree
Hide file tree
Showing 33 changed files with 278 additions and 169 deletions.
22 changes: 15 additions & 7 deletions SRC/zgebrd.f
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,8 @@
*> \param[in] LWORK
*> \verbatim
*> LWORK is INTEGER
*> The length of the array WORK. LWORK >= max(1,M,N).
*> The length of the array WORK.
*> LWORK >= 1, if MIN(M,N) = 0, and LWORK >= MAX(M,N), otherwise.
*> For optimum performance LWORK >= (M+N)*NB, where NB
*> is the optimal blocksize.
*>
Expand Down Expand Up @@ -223,8 +224,8 @@ SUBROUTINE ZGEBRD( M, N, A, LDA, D, E, TAUQ, TAUP, WORK, LWORK,
* ..
* .. Local Scalars ..
LOGICAL LQUERY
INTEGER I, IINFO, J, LDWRKX, LDWRKY, LWKOPT, MINMN, NB,
$ NBMIN, NX, WS
INTEGER I, IINFO, J, LDWRKX, LDWRKY, LWKMIN, LWKOPT,
$ MINMN, NB, NBMIN, NX, WS
* ..
* .. External Subroutines ..
EXTERNAL XERBLA, ZGEBD2, ZGEMM, ZLABRD
Expand All @@ -241,17 +242,25 @@ SUBROUTINE ZGEBRD( M, N, A, LDA, D, E, TAUQ, TAUP, WORK, LWORK,
* Test the input parameters
*
INFO = 0
NB = MAX( 1, ILAENV( 1, 'ZGEBRD', ' ', M, N, -1, -1 ) )
LWKOPT = ( M+N )*NB
MINMN = MIN( M, N )
IF( MINMN.EQ.0 ) THEN
LWKMIN = 1
LWKOPT = 1

Check warning on line 248 in SRC/zgebrd.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgebrd.f#L245-L248

Added lines #L245 - L248 were not covered by tests
ELSE
LWKMIN = MAX( M, N )
NB = MAX( 1, ILAENV( 1, 'ZGEBRD', ' ', M, N, -1, -1 ) )
LWKOPT = MAX( 1, ( M+N )*NB )

Check warning on line 252 in SRC/zgebrd.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgebrd.f#L250-L252

Added lines #L250 - L252 were not covered by tests
END IF
WORK( 1 ) = DBLE( LWKOPT )
*
LQUERY = ( LWORK.EQ.-1 )
IF( M.LT.0 ) THEN
INFO = -1
ELSE IF( N.LT.0 ) THEN
INFO = -2
ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
INFO = -4
ELSE IF( LWORK.LT.MAX( 1, M, N ) .AND. .NOT.LQUERY ) THEN
ELSE IF( LWORK.LT.LWKMIN .AND. .NOT.LQUERY ) THEN

Check warning on line 263 in SRC/zgebrd.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgebrd.f#L263

Added line #L263 was not covered by tests
INFO = -10
END IF
IF( INFO.LT.0 ) THEN
Expand All @@ -263,7 +272,6 @@ SUBROUTINE ZGEBRD( M, N, A, LDA, D, E, TAUQ, TAUP, WORK, LWORK,
*
* Quick return if possible
*
MINMN = MIN( M, N )
IF( MINMN.EQ.0 ) THEN
WORK( 1 ) = 1
RETURN
Expand Down
11 changes: 8 additions & 3 deletions SRC/zgehrd.f
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@
*>
*> \param[out] WORK
*> \verbatim
*> WORK is COMPLEX*16 array, dimension (LWORK)
*> WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
*> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
*> \endverbatim
*>
Expand Down Expand Up @@ -225,8 +225,13 @@ SUBROUTINE ZGEHRD( N, ILO, IHI, A, LDA, TAU, WORK, LWORK, INFO )
*
* Compute the workspace requirements
*
NB = MIN( NBMAX, ILAENV( 1, 'ZGEHRD', ' ', N, ILO, IHI, -1 ) )
LWKOPT = N*NB + TSIZE
IF( N.EQ.0 ) THEN
LWKOPT = 1

Check warning on line 229 in SRC/zgehrd.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgehrd.f#L228-L229

Added lines #L228 - L229 were not covered by tests
ELSE
NB = MIN( NBMAX, ILAENV( 1, 'ZGEHRD', ' ', N, ILO, IHI,
$ -1 ) )
LWKOPT = N*NB + TSIZE

Check warning on line 233 in SRC/zgehrd.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgehrd.f#L232-L233

Added lines #L232 - L233 were not covered by tests
END IF
WORK( 1 ) = LWKOPT
ENDIF
*
Expand Down
2 changes: 1 addition & 1 deletion SRC/zgelq.f
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@
*> \param[in] LWORK
*> \verbatim
*> LWORK is INTEGER
*> The dimension of the array WORK.
*> The dimension of the array WORK. LWORK >= 1.
*> If LWORK = -1 or -2, then a workspace query is assumed. The routine
*> only calculates the sizes of the T and WORK arrays, returns these
*> values as the first entries of the T and WORK arrays, and no error
Expand Down
16 changes: 11 additions & 5 deletions SRC/zgelqf.f
Original file line number Diff line number Diff line change
Expand Up @@ -93,6 +93,7 @@
*> \param[in] LWORK
*> \verbatim
*> LWORK is INTEGER
*> LWORK >= 1, if MIN(M,N) = 0, and LWORK >= M, otherwise.
*> The dimension of the array WORK. LWORK >= max(1,M).
*> For optimum performance LWORK >= M*NB, where NB is the
*> optimal blocksize.
Expand Down Expand Up @@ -174,29 +175,34 @@ SUBROUTINE ZGELQF( M, N, A, LDA, TAU, WORK, LWORK, INFO )
* Test the input arguments
*
INFO = 0
K = MIN( M, N )

Check warning on line 178 in SRC/zgelqf.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgelqf.f#L178

Added line #L178 was not covered by tests
NB = ILAENV( 1, 'ZGELQF', ' ', M, N, -1, -1 )
LWKOPT = M*NB
WORK( 1 ) = LWKOPT
LQUERY = ( LWORK.EQ.-1 )
IF( M.LT.0 ) THEN
INFO = -1
ELSE IF( N.LT.0 ) THEN
INFO = -2
ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
INFO = -4
ELSE IF( LWORK.LT.MAX( 1, M ) .AND. .NOT.LQUERY ) THEN
INFO = -7
ELSE IF( .NOT.LQUERY ) THEN
IF( LWORK.LE.0 .OR. ( N.GT.0 .AND. LWORK.LT.MAX( 1, M ) ) )
$ INFO = -7

Check warning on line 189 in SRC/zgelqf.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgelqf.f#L187-L189

Added lines #L187 - L189 were not covered by tests
END IF
IF( INFO.NE.0 ) THEN
CALL XERBLA( 'ZGELQF', -INFO )
RETURN
ELSE IF( LQUERY ) THEN
IF( K.EQ.0 ) THEN
LWKOPT = 1

Check warning on line 196 in SRC/zgelqf.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgelqf.f#L195-L196

Added lines #L195 - L196 were not covered by tests
ELSE
LWKOPT = M*NB

Check warning on line 198 in SRC/zgelqf.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgelqf.f#L198

Added line #L198 was not covered by tests
END IF
WORK( 1 ) = LWKOPT

Check warning on line 200 in SRC/zgelqf.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgelqf.f#L200

Added line #L200 was not covered by tests
RETURN
END IF
*
* Quick return if possible
*
K = MIN( M, N )
IF( K.EQ.0 ) THEN
WORK( 1 ) = 1
RETURN
Expand Down
20 changes: 14 additions & 6 deletions SRC/zgemlq.f
Original file line number Diff line number Diff line change
Expand Up @@ -109,13 +109,14 @@
*>
*> \param[out] WORK
*> \verbatim
*> (workspace) COMPLEX*16 array, dimension (MAX(1,LWORK))
*> (workspace) COMPLEX*16 array, dimension (MAX(1,LWORK))
*> On exit, if INFO = 0, WORK(1) returns the minimal LWORK.
*> \endverbatim
*>
*> \param[in] LWORK
*> \verbatim
*> LWORK is INTEGER
*> The dimension of the array WORK.
*> The dimension of the array WORK. LWORK >= 1.
*> If LWORK = -1, then a workspace query is assumed. The routine
*> only calculates the size of the WORK array, returns this
*> value as WORK(1), and no error message related to WORK
Expand Down Expand Up @@ -186,7 +187,7 @@ SUBROUTINE ZGEMLQ( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN, LQUERY
INTEGER MB, NB, LW, NBLCKS, MN
INTEGER MB, NB, LW, NBLCKS, MN, MINMNK, LWMIN
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -202,7 +203,7 @@ SUBROUTINE ZGEMLQ( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
*
* Test the input arguments
*
LQUERY = LWORK.EQ.-1
LQUERY = ( LWORK.EQ.-1 )

Check warning on line 206 in SRC/zgemlq.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgemlq.f#L206

Added line #L206 was not covered by tests
NOTRAN = LSAME( TRANS, 'N' )
TRAN = LSAME( TRANS, 'C' )
LEFT = LSAME( SIDE, 'L' )
Expand All @@ -217,6 +218,13 @@ SUBROUTINE ZGEMLQ( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
LW = M * MB
MN = N
END IF
*
MINMNK = MIN( M, N, K )
IF( MINMNK.EQ.0 ) THEN
LWMIN = 1

Check warning on line 224 in SRC/zgemlq.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgemlq.f#L222-L224

Added lines #L222 - L224 were not covered by tests
ELSE
LWMIN = MAX( 1, LW )

Check warning on line 226 in SRC/zgemlq.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgemlq.f#L226

Added line #L226 was not covered by tests
END IF
*
IF( ( NB.GT.K ) .AND. ( MN.GT.K ) ) THEN
IF( MOD( MN - K, NB - K ) .EQ. 0 ) THEN
Expand Down Expand Up @@ -245,7 +253,7 @@ SUBROUTINE ZGEMLQ( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
INFO = -9
ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
INFO = -11
ELSE IF( ( LWORK.LT.MAX( 1, LW ) ) .AND. ( .NOT.LQUERY ) ) THEN
ELSE IF( ( LWORK.LT.LWMIN ) .AND. ( .NOT.LQUERY ) ) THEN

Check warning on line 256 in SRC/zgemlq.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgemlq.f#L256

Added line #L256 was not covered by tests
INFO = -13
END IF
*
Expand All @@ -262,7 +270,7 @@ SUBROUTINE ZGEMLQ( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
*
* Quick return if possible
*
IF( MIN( M, N, K ).EQ.0 ) THEN
IF( MINMNK.EQ.0 ) THEN

Check warning on line 273 in SRC/zgemlq.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgemlq.f#L273

Added line #L273 was not covered by tests
RETURN
END IF
*
Expand Down
20 changes: 14 additions & 6 deletions SRC/zgemqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -111,13 +111,14 @@
*>
*> \param[out] WORK
*> \verbatim
*> (workspace) COMPLEX*16 array, dimension (MAX(1,LWORK))
*> (workspace) COMPLEX*16 array, dimension (MAX(1,LWORK))
*> On exit, if INFO = 0, WORK(1) returns the minimal LWORK.
*> \endverbatim
*>
*> \param[in] LWORK
*> \verbatim
*> LWORK is INTEGER
*> The dimension of the array WORK.
*> The dimension of the array WORK. LWORK >= 1.
*> If LWORK = -1, then a workspace query is assumed. The routine
*> only calculates the size of the WORK array, returns this
*> value as WORK(1), and no error message related to WORK
Expand Down Expand Up @@ -189,7 +190,7 @@ SUBROUTINE ZGEMQR( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
* ..
* .. Local Scalars ..
LOGICAL LEFT, RIGHT, TRAN, NOTRAN, LQUERY
INTEGER MB, NB, LW, NBLCKS, MN
INTEGER MB, NB, LW, NBLCKS, MN, MINMNK, LWMIN
* ..
* .. External Functions ..
LOGICAL LSAME
Expand All @@ -205,7 +206,7 @@ SUBROUTINE ZGEMQR( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
*
* Test the input arguments
*
LQUERY = LWORK.EQ.-1
LQUERY = ( LWORK.EQ.-1 )

Check warning on line 209 in SRC/zgemqr.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgemqr.f#L209

Added line #L209 was not covered by tests
NOTRAN = LSAME( TRANS, 'N' )
TRAN = LSAME( TRANS, 'C' )
LEFT = LSAME( SIDE, 'L' )
Expand All @@ -220,6 +221,13 @@ SUBROUTINE ZGEMQR( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
LW = MB * NB
MN = N
END IF
*
MINMNK = MIN( M, N, K )
IF( MINMNK.EQ.0 ) THEN
LWMIN = 1

Check warning on line 227 in SRC/zgemqr.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgemqr.f#L225-L227

Added lines #L225 - L227 were not covered by tests
ELSE
LWMIN = MAX( 1, LW )

Check warning on line 229 in SRC/zgemqr.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgemqr.f#L229

Added line #L229 was not covered by tests
END IF
*
IF( ( MB.GT.K ) .AND. ( MN.GT.K ) ) THEN
IF( MOD( MN - K, MB - K ).EQ.0 ) THEN
Expand Down Expand Up @@ -248,7 +256,7 @@ SUBROUTINE ZGEMQR( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
INFO = -9
ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
INFO = -11
ELSE IF( ( LWORK.LT.MAX( 1, LW ) ) .AND. ( .NOT.LQUERY ) ) THEN
ELSE IF( LWORK.LT.LWMIN .AND. .NOT.LQUERY ) THEN

Check warning on line 259 in SRC/zgemqr.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgemqr.f#L259

Added line #L259 was not covered by tests
INFO = -13
END IF
*
Expand All @@ -265,7 +273,7 @@ SUBROUTINE ZGEMQR( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
*
* Quick return if possible
*
IF( MIN( M, N, K ).EQ.0 ) THEN
IF( MINMNK.EQ.0 ) THEN

Check warning on line 276 in SRC/zgemqr.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgemqr.f#L276

Added line #L276 was not covered by tests
RETURN
END IF
*
Expand Down
8 changes: 5 additions & 3 deletions SRC/zgeqlf.f
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,8 @@
*> \param[in] LWORK
*> \verbatim
*> LWORK is INTEGER
*> The dimension of the array WORK. LWORK >= max(1,N).
*> The dimension of the array WORK.
*> LWORK >= 1, if MIN(M,N) = 0, and LWORK >= N, otherwise.
*> For optimum performance LWORK >= N*NB, where NB is
*> the optimal blocksize.
*>
Expand Down Expand Up @@ -188,8 +189,9 @@ SUBROUTINE ZGEQLF( M, N, A, LDA, TAU, WORK, LWORK, INFO )
END IF
WORK( 1 ) = LWKOPT
*
IF( LWORK.LT.MAX( 1, N ) .AND. .NOT.LQUERY ) THEN
INFO = -7
IF( .NOT.LQUERY ) THEN
IF( LWORK.LE.0 .OR. ( M.GT.0 .AND. LWORK.LT.MAX( 1, N ) ) )
$ INFO = -7

Check warning on line 194 in SRC/zgeqlf.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgeqlf.f#L192-L194

Added lines #L192 - L194 were not covered by tests
END IF
END IF
*
Expand Down
3 changes: 2 additions & 1 deletion SRC/zgeqp3rk.f
Original file line number Diff line number Diff line change
Expand Up @@ -428,7 +428,8 @@
*> \verbatim
*> LWORK is INTEGER
*> The dimension of the array WORK.
*. LWORK >= N+NRHS-1
*> LWORK >= 1, if MIN(M,N) = 0, and
*> LWORK >= N+NRHS-1, otherwise.
*> For optimal performance LWORK >= NB*( N+NRHS+1 ),
*> where NB is the optimal block size for ZGEQP3RK returned
*> by ILAENV. Minimal block size MINNB=2.
Expand Down
16 changes: 9 additions & 7 deletions SRC/zgeqr.f
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,7 @@
*> \param[in] LWORK
*> \verbatim
*> LWORK is INTEGER
*> The dimension of the array WORK.
*> The dimension of the array WORK. LWORK >= 1.
*> If LWORK = -1 or -2, then a workspace query is assumed. The routine
*> only calculates the sizes of the T and WORK arrays, returns these
*> values as the first entries of the T and WORK arrays, and no error
Expand Down Expand Up @@ -190,7 +190,7 @@ SUBROUTINE ZGEQR( M, N, A, LDA, T, TSIZE, WORK, LWORK,
* ..
* .. Local Scalars ..
LOGICAL LQUERY, LMINWS, MINT, MINW
INTEGER MB, NB, MINTSZ, NBLCKS
INTEGER MB, NB, MINTSZ, NBLCKS, LWMIN, LWREQ
* ..
* .. External Functions ..
LOGICAL LSAME
Expand Down Expand Up @@ -246,16 +246,18 @@ SUBROUTINE ZGEQR( M, N, A, LDA, T, TSIZE, WORK, LWORK,
*
* Determine if the workspace size satisfies minimal size
*
LWMIN = MAX( 1, N )
LWREQ = MAX( 1, N*NB )

Check warning on line 250 in SRC/zgeqr.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgeqr.f#L249-L250

Added lines #L249 - L250 were not covered by tests
LMINWS = .FALSE.
IF( ( TSIZE.LT.MAX( 1, NB*N*NBLCKS + 5 ) .OR. LWORK.LT.NB*N )
IF( ( TSIZE.LT.MAX( 1, NB*N*NBLCKS + 5 ) .OR. LWORK.LT.LWREQ )
$ .AND. ( LWORK.GE.N ) .AND. ( TSIZE.GE.MINTSZ )
$ .AND. ( .NOT.LQUERY ) ) THEN
IF( TSIZE.LT.MAX( 1, NB*N*NBLCKS + 5 ) ) THEN
LMINWS = .TRUE.
NB = 1
MB = M
END IF
IF( LWORK.LT.NB*N ) THEN
IF( LWORK.LT.LWREQ ) THEN

Check warning on line 260 in SRC/zgeqr.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgeqr.f#L260

Added line #L260 was not covered by tests
LMINWS = .TRUE.
NB = 1
END IF
Expand Down Expand Up @@ -284,9 +286,9 @@ SUBROUTINE ZGEQR( M, N, A, LDA, T, TSIZE, WORK, LWORK,
T( 2 ) = MB
T( 3 ) = NB
IF( MINW ) THEN
WORK( 1 ) = MAX( 1, N )
WORK( 1 ) = LWMIN

Check warning on line 289 in SRC/zgeqr.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgeqr.f#L289

Added line #L289 was not covered by tests
ELSE
WORK( 1 ) = MAX( 1, NB*N )
WORK( 1 ) = LWREQ

Check warning on line 291 in SRC/zgeqr.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgeqr.f#L291

Added line #L291 was not covered by tests
END IF
END IF
IF( INFO.NE.0 ) THEN
Expand All @@ -311,7 +313,7 @@ SUBROUTINE ZGEQR( M, N, A, LDA, T, TSIZE, WORK, LWORK,
$ LWORK, INFO )
END IF
*
WORK( 1 ) = MAX( 1, NB*N )
WORK( 1 ) = LWREQ

Check warning on line 316 in SRC/zgeqr.f

View check run for this annotation

Codecov / codecov/patch

SRC/zgeqr.f#L316

Added line #L316 was not covered by tests
*
RETURN
*
Expand Down
Loading

0 comments on commit 4d3d130

Please sign in to comment.