Skip to content

Commit

Permalink
Enable nvhpc preprocessor via intdroducing JPRC so macro to replace _…
Browse files Browse the repository at this point in the history
…JPRB eg in 0.0_JPRB is not needed. C stands for constant)
  • Loading branch information
piotrows committed Nov 16, 2023
1 parent 428cb68 commit 205d60d
Show file tree
Hide file tree
Showing 31 changed files with 281 additions and 251 deletions.
7 changes: 4 additions & 3 deletions src/programs/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,9 @@ ecbuild_list_add_pattern( LIST driver_src
ectrans-benchmark-data_mod.F90
QUIET
)
set(CMAKE_Fortran_PREPROCESS_SOURCE
"<CMAKE_C_COMPILER> -cpp <DEFINES> <INCLUDES> -E <SOURCE> -o <PREPROCESSED_SOURCE>")
#set(CMAKE_Fortran_PREPROCESS_SOURCE
# "<CMAKE_C_COMPILER> -cpp <DEFINES> <INCLUDES> -E <SOURCE> -o <PREPROCESSED_SOURCE>")
# "gcc -cpp <DEFINES> <INCLUDES> -E <SOURCE> -o <PREPROCESSED_SOURCE>")
# if( HAVE_${prec} )
# if( ${prec} MATCHES "sp" )
# set(precno 1)
Expand Down Expand Up @@ -89,7 +90,7 @@ foreach( prec sp dp )
SOURCES ${driver_src}
PUBLIC_LIBS fiat
PRIVATE_LIBS parkind_${prec} trans_${prec}
PRIVATE_DEFINITIONS SYMBOLSUFFIX=${prec}
PRIVATE_DEFINITIONS SYMBOLSUFFIX=_${prec}
PRECOPT=${precno}

)
Expand Down
13 changes: 7 additions & 6 deletions src/programs/ectrans-benchmark-driver_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
#include "renames.inc"
MODULE transform_driver_mod
use parkind1, only: jpim, jprb, jprd
use parkind1, only: jprc => jprb
use oml_mod ,only : oml_max_threads
use yomgstats, only: jpmaxstat
use yomhook, only : dr_hook_init
Expand Down Expand Up @@ -429,22 +430,22 @@ SUBROUTINE ectrans_print_norms_calc(nout,jstep,myproc,nflevg)
do ifld = 1, 1
write(nout,*) "znormsp", znormsp
call flush(nout)
zerr(1) = abs(znormsp1(ifld)/znormsp(ifld) - 1.0_jprb)
zerr(1) = abs(znormsp1(ifld)/znormsp(ifld) - 1.0_jprc)
zmaxerr(1) = max(zmaxerr(1), zerr(1))
enddo
! Divergence
do ifld = 1, nflevg
zerr(2) = abs(znormdiv1(ifld)/znormdiv(ifld) - 1.0_jprb)
zerr(2) = abs(znormdiv1(ifld)/znormdiv(ifld) - 1.0_jprc)
zmaxerr(2) = max(zmaxerr(2), zerr(2))
enddo
! Vorticity
do ifld = 1, nflevg
zerr(3) = abs(znormvor1(ifld)/znormvor(ifld) - 1.0_jprb)
zerr(3) = abs(znormvor1(ifld)/znormvor(ifld) - 1.0_jprc)
zmaxerr(3) = max(zmaxerr(3),zerr(3))
enddo
! Temperature
do ifld = 1, nflevg
zerr(4) = abs(znormt1(ifld)/znormt(ifld) - 1.0_jprb)
zerr(4) = abs(znormt1(ifld)/znormt(ifld) - 1.0_jprc)
zmaxerr(4) = max(zmaxerr(4), zerr(4))
enddo
write(nout,'("time step ",i6," took", f8.4," | zspvor max err="e10.3,&
Expand Down Expand Up @@ -511,11 +512,11 @@ FUNCTION ectrans_print_norms_fails(nout,ncheck) result (ierr)
integer(kind=jpim), intent(in) :: nout,ncheck
integer(kind=jpim) :: ierr
ierr = 0
if (zmaxerrg > real(ncheck, jprb) * epsilon(1.0_jprb)) then
if (zmaxerrg > real(ncheck, jprb) * epsilon(1.0_jprc)) then
write(nout, '(a)') '*******************************'
write(nout, '(a)') 'Correctness test failed'
write(nout, '(a,1e7.2)') 'Maximum spectral norm error = ', zmaxerrg
write(nout, '(a,1e7.2)') 'Error tolerance = ', real(ncheck, jprb) * epsilon(1.0_jprb)
write(nout, '(a,1e7.2)') 'Error tolerance = ', real(ncheck, jprb) * epsilon(1.0_jprc)
write(nout, '(a)') '*******************************'
ierr = 1
endif
Expand Down
6 changes: 3 additions & 3 deletions src/trans/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,8 @@ ecbuild_list_add_pattern( LIST trans_src
if( NOT HAVE_FFTW )
ecbuild_list_exclude_pattern( LIST trans_src REGEX tpm_fftw.F90 )
endif()
set(CMAKE_Fortran_PREPROCESS_SOURCE
"<CMAKE_C_COMPILER> -cpp <DEFINES> <INCLUDES> -E <SOURCE> -o <PREPROCESSED_SOURCE>")
#set(CMAKE_Fortran_PREPROCESS_SOURCE
# "<CMAKE_C_COMPILER> -cpp <DEFINES> <INCLUDES> -E <SOURCE> -o <PREPROCESSED_SOURCE>")

foreach( prec dp sp )
if( HAVE_${prec} )
Expand All @@ -69,7 +69,7 @@ foreach( prec dp sp )
$<INSTALL_INTERFACE:include/ectrans>
$<INSTALL_INTERFACE:include>
PRIVATE_INCLUDES ${PROJECT_SOURCE_DIR}/src/trans/external
PRIVATE_DEFINITIONS SYMBOLSUFFIX=${prec}
PRIVATE_DEFINITIONS SYMBOLSUFFIX=_${prec}
PRECOPT=${precno}
PUBLIC_LIBS fiat parkind_${prec}
)
Expand Down
14 changes: 7 additions & 7 deletions src/trans/algor/bluestein_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@
! granted to it by virtue of its status as an intergovernmental organisation
! nor does it submit to any jurisdiction.
!

MODULE BLUESTEIN_MOD

! Implementation of the Bluestein FFT algorithm as described in a paper titled
Expand All @@ -19,6 +18,7 @@ MODULE BLUESTEIN_MOD
! The naming convention follows the algorithm description in the above paper.
!
USE PARKIND1, ONLY : JPIM, JPRB
USE PARKIND1, ONLY : JPRC => JPRB

IMPLICIT NONE

Expand Down Expand Up @@ -98,7 +98,7 @@ SUBROUTINE BLUESTEIN_FFT(TB,N,KSIGN,KLOT,PDAT)
ZDATAI(JLOT,K)=PDAT(JLOT,K*2+2)
ZDATAI(JLOT,N-K) = -PDAT(JLOT,K*2+2)
ENDDO
ZDATAI(JLOT,0)=0._JPRB
ZDATAI(JLOT,0)=0._JPRC
ENDDO

ENDIF
Expand Down Expand Up @@ -138,7 +138,7 @@ SUBROUTINE BLUESTEIN_FFT(TB,N,KSIGN,KLOT,PDAT)
! zero padding of Y

DO I=N,(M/2+1)*2
ZY(:,I) = 0._JPRB
ZY(:,I) = 0._JPRC
ENDDO

! FFT of Y
Expand Down Expand Up @@ -322,8 +322,8 @@ SUBROUTINE BLUESTEIN_INIT(TB)
ENDDO

DO K=0,(M/2+1)*2
TB%FFTB(N)%H2xT(1,K,ISIGN) = 0._JPRB
TB%FFTB(N)%H2xT(2,K,ISIGN) = 0._JPRB
TB%FFTB(N)%H2xT(1,K,ISIGN) = 0._JPRC
TB%FFTB(N)%H2xT(2,K,ISIGN) = 0._JPRC
ENDDO
TB%FFTB(N)%H2xT(1,0,ISIGN) = TB%FFTB(N)%HS(1,0,ISIGN)
TB%FFTB(N)%H2xT(2,0,ISIGN) = TB%FFTB(N)%HS(2,0,ISIGN)
Expand All @@ -336,8 +336,8 @@ SUBROUTINE BLUESTEIN_INIT(TB)
ENDDO
IF( M > 2*N-2 ) THEN
DO K=N,M-N+1
TB%FFTB(N)%H2xT(1,K,ISIGN) = 0._JPRB
TB%FFTB(N)%H2xT(2,K,ISIGN) = 0._JPRB
TB%FFTB(N)%H2xT(1,K,ISIGN) = 0._JPRC
TB%FFTB(N)%H2xT(2,K,ISIGN) = 0._JPRC
ENDDO
ENDIF

Expand Down
Loading

0 comments on commit 205d60d

Please sign in to comment.