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

Juan 15/06/2021: turb_ver.f90, acc opt , replace allocate -> MNH_ALLOCATE_ZT4D

parent dccdfaeb
No related branches found
No related tags found
No related merge requests found
......@@ -344,7 +344,7 @@ USE MODE_PRANDTL
USE MODI_SECOND_MNH
!
#ifdef MNH_OPENACC
USE MODE_MNH_ZWORK, ONLY : MNH_ALLOCATE_ZT3D , MNH_REL_ZT3D
USE MODE_MNH_ZWORK, ONLY : MNH_ALLOCATE_ZT3D , MNH_REL_ZT3D, MNH_ALLOCATE_ZT4D , MNH_REL_ZT4D
#endif
!
IMPLICIT NONE
......@@ -464,11 +464,12 @@ INTEGER :: izbeta,izsqrt_tke,izdth_dz,izdr_dz,izred2th3,izred2r3,izred2thr3, &
izbll_o_e,izetheta,izemoist,izredth1,izredr1,izphi3,izpsi3, &
izd,izwthv,izwu,izwv,izthlp,izrp
REAL, DIMENSION(:,:,:,:), allocatable :: &
REAL, DIMENSION(:,:,:,:), pointer , contiguous :: &
ZPSI_SV, & ! Prandtl number for scalars
ZREDS1, & ! 1D Redeslperger number R_sv
ZRED2THS, & ! 3D Redeslperger number R*2_thsv
ZRED2RS ! 3D Redeslperger number R*2_rsv
INTEGER :: IZPSI_SV,IZREDS1,IZRED2THS,IZRED2RS
!
LOGICAL :: GUSERV ! flag to use water vapor
INTEGER :: IKB,IKE ! index value for the Beginning
......@@ -601,15 +602,22 @@ izthlp = MNH_ALLOCATE_ZT3D( zthlp ,JIU,JJU,JKU )
izrp = MNH_ALLOCATE_ZT3D( zrp ,JIU,JJU,JKU )
#endif
allocate( zpsi_sv (size( pthlm, 1 ), size( pthlm, 2 ), size( pthlm, 3 ), nsv ) )
allocate( zreds1 (size( pthlm, 1 ), size( pthlm, 2 ), size( pthlm, 3 ), nsv ) )
allocate( zred2ths(size( pthlm, 1 ), size( pthlm, 2 ), size( pthlm, 3 ), nsv ) )
allocate( zred2rs (size( pthlm, 1 ), size( pthlm, 2 ), size( pthlm, 3 ), nsv ) )
#ifndef MNH_OPENACC
allocate( zpsi_sv (JIU,JJU,JKU, nsv ) )
allocate( zreds1 (JIU,JJU,JKU, nsv ) )
allocate( zred2ths(JIU,JJU,JKU, nsv ) )
allocate( zred2rs (JIU,JJU,JKU, nsv ) )
#else
izpsi_sv = MNH_ALLOCATE_ZT4D( zpsi_sv ,JIU,JJU,JKU, nsv )
izreds1 = MNH_ALLOCATE_ZT4D( zreds1 ,JIU,JJU,JKU, nsv )
izred2ths = MNH_ALLOCATE_ZT4D( zred2ths,JIU,JJU,JKU, nsv )
izred2rs = MNH_ALLOCATE_ZT4D( zred2rs ,JIU,JJU,JKU, nsv )
#endif
!$acc data present (ZBETA, ZSQRT_TKE, ZDTH_DZ, ZDR_DZ, ZRED2TH3, ZRED2R3, ZRED2THR3,&
!$acc & ZBLL_O_E, ZETHETA, ZEMOIST, ZREDTH1, ZREDR1, &
!$acc & ZPHI3, ZPSI3, ZD, ZWTHV, ZWU, ZWV, ZTHLP, ZRP) &
!$acc & create ( ZPSI_SV, ZREDS1, ZRED2THS, ZRED2RS )
!$acc & ZPHI3, ZPSI3, ZD, ZWTHV, ZWU, ZWV, ZTHLP, ZRP, &
!$acc & ZPSI_SV, ZREDS1, ZRED2THS, ZRED2RS )
!
!* 1. PRELIMINARIES
......@@ -908,6 +916,14 @@ CALL MNH_REL_ZT3D(izbeta,izsqrt_tke,izdth_dz,izdr_dz,izred2th3,izred2r3,izred2th
izd,izwthv,izwu,izwv,izthlp,izrp)
#endif
#ifndef MNH_OPENACC
DEALLOCATE(zpsi_sv,zreds1,zred2ths,zred2rs)
#else
CALL MNH_REL_ZT4D (nsv , izred2rs )
CALL MNH_REL_ZT4D (nsv , izred2ths )
CALL MNH_REL_ZT4D (nsv , izreds1 )
CALL MNH_REL_ZT4D (nsv , izpsi_sv )
#endif
!$acc end data
!----------------------------------------------------------------------------
......
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