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

Juan 15/09/2021:pressurez.f90, for GPU replace automatic array -> pointer...

Juan 15/09/2021:pressurez.f90, for GPU replace automatic array -> pointer contiguous + MNH_ALLOCATE_ZT3D
parent 7f77d356
No related branches found
No related tags found
No related merge requests found
......@@ -366,8 +366,9 @@ REAL, OPTIONAL :: PRESIDUAL
!
! Metric coefficients:
!
REAL, DIMENSION(SIZE(PPABST,1),SIZE(PPABST,2),SIZE(PPABST,3)) :: ZDV_SOURCE
REAL, DIMENSION(:,:,:) , POINTER , CONTIGUOUS :: ZDV_SOURCE
! ! divergence of the sources
INTEGER :: IZDV_SOURCE
!
INTEGER :: IIB ! indice I for the first inner mass point along x
INTEGER :: IIE ! indice I for the last inner mass point along x
......@@ -378,11 +379,12 @@ INTEGER :: IKE ! indice K for the last inner mass point along z
INTEGER :: ILUOUT ! Logical unit of output listing
INTEGER :: IRESP ! Return code of FM routines
!
REAL, DIMENSION(SIZE(PPABST,1),SIZE(PPABST,2),SIZE(PPABST,3)) :: ZTHETAV, &
REAL, DIMENSION(:,:,:) , POINTER , CONTIGUOUS :: ZTHETAV, &
! virtual potential temperature
ZPHIT
ZPHIT
! MAE + DUR => Exner function perturbation
! LHE => Exner function perturbation * CPD * THVREF
INTEGER :: IZTHETAV,IZPHIT
!
REAL :: ZRV_OV_RD ! XRV / XRD
REAL :: ZMAXVAL, ZMAXRES, ZMAX,ZMAX_ll ! for print
......@@ -442,6 +444,10 @@ GNORTH2D = ( L2D .AND. LNORTH_ll() )
!
GPRVREF0 = ( SIZE(PRVREF,1) == 0 )
!
IZDV_SOURCE = MNH_ALLOCATE_ZT3D(ZDV_SOURCE ,IIU,IJU,IKU )
IZTHETAV = MNH_ALLOCATE_ZT3D(ZTHETAV ,IIU,IJU,IKU )
IZPHIT = MNH_ALLOCATE_ZT3D(ZPHIT ,IIU,IJU,IKU )
!
IZPRHODJ = MNH_ALLOCATE_ZT3D( ZPRHODJ,IIU,IJU,IKU )
IZMXM_PRHODJ = MNH_ALLOCATE_ZT3D( ZMXM_PRHODJ,IIU,IJU,IKU )
IZMZM_PRHODJ = MNH_ALLOCATE_ZT3D( ZMZM_PRHODJ,IIU,IJU,IKU )
......@@ -532,6 +538,7 @@ IF(CEQNSYS=='MAE' .OR. CEQNSYS=='DUR') THEN
! compute the ratio : 1 + total water mass / dry air mass
ZRV_OV_RD = XRV / XRD
ZTHETAV(:,:,:) = 1. + PRT(:,:,:,1)
!$acc loop seq
DO JWATER = 2 , 1+KRRL+KRRI
ZTHETAV(:,:,:) = ZTHETAV(:,:,:) + PRT(:,:,:,JWATER)
END DO
......@@ -548,7 +555,9 @@ IF(CEQNSYS=='MAE' .OR. CEQNSYS=='DUR') THEN
ZPHIT(:,:,:)=(PPABST(:,:,:)/XP00)**(XRD/XCPD)-PEXNREF(:,:,:)
#else
!$acc kernels
ZPHIT(:,:,:)=BR_POW((PPABST(:,:,:)/XP00),(XRD/XCPD))-PEXNREF(:,:,:)
DO CONCURRENT ( JI=1:IIU,JJ=1:IJU,JK=1:IKU )
ZPHIT(JI,JJ,JK)=BR_POW((PPABST(JI,JJ,JK)/XP00),(XRD/XCPD))-PEXNREF(JI,JJ,JK)
END DO
!$acc end kernels
#endif
!
......@@ -922,6 +931,7 @@ END IF
!
#ifdef MNH_OPENACC
CALL MNH_REL_ZT3D ( IZPRHODJ,IZMXM_PRHODJ,IZMZM_PRHODJ,IZGZ_M_W,IZMYM_PRHODJ )
CALL MNH_REL_ZT3D ( IZDV_SOURCE,IZTHETAV,IZPHIT)
#endif
!-------------------------------------------------------------------------------
!
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment