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

Juan 04/11/2022:ZSOLVER/rain_ice_red.f90, ATTENTION , for CCE > 14.X,...

Juan 04/11/2022:ZSOLVER/rain_ice_red.f90, ATTENTION , for CCE > 14.X, temporarely inhibe compilation of rain_ice_red, MORE THEN 30 minutes !!!
parent aaaedd9a
No related branches found
No related tags found
No related merge requests found
...@@ -359,6 +359,11 @@ REAL, DIMENSION(:,:,:), OPTIONAL, INTENT(INOUT) :: PRHS ! Hail m.r. source ...@@ -359,6 +359,11 @@ REAL, DIMENSION(:,:,:), OPTIONAL, INTENT(INOUT) :: PRHS ! Hail m.r. source
REAL, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: PINPRH! Hail instant precip REAL, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: PINPRH! Hail instant precip
REAL, DIMENSION(:,:,:,:), OPTIONAL, INTENT(OUT) :: PFPR ! upper-air precipitation fluxes REAL, DIMENSION(:,:,:,:), OPTIONAL, INTENT(OUT) :: PFPR ! upper-air precipitation fluxes
! !
#ifdef MNH_COMPILER_CCE
STOP "RAIN_ICE_RED TROP LENT A COMPILER AVEC CRAY/CCE >> 30 Minutes "
STOP "ENLEVE LE ifdefMNH_COMPILER_CCE , SI VOUS EN AVEZ BESOIN sur GPU AMD "
#else
!
!* 0.2 Declarations of local variables : !* 0.2 Declarations of local variables :
! !
INTEGER :: IIB ! Define the domain where is INTEGER :: IIB ! Define the domain where is
...@@ -734,9 +739,9 @@ END IF ...@@ -734,9 +739,9 @@ END IF
imicro = count(odmicro) imicro = count(odmicro)
!$acc end kernels !$acc end kernels
JIU = size(ptht, 1 ) JIU = SIZE( ptht, 1 )
JJU = size(ptht, 2 ) JJU = SIZE( ptht, 2 )
JKU = size(ptht, 3 ) JKU = SIZE( ptht, 3 )
#ifndef MNH_OPENACC #ifndef MNH_OPENACC
allocate( i1(imicro ) ) allocate( i1(imicro ) )
...@@ -746,22 +751,22 @@ allocate( i3(imicro ) ) ...@@ -746,22 +751,22 @@ allocate( i3(imicro ) )
allocate( zw(size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) ) ) allocate( zw(size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) ) )
allocate( zt(size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) ) ) allocate( zt(size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) ) )
allocate( zz_rvheni_mr(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zz_rvheni_mr(jiu, jju, jku ) )
allocate( zz_rvheni (size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zz_rvheni (jiu, jju, jku ) )
allocate( zz_lvfact (size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zz_lvfact (jiu, jju, jku ) )
allocate( zz_lsfact (size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zz_lsfact (jiu, jju, jku ) )
allocate( zlsfact3d (size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zlsfact3d (jiu, jju, jku ) )
allocate( ZHLC_HCF3D(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( ZHLC_HCF3D(jiu, jju, jku ) )
allocate( ZHLC_LCF3D(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( ZHLC_LCF3D(jiu, jju, jku ) )
allocate( ZHLC_HRC3D(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( ZHLC_HRC3D(jiu, jju, jku ) )
allocate( ZHLC_LRC3D(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( ZHLC_LRC3D(jiu, jju, jku ) )
allocate( ZHLI_HCF3D(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( ZHLI_HCF3D(jiu, jju, jku ) )
allocate( ZHLI_LCF3D(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( ZHLI_LCF3D(jiu, jju, jku ) )
allocate( ZHLI_HRI3D(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( ZHLI_HRI3D(jiu, jju, jku ) )
allocate( ZHLI_LRI3D(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( ZHLI_LRI3D(jiu, jju, jku ) )
allocate( zinpri(size( ptht, 1 ), size( ptht, 2 ) ) ) allocate( zinpri(jiu, jju ) )
allocate( zrvt (imicro ) ) allocate( zrvt (imicro ) )
allocate( zrct (imicro ) ) allocate( zrct (imicro ) )
...@@ -934,15 +939,14 @@ allocate( zrh_tend(imicro, 10 ) ) ...@@ -934,15 +939,14 @@ allocate( zrh_tend(imicro, 10 ) )
allocate( zssi(imicro ) ) allocate( zssi(imicro ) )
allocate( zw_rvs(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zw_rvs(jiu, jju, jku ) )
allocate( zw_rcs(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zw_rcs(jiu, jju, jku ) )
allocate( zw_rrs(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zw_rrs(jiu, jju, jku ) )
allocate( zw_ris(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zw_ris(jiu, jju, jku ) )
allocate( zw_rss(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zw_rss(jiu, jju, jku ) )
allocate( zw_rgs(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zw_rgs(jiu, jju, jku ) )
allocate( zw_rhs(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zw_rhs(jiu, jju, jku ) )
allocate( zw_ths(size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) ) allocate( zw_ths(jiu, jju, jku ) )
allocate( ZTEMP_BUD(JIU,JJU,JKU) ) allocate( ZTEMP_BUD(JIU,JJU,JKU) )
#else #else
!Pin positions in the pools of MNH memory !Pin positions in the pools of MNH memory
...@@ -955,22 +959,22 @@ CALL MNH_MEM_GET( i3, imicro ) ...@@ -955,22 +959,22 @@ CALL MNH_MEM_GET( i3, imicro )
CALL MNH_MEM_GET( zw, size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) ) CALL MNH_MEM_GET( zw, size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) )
CALL MNH_MEM_GET( zt, size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) ) CALL MNH_MEM_GET( zt, size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) )
CALL MNH_MEM_GET( zz_rvheni_mr, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zz_rvheni_mr, jiu, jju, jku )
CALL MNH_MEM_GET( zz_rvheni, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zz_rvheni, jiu, jju, jku )
CALL MNH_MEM_GET( zz_lvfact, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zz_lvfact, jiu, jju, jku )
CALL MNH_MEM_GET( zz_lsfact, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zz_lsfact, jiu, jju, jku )
CALL MNH_MEM_GET( zlsfact3d, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zlsfact3d, jiu, jju, jku )
CALL MNH_MEM_GET( ZHLC_HCF3D, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( ZHLC_HCF3D, jiu, jju, jku )
CALL MNH_MEM_GET( ZHLC_LCF3D, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( ZHLC_LCF3D, jiu, jju, jku )
CALL MNH_MEM_GET( ZHLC_HRC3D, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( ZHLC_HRC3D, jiu, jju, jku )
CALL MNH_MEM_GET( ZHLC_LRC3D, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( ZHLC_LRC3D, jiu, jju, jku )
CALL MNH_MEM_GET( ZHLI_HCF3D, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( ZHLI_HCF3D, jiu, jju, jku )
CALL MNH_MEM_GET( ZHLI_LCF3D, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( ZHLI_LCF3D, jiu, jju, jku )
CALL MNH_MEM_GET( ZHLI_HRI3D, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( ZHLI_HRI3D, jiu, jju, jku )
CALL MNH_MEM_GET( ZHLI_LRI3D, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( ZHLI_LRI3D, jiu, jju, jku )
CALL MNH_MEM_GET( zinpri, size( ptht, 1 ), size( ptht, 2 ) ) CALL MNH_MEM_GET( zinpri, jiu, jju )
CALL MNH_MEM_GET( zrvt , imicro ) CALL MNH_MEM_GET( zrvt , imicro )
CALL MNH_MEM_GET( zrct , imicro ) CALL MNH_MEM_GET( zrct , imicro )
...@@ -1143,17 +1147,15 @@ CALL MNH_MEM_GET( zrh_tend, imicro, 10 ) ...@@ -1143,17 +1147,15 @@ CALL MNH_MEM_GET( zrh_tend, imicro, 10 )
CALL MNH_MEM_GET( zssi, imicro ) CALL MNH_MEM_GET( zssi, imicro )
CALL MNH_MEM_GET( zw_rvs, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zw_rvs, jiu, jju, jku )
CALL MNH_MEM_GET( zw_rcs, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zw_rcs, jiu, jju, jku )
CALL MNH_MEM_GET( zw_rrs, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zw_rrs, jiu, jju, jku )
CALL MNH_MEM_GET( zw_ris, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zw_ris, jiu, jju, jku )
CALL MNH_MEM_GET( zw_rss, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zw_rss, jiu, jju, jku )
CALL MNH_MEM_GET( zw_rgs, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zw_rgs, jiu, jju, jku )
CALL MNH_MEM_GET( zw_rhs, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zw_rhs, jiu, jju, jku )
CALL MNH_MEM_GET( zw_ths, size( ptht, 1 ), size( ptht, 2 ), size( ptht, 3 ) ) CALL MNH_MEM_GET( zw_ths, jiu, jju, jku )
CALL MNH_MEM_GET( ZTEMP_BUD, JIU, JJU, JKU ) CALL MNH_MEM_GET( ZTEMP_BUD, JIU, JJU, JKU )
!$acc data present( I1, I2, I3, & !$acc data present( I1, I2, I3, &
!$acc & ZW, ZT, ZZ_RVHENI_MR, ZZ_RVHENI, ZZ_LVFACT, ZZ_LSFACT, ZLSFACT3D, ZINPRI, & !$acc & ZW, ZT, ZZ_RVHENI_MR, ZZ_RVHENI, ZZ_LVFACT, ZZ_LSFACT, ZLSFACT3D, ZINPRI, &
!$acc & ZRVT, ZRCT, ZRRT, ZRIT, ZRST, ZRGT, ZRHT, ZCIT, ZTHT, ZRHODREF, ZZT, ZPRES, ZEXN, & !$acc & ZRVT, ZRCT, ZRRT, ZRIT, ZRST, ZRGT, ZRHT, ZCIT, ZTHT, ZRHODREF, ZZT, ZPRES, ZEXN, &
...@@ -1184,13 +1186,13 @@ CALL MNH_MEM_GET( ZTEMP_BUD, JIU, JJU, JKU ) ...@@ -1184,13 +1186,13 @@ CALL MNH_MEM_GET( ZTEMP_BUD, JIU, JJU, JKU )
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
if ( lbu_enable ) then if ( lbu_enable ) then
if ( lbudget_th ) then if ( lbudget_th ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = pths(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = pths(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_TH), 'HENU', ZTEMP_BUD(:,:,:) ) call Budget_store_init( tbudgets(NBUDGET_TH), 'HENU', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_rv ) then if ( lbudget_rv ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prvs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prvs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RV), 'HENU', ZTEMP_BUD(:,:,:) ) call Budget_store_init( tbudgets(NBUDGET_RV), 'HENU', ZTEMP_BUD(:,:,:) )
...@@ -1202,7 +1204,13 @@ end if ...@@ -1202,7 +1204,13 @@ end if
! ----------------------- ! -----------------------
! !
CALL GET_INDICE_ll (IIB,IJB,IIE,IJE) CALL GET_INDICE_ll (IIB,IJB,IIE,IJE)
#ifdef MNH_COMPILER_CCE
!$acc kernels present(ZRS_TEND,ZRG_TEND,ZRH_TEND,ZRCHONI,ZRVDEPS,ZRIAGGS,ZRIAUTS, &
!$acc & ZRVDEPG,ZRCAUTR,ZRCACCR,ZRREVAV,ZRSMLTG,ZRCMLTSR,ZRICFRRG, &
!$acc & ZRRCFRIG,ZRICFRR,ZRGMLTR,ZRHMLTR,ZRCBERI)
#else
!$acc kernels !$acc kernels
#endif
IKB=KKA+JPVEXT*KKL IKB=KKA+JPVEXT*KKL
IKE=KKU-JPVEXT*KKL IKE=KKU-JPVEXT*KKL
IKTB=1+JPVEXT IKTB=1+JPVEXT
...@@ -1277,37 +1285,37 @@ IF(.NOT. LSEDIM_AFTER) THEN ...@@ -1277,37 +1285,37 @@ IF(.NOT. LSEDIM_AFTER) THEN
!* 2.1 sedimentation !* 2.1 sedimentation
! !
if ( lbudget_rc .and. osedic ) then if ( lbudget_rc .and. osedic ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prcs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prcs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RC), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_init( tbudgets(NBUDGET_RC), 'SEDI', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_rr ) then if ( lbudget_rr ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prrs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prrs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RR), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_init( tbudgets(NBUDGET_RR), 'SEDI', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_ri ) then if ( lbudget_ri ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = pris(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = pris(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RI), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_init( tbudgets(NBUDGET_RI), 'SEDI', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_rs ) then if ( lbudget_rs ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prss(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prss(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RS), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_init( tbudgets(NBUDGET_RS), 'SEDI', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_rg ) then if ( lbudget_rg ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prgs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prgs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RG), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_init( tbudgets(NBUDGET_RG), 'SEDI', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_rh ) then if ( lbudget_rh ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prhs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prhs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RH), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_init( tbudgets(NBUDGET_RH), 'SEDI', ZTEMP_BUD(:,:,:) )
...@@ -1317,7 +1325,7 @@ IF(.NOT. LSEDIM_AFTER) THEN ...@@ -1317,7 +1325,7 @@ IF(.NOT. LSEDIM_AFTER) THEN
!Remark: the 2 source terms SEDI and DEPO could be mixed and stored in the same source term (SEDI) !Remark: the 2 source terms SEDI and DEPO could be mixed and stored in the same source term (SEDI)
! if osedic=T and ldeposc=T (a warning is printed in ini_budget in that case) ! if osedic=T and ldeposc=T (a warning is printed in ini_budget in that case)
if ( lbudget_rc .and. ldeposc .and. .not.osedic ) then if ( lbudget_rc .and. ldeposc .and. .not.osedic ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prcs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prcs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_init( tbudgets(NBUDGET_RC), 'DEPO', ZTEMP_BUD(:,:,:) ) call Budget_store_init( tbudgets(NBUDGET_RC), 'DEPO', ZTEMP_BUD(:,:,:) )
...@@ -1394,37 +1402,37 @@ IF(.NOT. LSEDIM_AFTER) THEN ...@@ -1394,37 +1402,37 @@ IF(.NOT. LSEDIM_AFTER) THEN
!* 2.2 budget storage !* 2.2 budget storage
! !
if ( lbudget_rc .and. osedic ) then if ( lbudget_rc .and. osedic ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prcs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prcs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RC), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_end( tbudgets(NBUDGET_RC), 'SEDI', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_rr ) then if ( lbudget_rr ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prrs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prrs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RR), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_end( tbudgets(NBUDGET_RR), 'SEDI', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_ri ) then if ( lbudget_ri ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = pris(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = pris(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RI), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_end( tbudgets(NBUDGET_RI), 'SEDI', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_rs ) then if ( lbudget_rs ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prss(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prss(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RS), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_end( tbudgets(NBUDGET_RS), 'SEDI', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_rg ) then if ( lbudget_rg ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prgs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prgs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RG), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_end( tbudgets(NBUDGET_RG), 'SEDI', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_rh ) then if ( lbudget_rh ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prhs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prhs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RH), 'SEDI', ZTEMP_BUD(:,:,:) ) call Budget_store_end( tbudgets(NBUDGET_RH), 'SEDI', ZTEMP_BUD(:,:,:) )
...@@ -1433,7 +1441,7 @@ IF(.NOT. LSEDIM_AFTER) THEN ...@@ -1433,7 +1441,7 @@ IF(.NOT. LSEDIM_AFTER) THEN
!If osedic=T and ldeposc=T, DEPO is in fact mixed and stored with the SEDI source term !If osedic=T and ldeposc=T, DEPO is in fact mixed and stored with the SEDI source term
!(a warning is printed in ini_budget in that case) !(a warning is printed in ini_budget in that case)
if ( lbudget_rc .and. ldeposc .and. .not.osedic) then if ( lbudget_rc .and. ldeposc .and. .not.osedic) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prcs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prcs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RC), 'DEPO', ZTEMP_BUD(:,:,:) ) call Budget_store_end( tbudgets(NBUDGET_RC), 'DEPO', ZTEMP_BUD(:,:,:) )
...@@ -1455,10 +1463,21 @@ CALL COUNTJV_DEVICE(ODMICRO(:,:,:),I1(:),I2(:),I3(:),IMICRO) ...@@ -1455,10 +1463,21 @@ CALL COUNTJV_DEVICE(ODMICRO(:,:,:),I1(:),I2(:),I3(:),IMICRO)
!Packing !Packing
GTEST=.false. GTEST=.false.
IF(HSUBG_AUCV_RC=='PDF ' .AND. CSUBG_PR_PDF=='SIGM') GTEST=.true. IF(HSUBG_AUCV_RC=='PDF ' .AND. CSUBG_PR_PDF=='SIGM') GTEST=.true.
#ifdef MNH_COMPILER_CCE
!$acc kernels present(ZSIGMA_RC,ZRHT,ZEXT_RH, &
!$acc & ZTOT_RVHENI, ZTOT_RCHONI, ZTOT_RRHONG, ZTOT_RVDEPS, ZTOT_RIAGGS, ZTOT_RIAUTS, ZTOT_RVDEPG, ZTOT_RCAUTR, &
!$acc & ZTOT_RCACCR, ZTOT_RREVAV, ZTOT_RCRIMSS, ZTOT_RCRIMSG, ZTOT_RSRIMCG, ZTOT_RIMLTC, ZTOT_RCBERI, ZTOT_RHMLTR, &
!$acc & ZTOT_RSMLTG, ZTOT_RCMLTSR, ZTOT_RRACCSS, ZTOT_RRACCSG, ZTOT_RSACCRG, ZTOT_RICFRRG, ZTOT_RRCFRIG, &
!$acc & ZTOT_RICFRR, ZTOT_RCWETG, ZTOT_RIWETG, ZTOT_RRWETG, ZTOT_RSWETG, ZTOT_RCDRYG, ZTOT_RIDRYG, ZTOT_RRDRYG, &
!$acc & ZTOT_RSDRYG, ZTOT_RWETGH, ZTOT_RGMLTR, ZTOT_RCWETH, ZTOT_RIWETH, ZTOT_RSWETH, ZTOT_RGWETH, ZTOT_RRWETH, &
!$acc & ZTOT_RCDRYH, ZTOT_RIDRYH, ZTOT_RSDRYH, ZTOT_RRDRYH, ZTOT_RGDRYH, ZTOT_RDRYHG)
#else
!$acc kernels !$acc kernels
#endif
IF(IMICRO>0) THEN IF(IMICRO>0) THEN
!$acc loop independent !acc loop independent
DO JL=1, IMICRO !$mnh_do_concurrent(JL=1:IMICRO)
ZRVT(JL) = PRVT(I1(JL),I2(JL),I3(JL)) ZRVT(JL) = PRVT(I1(JL),I2(JL),I3(JL))
ZRCT(JL) = PRCT(I1(JL),I2(JL),I3(JL)) ZRCT(JL) = PRCT(I1(JL),I2(JL),I3(JL))
ZRRT(JL) = PRRT(I1(JL),I2(JL),I3(JL)) ZRRT(JL) = PRRT(I1(JL),I2(JL),I3(JL))
...@@ -1487,7 +1506,7 @@ IF(IMICRO>0) THEN ...@@ -1487,7 +1506,7 @@ IF(IMICRO>0) THEN
ELSE ELSE
ZHLI_LCF(JL)=0. ZHLI_LCF(JL)=0.
ENDIF ENDIF
ENDDO !$mnh_end_do()
IF(GEXT_TEND) THEN IF(GEXT_TEND) THEN
!$acc loop independent !$acc loop independent
DO JL=1, IMICRO DO JL=1, IMICRO
...@@ -1589,7 +1608,7 @@ IF(XTSTEP_TS/=0.)THEN ...@@ -1589,7 +1608,7 @@ IF(XTSTEP_TS/=0.)THEN
INB_ITER_MAX=MAX(NMAXITER, INB_ITER_MAX) !For the case XMRSTEP/=0. at the same time INB_ITER_MAX=MAX(NMAXITER, INB_ITER_MAX) !For the case XMRSTEP/=0. at the same time
ENDIF ENDIF
!acc end kernels !acc end kernels
!$acc kernels !$acc kernels present_cr(IITER,ZTIME)
IITER(:)=0 IITER(:)=0
ZTIME(:)=0. ! Current integration time (all points may have a different integration time) ZTIME(:)=0. ! Current integration time (all points may have a different integration time)
!$acc end kernels !$acc end kernels
...@@ -1977,7 +1996,7 @@ ENDDO ...@@ -1977,7 +1996,7 @@ ENDDO
! !
! !$acc kernels ! !$acc kernels
IF(IMICRO>0) THEN IF(IMICRO>0) THEN
!$acc kernels !$acc kernels present_cr(ZHLC_HCF3D,ZHLC_LCF3D,ZHLC_HRC3D,ZHLC_LRC3D,ZHLI_HCF3D,ZHLI_LCF3D,ZHLI_HRI3D,ZHLI_LRI3D)
ZHLC_HCF3D(:,:,:)=0. ZHLC_HCF3D(:,:,:)=0.
ZHLC_LCF3D(:,:,:)=0. ZHLC_LCF3D(:,:,:)=0.
ZHLC_HRC3D(:,:,:)=0. ZHLC_HRC3D(:,:,:)=0.
...@@ -2000,7 +2019,7 @@ IF(IMICRO>0) THEN ...@@ -2000,7 +2019,7 @@ IF(IMICRO>0) THEN
END DO END DO
!$acc end kernels !$acc end kernels
ELSE ELSE
!$acc kernels !$acc kernels present_cr(PRAINFR,ZHLC_HCF3D,ZHLC_LCF3D,ZHLC_HRC3D,ZHLC_LRC3D,ZHLI_HCF3D,ZHLI_LCF3D,ZHLI_HRI3D,ZHLI_LRI3D,PCIT)
PRAINFR(:,:,:)=0. PRAINFR(:,:,:)=0.
ZHLC_HCF3D(:,:,:)=0. ZHLC_HCF3D(:,:,:)=0.
ZHLC_LCF3D(:,:,:)=0. ZHLC_LCF3D(:,:,:)=0.
...@@ -2013,7 +2032,7 @@ ELSE ...@@ -2013,7 +2032,7 @@ ELSE
PCIT(:,:,:) = 0. PCIT(:,:,:) = 0.
!$acc end kernels !$acc end kernels
ENDIF ENDIF
!$acc kernels !$acc kernels present_cr(PEVAP3D)
IF(OWARM) THEN IF(OWARM) THEN
PEVAP3D(:,:,:) = 0. PEVAP3D(:,:,:) = 0.
!$acc loop independent !$acc loop independent
...@@ -2053,19 +2072,19 @@ ENDDO ...@@ -2053,19 +2072,19 @@ ENDDO
if ( lbu_enable ) then if ( lbu_enable ) then
!Note: there is an other contribution for HENU later !Note: there is an other contribution for HENU later
if ( lbudget_th ) then if ( lbudget_th ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = pths(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = pths(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_TH), 'HENU', ZTEMP_BUD(:,:,:) ) call Budget_store_end( tbudgets(NBUDGET_TH), 'HENU', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_rv ) then if ( lbudget_rv ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = prvs(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = prvs(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_end( tbudgets(NBUDGET_RV), 'HENU', ZTEMP_BUD(:,:,:) ) call Budget_store_end( tbudgets(NBUDGET_RV), 'HENU', ZTEMP_BUD(:,:,:) )
end if end if
if ( lbudget_ri ) then if ( lbudget_ri ) then
!$acc kernels present(ZTEMP_BUD) !$acc kernels present_cr(ZTEMP_BUD)
ZTEMP_BUD(:,:,:) = zz_rvheni(:, :, :) * prhodj(:, :, :) ZTEMP_BUD(:,:,:) = zz_rvheni(:, :, :) * prhodj(:, :, :)
!$acc end kernels !$acc end kernels
call Budget_store_add( tbudgets(NBUDGET_RI), 'HENU', ZTEMP_BUD(:,:,:) ) call Budget_store_add( tbudgets(NBUDGET_RI), 'HENU', ZTEMP_BUD(:,:,:) )
...@@ -2227,7 +2246,7 @@ ELSE ...@@ -2227,7 +2246,7 @@ ELSE
END DO END DO
!$acc end kernels !$acc end kernels
! !
!$acc kernels !$acc kernels present_cr(ZW_RHS)
ZW_RVS(:,:,:) = ( ZW_RVS(:,:,:) - PRVT(:,:,:) ) * ZINV_TSTEP ZW_RVS(:,:,:) = ( ZW_RVS(:,:,:) - PRVT(:,:,:) ) * ZINV_TSTEP
ZW_RCS(:,:,:) = ( ZW_RCS(:,:,:) - PRCT(:,:,:) ) * ZINV_TSTEP ZW_RCS(:,:,:) = ( ZW_RCS(:,:,:) - PRCT(:,:,:) ) * ZINV_TSTEP
ZW_RRS(:,:,:) = ( ZW_RRS(:,:,:) - PRRT(:,:,:) ) * ZINV_TSTEP ZW_RRS(:,:,:) = ( ZW_RRS(:,:,:) - PRRT(:,:,:) ) * ZINV_TSTEP
...@@ -2801,7 +2820,6 @@ CONTAINS ...@@ -2801,7 +2820,6 @@ CONTAINS
REAL, DIMENSION(:,:,:), POINTER, CONTIGUOUS :: ZW REAL, DIMENSION(:,:,:), POINTER, CONTIGUOUS :: ZW
#endif #endif
! !
!$acc data present( PRV, PRC, PRR, PRI, PRS, PRG, PTH, PLVFACT, PLSFACT, PRH )
! !
IF (MPPDB_INITIALIZED) THEN IF (MPPDB_INITIALIZED) THEN
!Check all IN arrays !Check all IN arrays
...@@ -2818,6 +2836,8 @@ CONTAINS ...@@ -2818,6 +2836,8 @@ CONTAINS
CALL MPPDB_CHECK(PTH,"CORRECT_NEGATIVITIES beg:PTH") CALL MPPDB_CHECK(PTH,"CORRECT_NEGATIVITIES beg:PTH")
END IF END IF
!$acc data present( PRV, PRC, PRR, PRI, PRS, PRG, PTH, PLVFACT, PLSFACT )
#ifndef MNH_OPENACC #ifndef MNH_OPENACC
allocate( gw(size( prv, 1 ), size( prv, 2 ), size( prv, 3 ) ) ) allocate( gw(size( prv, 1 ), size( prv, 2 ), size( prv, 3 ) ) )
allocate( zw(size( prv, 1 ), size( prv, 2 ), size( prv, 3 ) ) ) allocate( zw(size( prv, 1 ), size( prv, 2 ), size( prv, 3 ) ) )
...@@ -2831,6 +2851,7 @@ CONTAINS ...@@ -2831,6 +2851,7 @@ CONTAINS
!$acc data present( GW, ZW ) !$acc data present( GW, ZW )
#endif #endif
!$acc data present( PRH ) if ( present( PRH ) )
!$acc kernels !$acc kernels
!We correct negativities with conservation !We correct negativities with conservation
! 1) deal with negative values for mixing ratio, except for vapor ! 1) deal with negative values for mixing ratio, except for vapor
...@@ -2926,6 +2947,7 @@ CONTAINS ...@@ -2926,6 +2947,7 @@ CONTAINS
ENDDO ENDDO
ENDIF ENDIF
!$acc end kernels !$acc end kernels
!$acc end data
!$acc end data !$acc end data
...@@ -2934,6 +2956,8 @@ CONTAINS ...@@ -2934,6 +2956,8 @@ CONTAINS
CALL MNH_MEM_RELEASE() CALL MNH_MEM_RELEASE()
#endif #endif
!$acc end data
IF (MPPDB_INITIALIZED) THEN IF (MPPDB_INITIALIZED) THEN
!Check all INOUT arrays !Check all INOUT arrays
CALL MPPDB_CHECK(PRV,"CORRECT_NEGATIVITIES end:PRV") CALL MPPDB_CHECK(PRV,"CORRECT_NEGATIVITIES end:PRV")
...@@ -2946,9 +2970,8 @@ CONTAINS ...@@ -2946,9 +2970,8 @@ CONTAINS
CALL MPPDB_CHECK(PTH,"CORRECT_NEGATIVITIES end:PTH") CALL MPPDB_CHECK(PTH,"CORRECT_NEGATIVITIES end:PTH")
END IF END IF
!$acc end data
END SUBROUTINE CORRECT_NEGATIVITIES END SUBROUTINE CORRECT_NEGATIVITIES
! !
#endif
END SUBROUTINE RAIN_ICE_RED END SUBROUTINE RAIN_ICE_RED
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment