Skip to content
Snippets Groups Projects
Commit af4c7c51 authored by ESCOBAR MUNOZ Juan's avatar ESCOBAR MUNOZ Juan
Browse files

Juan 22/04/2022:Juan:ZSOLVER/tke_eps_sources.f90, Bit Reproductible for CRAY -> MNH_BITREP_OMP

parent c20c231a
No related branches found
No related tags found
No related merge requests found
......@@ -191,7 +191,7 @@ USE MODE_MNH_ZWORK, ONLY: MNH_MEM_GET, MNH_MEM_POSITION_PIN, MNH_MEM_RELEAS
#endif
use mode_mppdb
!
#ifdef MNH_BITREP
#if defined(MNH_BITREP) || defined(MNH_BITREP_OMP)
USE MODI_BITREP
#endif
USE MODI_GET_HALO
......@@ -271,8 +271,11 @@ REAL, DIMENSION(:,:,:), pointer , contiguous :: ZTMP1_DEVICE, ZTMP2_DEVICE, ZTMP
!
INTEGER :: JIU,JJU,JKU
INTEGER :: JI,JJ,JK
LOGICAL :: GTURBDIM_3DIM
!----------------------------------------------------------------------------
!
GTURBDIM_3DIM = HTURBDIM=='3DIM'
!
!$acc data present( PTKEM, PLM, PLEPS, PDP, PTRH, &
!$acc & PRHODJ, PDZZ, PDXX, PDYY, PDZX, PDZY, PZZ, &
!$acc & PTP, PRTKES, PRTKESM, PRTHLS, PCOEF_DISS, &
......@@ -341,7 +344,7 @@ IKB=KKA+JPVEXT_TURB*KKL
IKE=KKU-JPVEXT_TURB*KKL
!
! compute the effective diffusion coefficient at the mass point
#ifndef MNH_BITREP
#if !defined(MNH_BITREP) && !defined(MNH_BITREP_OMP)
ZKEFF(:,:,:) = PLM(:,:,:) * SQRT(PTKEM(:,:,:))
#else
#ifdef MNH_COMPILER_NVHPC
......@@ -365,7 +368,7 @@ if (lbudget_th) call Budget_store_init( tbudgets(NBUDGET_TH), 'DISSH', prthls(
!
! Complete the sources of TKE with the horizontal turbulent explicit transport
!
IF (HTURBDIM=='3DIM') THEN
IF (GTURBDIM_3DIM) THEN
PTR(:,:,:) = PTRH(:,:,:)
ELSE
PTR(:,:,:) = 0.
......@@ -382,7 +385,7 @@ PDP(:,:,IKB) = PDP(:,:,IKB) * (1. + PDZZ(:,:,IKB+KKL)/PDZZ(:,:,IKB))
!
! Compute the source terms for TKE: ( ADVECtion + NUMerical DIFFusion + ..)
! + (Dynamical Production) + (Thermal Production) - (dissipation)
#ifndef MNH_BITREP
#if !defined(MNH_BITREP) && !defined(MNH_BITREP_OMP)
ZFLX(:,:,:) = XCED * SQRT(PTKEM(:,:,:)) / PLEPS(:,:,:)
#else
#ifdef MNH_COMPILER_NVHPC
......@@ -410,7 +413,7 @@ END DO !CONCURRENT
!
#ifndef MNH_OPENACC
ZA(:,:,:) = - PTSTEP * XCET * &
#ifndef MNH_BITREP
#if !defined(MNH_BITREP) && !defined(MNH_BITREP_OMP)
MZM(ZKEFF) * MZM(PRHODJ) / PDZZ(:,:,:)**2
#else
MZM(ZKEFF) * MZM(PRHODJ) / BR_P2(PDZZ(:,:,:))
......@@ -418,13 +421,11 @@ ZA(:,:,:) = - PTSTEP * XCET * &
#else
CALL MZM_DEVICE(ZKEFF, ZTMP1_DEVICE) !Warning: re-used later
CALL MZM_DEVICE(PRHODJ,ZTMP2_DEVICE) !Warning: re-used later
!$acc kernels present(ZA)
#ifndef MNH_BITREP
!$acc kernels ! present(ZA)
#if !defined(MNH_BITREP) && !defined(MNH_BITREP_OMP)
ZA(:,:,:) = - PTSTEP * XCET * ZTMP1_DEVICE(:,:,:) * ZTMP2_DEVICE(:,:,:) / PDZZ(:,:,:)**2
#else
#ifdef MNH_COMPILER_NVHPC
!$acc loop independent collapse(3)
#endif
!$acc_nv loop independent collapse(3)
DO CONCURRENT ( JI=1:JIU,JJ=1:JJU,JK=1:JKU)
ZA(JI,JJ,JK) = - PTSTEP * XCET * ZTMP1_DEVICE(JI,JJ,JK) * ZTMP2_DEVICE(JI,JJ,JK) / BR_P2(PDZZ(JI,JJ,JK))
END DO !CONCURRENT
......@@ -544,7 +545,7 @@ end if
if (lbudget_tke) then
!Store the previous source terms in prtkes before initializing the next one
!$acc kernels
!$acc kernels present(ZRES)
PRTKES(:,:,:) = PRTKES(:,:,:) + PRHODJ(:,:,:) * &
( PDP(:,:,:) + PTP(:,:,:) &
- XCED * SQRT(PTKEM(:,:,:)) / PLEPS(:,:,:) * ( PEXPL*PTKEM(:,:,:) + PIMPL*ZRES(:,:,:) ) )
......@@ -553,8 +554,9 @@ if (lbudget_tke) then
end if
!$acc kernels
!dir$ concurrent
PRTKES(:,:,:) = ZRES(:,:,:) * PRHODJ(:,:,:) / PTSTEP - PRTKESM(:,:,:)
DO CONCURRENT ( JI=1:JIU,JJ=1:JJU,JK=1:JKU)
PRTKES(JI,JJ,JK) = ZRES(JI,JJ,JK) * PRHODJ(JI,JJ,JK) / PTSTEP - PRTKESM(JI,JJ,JK)
ENDDO
!$acc end kernels
!
! stores the whole turbulent transport
......@@ -567,13 +569,16 @@ if (lbudget_tke) call Budget_store_end( tbudgets(NBUDGET_TKE), 'TR', prtkes(:, :
! -------------------------------
!
!$acc kernels
#ifndef MNH_BITREP
#if !defined(MNH_BITREP) && !defined(MNH_BITREP_OMP)
!dir$ concurrent
PRTHLS(:,:,:) = PRTHLS(:,:,:) + XCED * SQRT(PTKEM(:,:,:)) / PLEPS(:,:,:) * &
(PEXPL*PTKEM(:,:,:) + PIMPL*ZRES(:,:,:)) * PRHODJ(:,:,:) * PCOEF_DISS(:,:,:)
#else
PRTHLS(:,:,:) = PRTHLS(:,:,:) + XCED * BR_POW(PTKEM(:,:,:),0.5) / PLEPS(:,:,:) * &
DO CONCURRENT (JI=1:JIU, JJ=1:JJU ,JK=1:JKU)
PRTHLS(JI,JJ,JK) = PRTHLS(JI,JJ,JK) + XCED * BR_POW(PTKEM(JI,JJ,JK),0.5) / PLEPS(JI,JJ,JK) * &
(PEXPL*PTKEM(JI,JJ,JK) + PIMPL*ZRES(JI,JJ,JK)) * PRHODJ(JI,JJ,JK) * PCOEF_DISS(JI,JJ,JK)
ENDDO
#endif
(PEXPL*PTKEM(:,:,:) + PIMPL*ZRES(:,:,:)) * PRHODJ(:,:,:) * PCOEF_DISS(:,:,:)
!$acc end kernels
if (lbudget_th) call Budget_store_end( tbudgets(NBUDGET_TH), 'DISSH', prthls(:, :, :) )
......@@ -584,10 +589,12 @@ if (lbudget_th) call Budget_store_end( tbudgets(NBUDGET_TH), 'DISSH', prthls(:,
! -----------------------
!
!$acc kernels
#ifndef MNH_BITREP
#if !defined(MNH_BITREP) && !defined(MNH_BITREP_OMP)
PDISS(:,:,:) = -XCED * (PTKEM(:,:,:)**1.5) / PLEPS(:,:,:)
#else
PDISS(:,:,:) = -XCED * BR_POW(PTKEM(:,:,:),1.5) / PLEPS(:,:,:)
DO CONCURRENT (JI=1:JIU, JJ=1:JJU, JK=1:JKU)
PDISS(JI,JJ,JK) = -XCED * BR_POW(PTKEM(JI,JJ,JK),1.5) / PLEPS(JI,JJ,JK)
ENDDO
#endif
!$acc end kernels
!
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment