Skip to content

Commit

Permalink
S. Riette 26 Apr 2024: GPU run without limiting the number of gangs
Browse files Browse the repository at this point in the history
  • Loading branch information
SebastienRietteMTO committed Apr 26, 2024
1 parent 9173882 commit bd155da
Show file tree
Hide file tree
Showing 5 changed files with 21 additions and 13 deletions.
13 changes: 7 additions & 6 deletions src/common/turb/mode_mf_turb.F90
Original file line number Diff line number Diff line change
Expand Up @@ -126,6 +126,7 @@ SUBROUTINE MF_TURB(D, KSV, OMIXUV, &
!

REAL, DIMENSION(D%NIJT,D%NKT) :: ZVARS
REAL, DIMENSION(D%NIJT,D%NKT) :: ZMEMF !-PEMF
INTEGER :: JSV !number of scalar variables and Loop counter
INTEGER :: JIJ, JK
INTEGER :: IIJB,IIJE ! physical horizontal domain indices
Expand All @@ -145,7 +146,7 @@ SUBROUTINE MF_TURB(D, KSV, OMIXUV, &
!
PFLXZSVMF(:,:,:) = 0.
PSVDT(:,:,:) = 0.

ZMEMF(:,:) = -PEMF(:,:)
!
!----------------------------------------------------------------------------
!
Expand Down Expand Up @@ -191,7 +192,7 @@ SUBROUTINE MF_TURB(D, KSV, OMIXUV, &
! 3.1 Compute the tendency for the conservative potential temperature
! (PDZZ and flux in w-point and PRHODJ is mass point, result in mass point)
!
CALL TRIDIAG_MASSFLUX(D,PTHLM,PFLXZTHMF,-PEMF,PTSTEP,PIMPL, &
CALL TRIDIAG_MASSFLUX(D,PTHLM,PFLXZTHMF,ZMEMF,PTSTEP,PIMPL, &
PDZZ,PRHODJ,ZVARS )
! compute new flux and THL tendency
CALL MZM_MF(D, ZVARS(:,:), PFLXZTHMF(:,:))
Expand All @@ -203,7 +204,7 @@ SUBROUTINE MF_TURB(D, KSV, OMIXUV, &
!
! 3.2 Compute the tendency for the conservative mixing ratio
!
CALL TRIDIAG_MASSFLUX(D,PRTM(:,:),PFLXZRMF,-PEMF,PTSTEP,PIMPL, &
CALL TRIDIAG_MASSFLUX(D,PRTM(:,:),PFLXZRMF,ZMEMF,PTSTEP,PIMPL, &
PDZZ,PRHODJ,ZVARS )
! compute new flux and RT tendency
CALL MZM_MF(D, ZVARS(:,:), PFLXZRMF(:,:))
Expand All @@ -219,7 +220,7 @@ SUBROUTINE MF_TURB(D, KSV, OMIXUV, &
! (PDZZ and flux in w-point and PRHODJ is mass point, result in mass point)
!

CALL TRIDIAG_MASSFLUX(D,PUM,PFLXZUMF,-PEMF,PTSTEP,PIMPL, &
CALL TRIDIAG_MASSFLUX(D,PUM,PFLXZUMF,ZMEMF,PTSTEP,PIMPL, &
PDZZ,PRHODJ,ZVARS )
! compute new flux and U tendency
CALL MZM_MF(D, ZVARS(:,:), PFLXZUMF(:,:))
Expand All @@ -233,7 +234,7 @@ SUBROUTINE MF_TURB(D, KSV, OMIXUV, &
! meridian momentum
! (PDZZ and flux in w-point and PRHODJ is mass point, result in mass point)
!
CALL TRIDIAG_MASSFLUX(D,PVM,PFLXZVMF,-PEMF,PTSTEP,PIMPL, &
CALL TRIDIAG_MASSFLUX(D,PVM,PFLXZVMF,ZMEMF,PTSTEP,PIMPL, &
PDZZ,PRHODJ,ZVARS )
! compute new flux and V tendency
CALL MZM_MF(D, ZVARS(:,:), PFLXZVMF(:,:))
Expand Down Expand Up @@ -263,7 +264,7 @@ SUBROUTINE MF_TURB(D, KSV, OMIXUV, &
! (PDZZ and flux in w-point and PRHODJ is mass point, result in mass point)
!
CALL TRIDIAG_MASSFLUX(D,PSVM(:,:,JSV),PFLXZSVMF(:,:,JSV),&
-PEMF,PTSTEP,PIMPL,PDZZ,PRHODJ,ZVARS )
ZMEMF,PTSTEP,PIMPL,PDZZ,PRHODJ,ZVARS )
! compute new flux and Sv tendency
CALL MZM_MF(D, ZVARS, PFLXZSVMF(:,:,JSV))
!$mnh_expand_array(JIJ=IIJB:IIJE,JK=1:IKT)
Expand Down
5 changes: 4 additions & 1 deletion src/common/turb/mode_prandtl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1090,7 +1090,10 @@ SUBROUTINE D_PHI3DTDZ2_O_DDTDZ(D,CSTURB,TURBN,PPHI3,PREDTH1,PREDR1,PRED2TH3,PRED
END IF
!
!* smoothing
CALL SMOOTH_TURB_FUNCT(D,CSTURB,TURBN,PPHI3,PPHI3*2.*PDTDZ,PD_PHI3DTDZ2_O_DDTDZ)
!$mnh_expand_where(JIJ=IIJB:IIJE,JK=1:IKT)
ZWORK1(:,:)=PPHI3(:,:)*2.*PDTDZ(:,:)
!$mnh_end_expand_where(JIJ=IIJB:IIJE,JK=1:IKT)
CALL SMOOTH_TURB_FUNCT(D,CSTURB,TURBN,PPHI3,ZWORK1,PD_PHI3DTDZ2_O_DDTDZ)
!
!
PD_PHI3DTDZ2_O_DDTDZ(IIJB:IIJE,IKB-1)=PD_PHI3DTDZ2_O_DDTDZ(IIJB:IIJE,IKB)
Expand Down
8 changes: 6 additions & 2 deletions src/common/turb/mode_tke_eps_sources.F90
Original file line number Diff line number Diff line change
Expand Up @@ -206,7 +206,8 @@ SUBROUTINE TKE_EPS_SOURCES(D,CST,CSTURB,BUCONF,TURBN,TLES, &
ZKEFF, & ! effectif diffusion coeff = LT * SQRT( TKE )
ZTR, & ! Transport term
ZMWORK1,ZMWORK2,& ! working var. for MZM/MZF operators (array syntax)
ZDWORK1,ZDWORK2 ! working var. for DZM/DZF operators (array syntax)
ZDWORK1,ZDWORK2,& ! working var. for DZM/DZF operators (array syntax)
ZW ! working array

LOGICAL,DIMENSION(D%NIJT,D%NKT) :: GTKENEG
! 3D mask .T. if TKE < CSTURB%XTKEMIN
Expand Down Expand Up @@ -306,7 +307,10 @@ SUBROUTINE TKE_EPS_SOURCES(D,CST,CSTURB,BUCONF,TURBN,TLES, &
!
! Compute TKE at time t+deltat: ( stored in ZRES )
!
CALL TRIDIAG_TKE(D,PTKEM,ZA,PTSTEP,PEXPL,TURBN%XIMPL,PRHODJ,ZSOURCE,PTSTEP*ZFLX,ZRES)
!$mnh_expand_array(JIJ=IIJB:IIJE,JK=1:IKT)
ZW(:,:)=PTSTEP*ZFLX(:,:)
!$mnh_end_expand_array(JIJ=IIJB:IIJE,JK=1:IKT)
CALL TRIDIAG_TKE(D,PTKEM,ZA,PTSTEP,PEXPL,TURBN%XIMPL,PRHODJ,ZSOURCE,ZW,ZRES)
CALL GET_HALO_PHY(D,ZRES)
!
!* diagnose the dissipation
Expand Down
6 changes: 3 additions & 3 deletions src/testprogs/turb_mnh/main_turb.F90
Original file line number Diff line number Diff line change
Expand Up @@ -254,9 +254,9 @@ PROGRAM MAIN_TURB
!$acc & PRHODJ, PTHVREF, PHGRAD, PZS, PSFTH, PSFRV, PSFSV, PSFU, PSFV, &
!$acc & PPABSM, PUM, PVM, PWM, PTKEM, ZSVM, PSRCM, PLENGTHM, PLENGTHH, MFMOIST, &
!$acc & ZCEI, PFLXZTHVMF) &
!$acc & copy (ZBL_DEPTH, ZSBL_DEPTH, PTHM, ZRM, PRUS, PRVS, PRWS, PRTHS, ZRRS, ZRSVS, PRTKES_OUT, &
!$acc & ZWTH, ZWRC, ZWSV, PDP, PTP, PTDIFF, PTDISS) &
!$acc & copyout (PSIGS, PEDR, PTPMF, PDRUS_TURB, PDRVS_TURB, PDRTHLS_TURB, PDRRTS_TURB, ZDRSVS_TURB) &
!$acc & copy (ZBL_DEPTH, ZSBL_DEPTH, PTHM, ZRM, PRUS, PRVS, PRWS, PRTHS, ZRRS, ZRSVS, PRTKES_OUT) &
!$acc & copyout (PSIGS, ZWTH, ZWRC, ZWSV, PDP, PTP, PTDIFF, PTDISS, PEDR, PTPMF, PDRUS_TURB, PDRVS_TURB, &
!$acc & PDRTHLS_TURB, PDRRTS_TURB, ZDRSVS_TURB) &
!$acc & create (PSTACK)

TSC = OMP_GET_WTIME ()
Expand Down
2 changes: 1 addition & 1 deletion tools/INSTALL.sh
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
set -e
set -o pipefail #abort if left command on a pipe fails

pyft_version=417286f52740ce558fd1dc9e6cfb0d35467903c5
pyft_version=50c0efa5877feec73cff2b1ce73f197d52417b51

#This script installs PHYEX
#Call the script with the -h option to get more information.
Expand Down

0 comments on commit bd155da

Please sign in to comment.