From 2cd9ab14ab4afaba51f8bf8fc001666cffb8fd94 Mon Sep 17 00:00:00 2001 From: Quentin Rodier <quentin.rodier@meteo.fr> Date: Mon, 28 Mar 2022 17:17:29 +0200 Subject: [PATCH] Quentin 28/03/2022: remove local ALLOCATABLEs in turb --- src/common/turb/mode_turb_ver_thermo_corr.F90 | 18 +++++++----------- src/common/turb/mode_turb_ver_thermo_flux.F90 | 14 +++++--------- src/common/turb/turb.F90 | 18 ++++-------------- 3 files changed, 16 insertions(+), 34 deletions(-) diff --git a/src/common/turb/mode_turb_ver_thermo_corr.F90 b/src/common/turb/mode_turb_ver_thermo_corr.F90 index b551bdd34..66b704cb5 100644 --- a/src/common/turb/mode_turb_ver_thermo_corr.F90 +++ b/src/common/turb/mode_turb_ver_thermo_corr.F90 @@ -320,7 +320,7 @@ REAL, DIMENSION(MERGE(D%NIT,0,OCOMPUTE_SRC),& !* 0.2 declaration of local variables ! ! -REAL, DIMENSION(SIZE(PTHLM,1),SIZE(PTHLM,2),SIZE(PTHLM,3)) :: & +REAL, DIMENSION(D%NIT,D%NJT,D%NKT) :: & ZA, & ! work variable for wrc ZFLXZ, & ! vertical flux of the treated variable ZSOURCE, & ! source of evolution for the treated variable @@ -339,11 +339,12 @@ INTEGER :: ILENCH ! Length of comment string in LFIFM file INTEGER :: IKB,IKE ! I index values for the Beginning and End INTEGER :: IKU ! array sizes - ! mass points of the domain in the 3 direct. -INTEGER :: I1,I2 ! For ZCOEFF allocation -REAL, DIMENSION(:,:,:),ALLOCATABLE :: ZCOEFF +REAL, DIMENSION(D%NIT,D%NJT,MIN(D%NKA+JPVEXT_TURB*KKL,D%NKA+JPVEXT_TURB*KKL+2*KKL):& + MAX(D%NKA+JPVEXT_TURB*KKL,D%NKA+JPVEXT_TURB*KKL+2*KKL))& + :: ZCOEFF ! coefficients for the uncentred gradient - ! computation near the ground + ! computation near the ground, defined in + ! mass points of the domain in the 3 direct. ! REAL :: ZTIME1, ZTIME2 ! @@ -361,13 +362,9 @@ TYPE(TFIELDDATA) :: TZFIELD ! REAL(KIND=JPRB) :: ZHOOK_HANDLE IF (LHOOK) CALL DR_HOOK('TURB_VER_THERMO_CORR',0,ZHOOK_HANDLE) - +! IKB=D%NKB IKE=D%NKE -I1=MIN(D%NKA+JPVEXT_TURB*KKL,D%NKA+JPVEXT_TURB*KKL+2*KKL) -I2=MAX(D%NKA+JPVEXT_TURB*KKL,D%NKA+JPVEXT_TURB*KKL+2*KKL) - -ALLOCATE(ZCOEFF(SIZE(PDZZ,1),SIZE(PDZZ,2),I1:I2)) ! GUSERV = (KRR/=0) ! @@ -863,7 +860,6 @@ ENDIF ! ! 4.6 Deallocate ! - DEALLOCATE(ZCOEFF) !---------------------------------------------------------------------------- IF (LHOOK) CALL DR_HOOK('TURB_VER_THERMO_CORR',1,ZHOOK_HANDLE) END SUBROUTINE TURB_VER_THERMO_CORR diff --git a/src/common/turb/mode_turb_ver_thermo_flux.F90 b/src/common/turb/mode_turb_ver_thermo_flux.F90 index fdbc06d2e..d853c5e59 100644 --- a/src/common/turb/mode_turb_ver_thermo_flux.F90 +++ b/src/common/turb/mode_turb_ver_thermo_flux.F90 @@ -235,7 +235,7 @@ USE MODD_FIELD, ONLY: TFIELDDATA, TYPEREAL USE MODD_GRID_n, ONLY: XZS, XXHAT, XYHAT USE MODD_IO, ONLY: TFILEDATA USE MODD_METRICS_n, ONLY: XDXX, XDYY, XDZX, XDZY, XDZZ -USE MODD_PARAMETERS, ONLY: JPVEXT_TURB +USE MODD_PARAMETERS, ONLY: JPVEXT_TURB, JPHEXT USE MODD_TURB_n, ONLY: TURB_t USE MODD_LES USE MODD_DIM_n, ONLY: NIMAX_ll, NJMAX_ll @@ -394,9 +394,9 @@ INTEGER :: IIB,IJB ! Lower bounds of the physical INTEGER :: IIE,IJE ! Upper bounds of the physical ! sub-domain in x and y directions ! -REAL, DIMENSION(:), ALLOCATABLE :: ZXHAT_ll ! Position x in the conformal +REAL, DIMENSION(NIMAX_ll+2*JPHEXT) :: ZXHAT_ll ! Position x in the conformal ! plane (array on the complete domain) -REAL, DIMENSION(:), ALLOCATABLE :: ZYHAT_ll ! Position y in the conformal +REAL, DIMENSION(NJMAX_ll+2*JPHEXT) :: ZYHAT_ll ! Position y in the conformal ! plane (array on the complete domain) ! ! @@ -429,14 +429,13 @@ REAL(KIND=JPRB) :: ZHOOK_HANDLE IF (LHOOK) CALL DR_HOOK('TURB_VER_THERMO_FLUX',0,ZHOOK_HANDLE) ! ! Size for a given proc & a given model -IIU=SIZE(PTHLM,1) -IJU=SIZE(PTHLM,2) +IIU=D%NIT +IJU=D%NJT ! !! Compute Shape of sfc flux for Oceanic Deep Conv Case ! IF (OOCEAN .AND. ODEEPOC) THEN !* COMPUTES THE PHYSICAL SUBDOMAIN BOUNDS - ALLOCATE(ZXHAT_ll(NIMAX_ll+2*JPHEXT),ZYHAT_ll(NJMAX_ll+2*JPHEXT)) !compute ZXHAT_ll = position in the (0:Lx) domain 1 (Lx=Size of domain1 ) !compute XXHAT_ll = position in the (L0_subproc,Lx_subproc) domain for the current subproc ! L0_subproc as referenced in the full domain 1 @@ -1035,9 +1034,6 @@ IF ( ((OTURB_FLX .AND. TPFILE%LOPENED) .OR. OLES_CALL) .AND. (KRRL > 0) ) THEN END IF ! END IF !end of <w Rc> -IF (OOCEAN .AND. ODEEPOC) THEN - DEALLOCATE(ZXHAT_ll,ZYHAT_ll) -END IF ! !---------------------------------------------------------------------------- IF (LHOOK) CALL DR_HOOK('TURB_VER_THERMO_FLUX',1,ZHOOK_HANDLE) diff --git a/src/common/turb/turb.F90 b/src/common/turb/turb.F90 index 38c17000f..46dbec082 100644 --- a/src/common/turb/turb.F90 +++ b/src/common/turb/turb.F90 @@ -437,7 +437,10 @@ REAL, DIMENSION(D%NIT,D%NJT,D%NKT) :: & ZMWTH,ZMWR,ZMTH2,ZMR2,ZMTHR,& ! 3rd order moments ZFWTH,ZFWR,ZFTH2,ZFR2,ZFTHR,& ! opposite of verticale derivate of 3rd order moments ZTHLM,ZRTKEMS, & ! initial potential temp; TKE advective source - ZSHEAR, ZDUDZ, ZDVDZ ! horizontal-wind vertical gradient + ZSHEAR, ZDUDZ, ZDVDZ, & ! horizontal-wind vertical gradient + ZLVOCPEXNM,ZLSOCPEXNM, & ! Lv/Cp/EXNREF and Ls/Cp/EXNREF at t-1 + ZATHETA_ICE,ZAMOIST_ICE ! coefficients for s = f (Thetal,Rnp) + REAL, DIMENSION(D%NIT,D%NJT,D%NKT,KRR) :: ZRM ! initial mixing ratio REAL, DIMENSION(D%NIT,D%NJT) :: ZTAU11M,ZTAU12M, & ZTAU22M,ZTAU33M, & @@ -454,9 +457,6 @@ REAL, DIMENSION(D%NIT,D%NJT) :: ZTAU11M,ZTAU12M, & ! ! Virtual Potential Temp. used ! in the Deardorff mixing length computation -REAL, DIMENSION(:,:,:), ALLOCATABLE :: & - ZLVOCPEXNM,ZLSOCPEXNM, & ! Lv/Cp/EXNREF and Ls/Cp/EXNREF at t-1 - ZATHETA_ICE,ZAMOIST_ICE ! coefficients for s = f (Thetal,Rnp) ! REAL :: ZEXPL ! 1-PIMPL deg of expl. REAL :: ZRVORD ! RV/RD @@ -553,11 +553,6 @@ IF (KRRL >=1) THEN !* 2.5 Lv/Cph/Exn ! IF ( KRRI >= 1 ) THEN - ALLOCATE(ZLVOCPEXNM(SIZE(PTHLT,1),SIZE(PTHLT,2),SIZE(PTHLT,3))) - ALLOCATE(ZLSOCPEXNM(SIZE(PTHLT,1),SIZE(PTHLT,2),SIZE(PTHLT,3))) - ALLOCATE(ZAMOIST_ICE(SIZE(PTHLT,1),SIZE(PTHLT,2),SIZE(PTHLT,3))) - ALLOCATE(ZATHETA_ICE(SIZE(PTHLT,1),SIZE(PTHLT,2),SIZE(PTHLT,3))) -! CALL COMPUTE_FUNCTION_THERMO(CST%XALPW,CST%XBETAW,CST%XGAMW,CST%XLVTT,CST%XCL,ZT,ZEXN,ZCP, & ZLVOCPEXNM,ZAMOIST,ZATHETA) CALL COMPUTE_FUNCTION_THERMO(CST%XALPI,CST%XBETAI,CST%XGAMI,CST%XLSTT,CST%XCI,ZT,ZEXN,ZCP, & @@ -573,9 +568,6 @@ IF (KRRL >=1) THEN +ZFRAC_ICE(:,:,:) *ZAMOIST_ICE(:,:,:) ZATHETA(:,:,:) = (1.0-ZFRAC_ICE(:,:,:))*ZATHETA(:,:,:) & +ZFRAC_ICE(:,:,:) *ZATHETA_ICE(:,:,:) - - DEALLOCATE(ZAMOIST_ICE) - DEALLOCATE(ZATHETA_ICE) ELSE CALL COMPUTE_FUNCTION_THERMO(CST%XALPW,CST%XBETAW,CST%XGAMW,CST%XLVTT,CST%XCL,ZT,ZEXN,ZCP, & ZLOCPEXNM,ZAMOIST,ZATHETA) @@ -1167,8 +1159,6 @@ IF ( KRRL >= 1 ) THEN PRTHLS(:,:,:) = PRTHLS(:,:,:) + ZLVOCPEXNM(:,:,:) * PRRS(:,:,:,2) & + ZLSOCPEXNM(:,:,:) * PRRS(:,:,:,4) ! - DEALLOCATE(ZLVOCPEXNM) - DEALLOCATE(ZLSOCPEXNM) ELSE PRT(:,:,:,1) = PRT(:,:,:,1) - PRT(:,:,:,2) PRRS(:,:,:,1) = PRRS(:,:,:,1) - PRRS(:,:,:,2) -- GitLab