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

Juan 03/03/2022:ZSOLVER/p_abs.f90, for no MANAGED version , update variable before SUM_DD_R2_ll

parent 65887065
No related branches found
No related tags found
No related merge requests found
......@@ -180,7 +180,7 @@ REAL :: ZMASSGUESS ! guess of mass resulting of the pressure function
! provided by the pressure solveur, to an arbitary constant
REAL :: ZWATERMASST ! Total mass of water Mw
!JUAN16
REAL, SAVE , ALLOCATABLE, DIMENSION(:,:) :: ZMASS_O_PI_2D,ZMASSGUESS_2D,ZWATERMASST_2D
REAL, DIMENSION(:,:) , POINTER , CONTIGUOUS :: ZMASS_O_PI_2D,ZMASSGUESS_2D,ZWATERMASST_2D
!JUAN16
REAL :: ZPI0 ! constant to retrieve the absolute Exner pressure
INTEGER :: JWATER ! loop index on the different types of water
......@@ -214,22 +214,22 @@ CALL GET_INDICE_ll(IIB,IJB,IIE,IJE)
!
GPRVREF0 = ( SIZE(PRVREF,1) == 0 )
!
IF (GFIRST_CALL_P_ABS) THEN
GFIRST_CALL_P_ABS = .FALSE.
ALLOCATE(ZMASS_O_PI_2D(IIB:IIE,IJB:IJE))
ALLOCATE(ZMASSGUESS_2D(IIB:IIE,IJB:IJE))
ALLOCATE(ZWATERMASST_2D(IIB:IIE,IJB:IJE))
END IF
!
ZP00_O_RD = XP00 / XRD
ZCVD_O_RD = (XCPD - XRD) / XRD
!
#ifndef MNH_OPENACC
ALLOCATE(ZMASS_O_PI_2D(IIB:IIE,IJB:IJE))
ALLOCATE(ZMASSGUESS_2D(IIB:IIE,IJB:IJE))
ALLOCATE(ZWATERMASST_2D(IIB:IIE,IJB:IJE))
ALLOCATE (ZRTOT(IIU,IJU,IKU), ZRHOREF(IIU,IJU,IKU), ZWORK(IIU,IJU,IKU))
#else
!Pin positions in the pools of MNH memory
CALL MNH_MEM_POSITION_PIN()
CALL MNH_MEM_GET(ZMASS_O_PI_2D , IIB,IIE , IJB,IJE)
CALL MNH_MEM_GET(ZMASSGUESS_2D , IIB,IIE , IJB,IJE)
CALL MNH_MEM_GET(ZWATERMASST_2D , IIB,IIE , IJB,IJE)
CALL MNH_MEM_GET( ZRTOT, IIU, IJU, IKU )
CALL MNH_MEM_GET( ZRHOREF, IIU, IJU, IKU )
CALL MNH_MEM_GET( ZWORK, IIU, IJU, IKU )
......@@ -310,6 +310,7 @@ IF ( CEQNSYS=='DUR' .OR. CEQNSYS=='MAE' ) THEN
END IF
!
!
!$acc update host(ZMASSGUESS_2D,ZMASS_O_PI_2D,ZWATERMASST_2D)
ZMASSGUESS = SUM_DD_R2_ll(ZMASSGUESS_2D)
ZMASS_O_PI = SUM_DD_R2_ll(ZMASS_O_PI_2D)
ZWATERMASST = SUM_DD_R2_ll(ZWATERMASST_2D)
......@@ -446,6 +447,7 @@ ELSEIF( CEQNSYS == 'LHE' ) THEN
END IF
!
#ifndef MNH_OPENACC
DEALLOCATE(ZMASS_O_PI_2D,ZMASSGUESS_2D,ZWATERMASST_2D)
DEALLOCATE (ZRTOT, ZRHOREF, ZWORK)
#else
!Release all memory allocated with MNH_MEM_GET calls since last call to MNH_MEM_POSITION_PIN
......
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