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

Juan 21/09/2022:rain_ice*.f90, GPU nvhpc/cray optimization , add...

Juan 21/09/2022:rain_ice*.f90, GPU nvhpc/cray optimization , add mnh_do_concurrent for nvhpc + mnh_undef(LOOP/OPENACC) for cray
parent af5ce936
No related branches found
No related tags found
No related merge requests found
......@@ -40,6 +40,10 @@ use mode_mppdb
#if defined(MNH_BITREP) || defined(MNH_BITREP_OMP)
USE MODI_BITREP
#endif
#ifdef MNH_BITREP_OMP
!$mnh_undef(LOOP)
!$mnh_undef(OPENACC)
#endif
IMPLICIT NONE
!
......@@ -169,7 +173,7 @@ CALL MNH_MEM_GET( ZLBEXI, SIZE(PRHODREF) )
#else
!!$ Le DO concurrent n'est pas bit-reproductible BUG NVHPC 20.7
DO CONCURRENT ( JL=1:JLU )
!$mnh_do_concurrent( JL=1:JLU )
ZLBEXI(JL) = XLBEXI
IF ( GWORK(JL) ) THEN
ZZW(JL) = MIN(1.E8,XLBI*BR_POW( PRHODREF(JL)*PRIT(JL)/PCIT(JL), ZLBEXI(JL) ) ) ! Lbda_i
......@@ -179,7 +183,7 @@ CALL MNH_MEM_GET( ZLBEXI, SIZE(PRHODREF) )
PRIS(JL) = PRIS(JL) + ZZW(JL)
PTHS(JL) = PTHS(JL) + ZZW(JL)*(PLSFACT(JL)-PLVFACT(JL)) ! f(L_f*(RCBERI))
END IF
END DO ! CONCURRENT
!$mnh_end_do() ! CONCURRENT
!!! WHERE( GWORK(:) )
!!!! ZLBEXI(:) = XLBEXI
......
......@@ -42,6 +42,10 @@ use mode_mppdb
#if defined(MNH_BITREP) || defined(MNH_BITREP_OMP)
USE MODI_BITREP
#endif
#ifdef MNH_BITREP_OMP
!$mnh_undef(LOOP)
!$mnh_undef(OPENACC)
#endif
IMPLICIT NONE
!
......@@ -155,7 +159,7 @@ CALL MNH_MEM_GET( zz_diff, SIZE(PLSFACT) )
ZZW(:) = 0.0
GWORK(:) = PZT(:)<XTT-35.0 .AND. PRCT(:)>XRTMIN(2) .AND. PRCS(:)>0.
DO CONCURRENT ( JL=1:JLU )
!$mnh_do_concurrent( JL=1:JLU )
IF ( GWORK(JL) ) THEN
ZZW(JL) = MIN( PRCS(JL),XHON*PRHODREF(JL)*PRCT(JL) &
#if !defined(MNH_BITREP) && !defined(MNH_BITREP_OMP)
......@@ -167,7 +171,7 @@ CALL MNH_MEM_GET( zz_diff, SIZE(PLSFACT) )
PRCS(JL) = PRCS(JL) - ZZW(JL)
PTHS(JL) = PTHS(JL) + ZZW(JL) * zz_diff(JL) ! f(L_f*(RCHONI))
END IF
ENDDO
!$mnh_end_do()
!$acc end kernels
if ( lbudget_th ) call Budget_store_add( tbudgets(NBUDGET_TH), 'HON', &
......@@ -180,7 +184,7 @@ ENDDO
!* 3.3 compute the spontaneous freezing source: RRHONG
!
!$acc kernels
DO CONCURRENT (JL=1:JLU)
!$mnh_do_concurrent (JL=1:JLU)
ZZW(JL) = 0.0
GWORK(JL) = PZT(JL)<XTT-35.0 .AND. PRRT(JL)>XRTMIN(3) .AND. PRRS(JL)>0.
IF( GWORK(JL) )THEN
......@@ -189,7 +193,7 @@ DO CONCURRENT (JL=1:JLU)
PRRS(JL) = PRRS(JL) - ZZW(JL)
PTHS(JL) = PTHS(JL) + ZZW(JL) * zz_diff(JL) ! f(L_f*(RRHONG))
ENDIF
ENDDO
!$mnh_end_do()
!$acc end kernels
if ( lbudget_th ) call Budget_store_add( tbudgets(NBUDGET_TH), 'SFR', &
......@@ -242,8 +246,7 @@ END DO
!* 3.4.3 compute the deposition on r_s: RVDEPS
!
GWORK(:) = PRST(:)>0.0
!$acc loop independent
DO CONCURRENT ( JL=1:JLU )
!$mnh_do_concurrent( JL=1:JLU )
IF ( GWORK(JL) ) THEN
PLBDAS(JL) = MIN( XLBDAS_MAX, &
#if !defined(MNH_BITREP) && !defined(MNH_BITREP_OMP)
......@@ -254,7 +257,7 @@ END DO
ELSE
PLBDAS(JL) = 0.
END IF
END DO ! CONCURRENT
!$mnh_end_do() ! CONCURRENT
ZZW(:) = 0.0
GWORK(:) = (PRST(:)>XRTMIN(5)) .AND. (PRSS(:)>0.0)
!$acc loop independent
......@@ -324,7 +327,7 @@ END DO
#endif
ZZW(:) = 0.0
GWORK(:) = PRIT(:)>XRTMIN(4) .AND. PRIS(:)>0.0
DO CONCURRENT ( JL=1:JLU )
!$mnh_do_concurrent( JL=1:JLU )
IF ( GWORK(JL) ) THEN
#if !defined(MNH_BITREP) && !defined(MNH_BITREP_OMP)
ZZW(JL) = MIN( PRIS(JL),XTIMAUTI * EXP( XTEXAUTI*(PZT(JL)-XTT) ) &
......@@ -337,7 +340,7 @@ DO CONCURRENT ( JL=1:JLU )
PRIS(JL) = PRIS(JL) - ZZW(JL)
!!END WHERE
END IF
END DO
!$mnh_end_do()
!$acc end kernels
if ( lbudget_ri ) call Budget_store_add( tbudgets(NBUDGET_RI), 'AUTS', &
......
......@@ -178,7 +178,7 @@ CALL MNH_MEM_GET( ZZW4, JLU )
!* 4.2 compute the autoconversion of r_c for r_r production: RCAUTR
!
!$acc kernels
DO CONCURRENT (JL=1:JLU)
!$mnh_do_concurrent(JL=1:JLU)
zzw(JL) = 0.
GWORK(JL) = PRCS(JL)>0.0 .AND. PHLC_HCF(JL)>0.0
IF( GWORK(JL) )THEN
......@@ -187,7 +187,7 @@ zzw(JL) = 0.
PRCS(JL) = PRCS(JL) - ZZW(JL)
PRRS(JL) = PRRS(JL) + ZZW(JL)
ENDIF
ENDDO
!$mnh_end_do()
!$acc end kernels
if ( lbudget_rc ) call Budget_store_add( tbudgets(NBUDGET_RC), 'AUTO', &
......@@ -358,10 +358,9 @@ IF (CSUBG_RR_EVAP=='CLFR') GCSUBG_RR_EVAP=.true.
!Ces variables devraient être sorties de rain_ice_slow et on mettrait le calcul de T^u, T^s
!et plusieurs versions (comme actuellement, en ciel clair, en ciel nuageux) de PKA, PDV, PCJ dans rain_ice
!On utiliserait la bonne version suivant l'option NONE, CLFR... dans l'évaporation et ailleurs
GWORK(:) = PRRT(:)>XRTMIN(3) .AND. ZZW4(:)>PCF(:)
!$acc loop independent
DO CONCURRENT ( JL=1:JLU )
GWORK(JL) = PRRT(JL)>XRTMIN(3) .AND. ZZW4(JL)>PCF(JL)
IF ( GWORK(JL) ) THEN
! outside the cloud (environment) the use of T^u (unsaturated) instead of T
! Bechtold et al. 1993
......
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