Skip to content

Commit

Permalink
Replace SCEIL with CEILING intrinsic (Reference-LAPACK PR 847)
Browse files Browse the repository at this point in the history
  • Loading branch information
martin-frbg committed Jun 18, 2023
1 parent f330f86 commit f524594
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 26 deletions.
13 changes: 6 additions & 7 deletions lapack-netlib/SRC/VARIANTS/qr/LL/cgeqrf.f
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@
C>\details \b Purpose:
C>\verbatim
C>
C> CGEQRF computes a QR factorization of a real M-by-N matrix A:
C> CGEQRF computes a QR factorization of a complex M-by-N matrix A:
C> A = Q * R.
C>
C> This is the left-looking Level 3 BLAS version of the algorithm.
Expand Down Expand Up @@ -172,12 +172,11 @@ SUBROUTINE CGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )
EXTERNAL CGEQR2, CLARFB, CLARFT, XERBLA
* ..
* .. Intrinsic Functions ..
INTRINSIC MAX, MIN
INTRINSIC CEILING, MAX, MIN, REAL
* ..
* .. External Functions ..
INTEGER ILAENV
REAL SCEIL
EXTERNAL ILAENV, SCEIL
EXTERNAL ILAENV
* ..
* .. Executable Statements ..

Expand Down Expand Up @@ -205,13 +204,13 @@ SUBROUTINE CGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )
*
* So here 4 x 4 is the last T stored in the workspace
*
NT = K-SCEIL(REAL(K-NX)/REAL(NB))*NB
NT = K-CEILING(REAL(K-NX)/REAL(NB))*NB

*
* optimal workspace = space for dlarfb + space for normal T's + space for the last T
*
LLWORK = MAX (MAX((N-M)*K, (N-M)*NB), MAX(K*NB, NB*NB))
LLWORK = SCEIL(REAL(LLWORK)/REAL(NB))
LLWORK = CEILING(REAL(LLWORK)/REAL(NB))

IF( K.EQ.0 ) THEN

Expand All @@ -230,7 +229,7 @@ SUBROUTINE CGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )

ELSE

LBWORK = SCEIL(REAL(K)/REAL(NB))*NB
LBWORK = CEILING(REAL(K)/REAL(NB))*NB
LWKOPT = (LBWORK+LLWORK-NB)*NB
WORK( 1 ) = LWKOPT

Expand Down
11 changes: 5 additions & 6 deletions lapack-netlib/SRC/VARIANTS/qr/LL/dgeqrf.f
Original file line number Diff line number Diff line change
Expand Up @@ -172,12 +172,11 @@ SUBROUTINE DGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )
EXTERNAL DGEQR2, DLARFB, DLARFT, XERBLA
* ..
* .. Intrinsic Functions ..
INTRINSIC MAX, MIN
INTRINSIC CEILING, MAX, MIN, REAL
* ..
* .. External Functions ..
INTEGER ILAENV
REAL SCEIL
EXTERNAL ILAENV, SCEIL
EXTERNAL ILAENV
* ..
* .. Executable Statements ..

Expand Down Expand Up @@ -205,13 +204,13 @@ SUBROUTINE DGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )
*
* So here 4 x 4 is the last T stored in the workspace
*
NT = K-SCEIL(REAL(K-NX)/REAL(NB))*NB
NT = K-CEILING(REAL(K-NX)/REAL(NB))*NB

*
* optimal workspace = space for dlarfb + space for normal T's + space for the last T
*
LLWORK = MAX (MAX((N-M)*K, (N-M)*NB), MAX(K*NB, NB*NB))
LLWORK = SCEIL(REAL(LLWORK)/REAL(NB))
LLWORK = CEILING(REAL(LLWORK)/REAL(NB))

IF( K.EQ.0 ) THEN

Expand All @@ -230,7 +229,7 @@ SUBROUTINE DGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )

ELSE

LBWORK = SCEIL(REAL(K)/REAL(NB))*NB
LBWORK = CEILING(REAL(K)/REAL(NB))*NB
LWKOPT = (LBWORK+LLWORK-NB)*NB
WORK( 1 ) = LWKOPT

Expand Down
11 changes: 5 additions & 6 deletions lapack-netlib/SRC/VARIANTS/qr/LL/sgeqrf.f
Original file line number Diff line number Diff line change
Expand Up @@ -172,12 +172,11 @@ SUBROUTINE SGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )
EXTERNAL SGEQR2, SLARFB, SLARFT, XERBLA
* ..
* .. Intrinsic Functions ..
INTRINSIC MAX, MIN
INTRINSIC CEILING, MAX, MIN, REAL
* ..
* .. External Functions ..
INTEGER ILAENV
REAL SCEIL
EXTERNAL ILAENV, SCEIL
EXTERNAL ILAENV
* ..
* .. Executable Statements ..

Expand Down Expand Up @@ -205,13 +204,13 @@ SUBROUTINE SGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )
*
* So here 4 x 4 is the last T stored in the workspace
*
NT = K-SCEIL(REAL(K-NX)/REAL(NB))*NB
NT = K-CEILING(REAL(K-NX)/REAL(NB))*NB

*
* optimal workspace = space for dlarfb + space for normal T's + space for the last T
*
LLWORK = MAX (MAX((N-M)*K, (N-M)*NB), MAX(K*NB, NB*NB))
LLWORK = SCEIL(REAL(LLWORK)/REAL(NB))
LLWORK = CEILING(REAL(LLWORK)/REAL(NB))

IF( K.EQ.0 ) THEN

Expand All @@ -230,7 +229,7 @@ SUBROUTINE SGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )

ELSE

LBWORK = SCEIL(REAL(K)/REAL(NB))*NB
LBWORK = CEILING(REAL(K)/REAL(NB))*NB
LWKOPT = (LBWORK+LLWORK-NB)*NB
WORK( 1 ) = LWKOPT

Expand Down
13 changes: 6 additions & 7 deletions lapack-netlib/SRC/VARIANTS/qr/LL/zgeqrf.f
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@
C>\details \b Purpose:
C>\verbatim
C>
C> ZGEQRF computes a QR factorization of a real M-by-N matrix A:
C> ZGEQRF computes a QR factorization of a complex M-by-N matrix A:
C> A = Q * R.
C>
C> This is the left-looking Level 3 BLAS version of the algorithm.
Expand Down Expand Up @@ -172,12 +172,11 @@ SUBROUTINE ZGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )
EXTERNAL ZGEQR2, ZLARFB, ZLARFT, XERBLA
* ..
* .. Intrinsic Functions ..
INTRINSIC MAX, MIN
INTRINSIC CEILING, MAX, MIN, REAL
* ..
* .. External Functions ..
INTEGER ILAENV
REAL SCEIL
EXTERNAL ILAENV, SCEIL
EXTERNAL ILAENV
* ..
* .. Executable Statements ..

Expand Down Expand Up @@ -205,13 +204,13 @@ SUBROUTINE ZGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )
*
* So here 4 x 4 is the last T stored in the workspace
*
NT = K-SCEIL(REAL(K-NX)/REAL(NB))*NB
NT = K-CEILING(REAL(K-NX)/REAL(NB))*NB

*
* optimal workspace = space for dlarfb + space for normal T's + space for the last T
*
LLWORK = MAX (MAX((N-M)*K, (N-M)*NB), MAX(K*NB, NB*NB))
LLWORK = SCEIL(REAL(LLWORK)/REAL(NB))
LLWORK = CEILING(REAL(LLWORK)/REAL(NB))

IF( K.EQ.0 ) THEN

Expand All @@ -230,7 +229,7 @@ SUBROUTINE ZGEQRF ( M, N, A, LDA, TAU, WORK, LWORK, INFO )

ELSE

LBWORK = SCEIL(REAL(K)/REAL(NB))*NB
LBWORK = CEILING(REAL(K)/REAL(NB))*NB
LWKOPT = (LBWORK+LLWORK-NB)*NB
WORK( 1 ) = LWKOPT

Expand Down

0 comments on commit f524594

Please sign in to comment.