Skip to content
Snippets Groups Projects
Commit d2a5c138 authored by RODIER Quentin's avatar RODIER Quentin
Browse files

Quentin 28/07/2022: move outside of turb, computation of ZDIST for OCEAN (+ not used yet)

parent 2cec482a
No related branches found
No related tags found
No related merge requests found
...@@ -240,7 +240,6 @@ USE MODD_LES ...@@ -240,7 +240,6 @@ USE MODD_LES
USE MODD_DIM_n, ONLY: NIMAX_ll, NJMAX_ll USE MODD_DIM_n, ONLY: NIMAX_ll, NJMAX_ll
USE MODD_OCEANH, ONLY: XSSTFL USE MODD_OCEANH, ONLY: XSSTFL
USE MODD_TURB_n, ONLY: TURB_t USE MODD_TURB_n, ONLY: TURB_t
USE MODD_FRC, ONLY: XCENTX_OC, XCENTY_OC, XRADX_OC,XRADY_OC
! !
USE MODI_GRADIENT_U USE MODI_GRADIENT_U
USE MODI_GRADIENT_V USE MODI_GRADIENT_V
...@@ -256,8 +255,6 @@ USE MODE_PRANDTL ...@@ -256,8 +255,6 @@ USE MODE_PRANDTL
USE SHUMAN_PHY, ONLY: MZM_PHY, MZF_PHY, DZM_PHY, DZF_PHY USE SHUMAN_PHY, ONLY: MZM_PHY, MZF_PHY, DZM_PHY, DZF_PHY
! !
USE MODI_SECOND_MNH USE MODI_SECOND_MNH
USE MODE_ll
USE MODE_GATHER_ll
! !
IMPLICIT NONE IMPLICIT NONE
! !
...@@ -394,16 +391,8 @@ INTEGER :: IIB,IJB ! Lower bounds of the physical ...@@ -394,16 +391,8 @@ INTEGER :: IIB,IJB ! Lower bounds of the physical
INTEGER :: IIE,IJE ! Upper bounds of the physical INTEGER :: IIE,IJE ! Upper bounds of the physical
! sub-domain in x and y directions ! sub-domain in x and y directions
! !
! NIMPORTE QUOI : TODO TO BE REMOVED OUTSIDE OF TURB ? :
REAL, DIMENSION(1) :: ZXHAT_ll ! Position x in the conformal
! plane (array on the complete domain)
REAL, DIMENSION(1) :: ZYHAT_ll ! Position y in the conformal
! plane (array on the complete domain)
!
!
REAL :: ZTIME1, ZTIME2 REAL :: ZTIME1, ZTIME2
REAL :: ZDELTAX REAL :: ZDELTAX
REAL :: ZXBEG,ZXEND,ZYBEG,ZYEND ! Forcing size for ocean deep convection
REAL, DIMENSION(D%NIT,D%NJT) :: ZDIST ! distance REAL, DIMENSION(D%NIT,D%NJT) :: ZDIST ! distance
! from the center of the cooling ! from the center of the cooling
REAL :: ZFLPROV REAL :: ZFLPROV
...@@ -412,7 +401,6 @@ INTEGER :: JSW ...@@ -412,7 +401,6 @@ INTEGER :: JSW
REAL :: ZSWA ! index for time flux interpolation REAL :: ZSWA ! index for time flux interpolation
! !
INTEGER :: IIU, IJU INTEGER :: IIU, IJU
INTEGER :: IRESP
LOGICAL :: GUSERV ! flag to use water LOGICAL :: GUSERV ! flag to use water
LOGICAL :: GFTH2 ! flag to use w'th'2 LOGICAL :: GFTH2 ! flag to use w'th'2
LOGICAL :: GFWTH ! flag to use w'2th' LOGICAL :: GFWTH ! flag to use w'2th'
...@@ -435,33 +423,6 @@ IIE=D%NIEC ...@@ -435,33 +423,6 @@ IIE=D%NIEC
IIB=D%NIBC IIB=D%NIBC
IJE=D%NJEC IJE=D%NJEC
IJB=D%NJBC IJB=D%NJBC
!
!! Compute Shape of sfc flux for Oceanic Deep Conv Case
!
IF (OOCEAN .AND. ODEEPOC) THEN
!* COMPUTES THE PHYSICAL SUBDOMAIN BOUNDS
!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
CALL GATHERALL_FIELD_ll('XX',XXHAT,ZXHAT_ll,IRESP)
CALL GATHERALL_FIELD_ll('YY',XYHAT,ZYHAT_ll,IRESP)
CALL GET_DIM_EXT_ll('B',IIU,IJU)
CALL GET_INDICE_ll(IIB,IJB,IIE,IJE,IIU,IJU)
DO JJ = IJB,IJE
DO JI = IIB,IIE
ZDIST(JI,JJ) = SQRT( &
(( (XXHAT(JI)+XXHAT(JI+1))*0.5 - XCENTX_OC ) / XRADX_OC)**2 + &
(( (XYHAT(JJ)+XYHAT(JJ+1))*0.5 - XCENTY_OC ) / XRADY_OC)**2 &
)
END DO
END DO
DO JJ=IJB,IJE
DO JI=IIB,IIE
IF ( ZDIST(JI,JJ) > 1.) XSSTFL(JI,JJ)=0.
END DO
END DO
END IF !END DEEP OCEAN CONV CASE
!
IKT=D%NKT IKT=D%NKT
IKTB=D%NKTB IKTB=D%NKTB
IKTE=D%NKTE IKTE=D%NKTE
......
...@@ -262,6 +262,7 @@ USE MODD_DEEP_CONVECTION_n ...@@ -262,6 +262,7 @@ USE MODD_DEEP_CONVECTION_n
USE MODD_DEF_EDDY_FLUX_n ! Ajout PP USE MODD_DEF_EDDY_FLUX_n ! Ajout PP
USE MODD_DEF_EDDYUV_FLUX_n ! Ajout PP USE MODD_DEF_EDDYUV_FLUX_n ! Ajout PP
USE MODD_DIAG_IN_RUN, ONLY: LDIAG_IN_RUN, XCURRENT_TKE_DISS USE MODD_DIAG_IN_RUN, ONLY: LDIAG_IN_RUN, XCURRENT_TKE_DISS
USE MODD_DIM_n, ONLY: NIMAX_ll, NJMAX_ll
USE MODD_DRAGBLDG_n USE MODD_DRAGBLDG_n
USE MODD_DRAGTREE_n USE MODD_DRAGTREE_n
USE MODD_DUST USE MODD_DUST
...@@ -324,6 +325,7 @@ use mode_budget, only: Budget_store_end, Budget_store_init ...@@ -324,6 +325,7 @@ use mode_budget, only: Budget_store_end, Budget_store_init
USE MODE_DATETIME USE MODE_DATETIME
USE MODE_DUST_PSD USE MODE_DUST_PSD
USE MODE_ll USE MODE_ll
USE MODE_GATHER_ll
USE MODE_MNH_TIMING USE MODE_MNH_TIMING
USE MODE_MODELN_HANDLER USE MODE_MODELN_HANDLER
USE MODE_MPPDB USE MODE_MPPDB
...@@ -428,7 +430,7 @@ INTEGER :: IIU, IJU, IKU ! dimensional indexes ...@@ -428,7 +430,7 @@ INTEGER :: IIU, IJU, IKU ! dimensional indexes
! !
INTEGER :: JSV ! Loop index for Scalar Variables INTEGER :: JSV ! Loop index for Scalar Variables
INTEGER :: JSWB ! loop on SW spectral bands INTEGER :: JSWB ! loop on SW spectral bands
INTEGER :: IIB,IIE,IJB,IJE, IKB, IKE INTEGER :: IIB,IIE,IJB,IJE, IKB, IKE, JI,JJ
INTEGER :: IMODEIDX INTEGER :: IMODEIDX
! index values for the Beginning or the End of the physical ! index values for the Beginning or the End of the physical
! domain in x and y directions ! domain in x and y directions
...@@ -463,6 +465,9 @@ REAL, DIMENSION(:), ALLOCATABLE :: ZPROSOL1(:),ZPROSOL2(:) ! Funtions for penetr ...@@ -463,6 +465,9 @@ REAL, DIMENSION(:), ALLOCATABLE :: ZPROSOL1(:),ZPROSOL2(:) ! Funtions for penetr
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZLENGTHM, ZLENGTHH, ZMFMOIST !OHARAT turb option from AROME (not allocated in MNH) REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZLENGTHM, ZLENGTHH, ZMFMOIST !OHARAT turb option from AROME (not allocated in MNH)
! to be moved as optional args for turb ! to be moved as optional args for turb
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZTDIFF, ZTDISS REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZTDIFF, ZTDISS
REAL, DIMENSION(:),ALLOCATABLE :: ZXHAT_ll,ZYHAT_ll ! Position x/y in the conformal
! plane (array on the complete domain)
REAL, DIMENSION(:,:), ALLOCATABLE :: ZDIST ! distance from the center of the cooling
! !
TYPE(DIMPHYEX_t) :: YLDIMPHYEX TYPE(DIMPHYEX_t) :: YLDIMPHYEX
LOGICAL :: GCOMPUTE_SRC ! flag to define dimensions of SIGS and SRCT variables LOGICAL :: GCOMPUTE_SRC ! flag to define dimensions of SIGS and SRCT variables
...@@ -1500,7 +1505,34 @@ GCOMPUTE_SRC=SIZE(XSIGS, 3)/=0 ...@@ -1500,7 +1505,34 @@ GCOMPUTE_SRC=SIZE(XSIGS, 3)/=0
! !
ALLOCATE(ZTDIFF(IIU,IJU,IKU)) ALLOCATE(ZTDIFF(IIU,IJU,IKU))
ALLOCATE(ZTDISS(IIU,IJU,IKU)) ALLOCATE(ZTDISS(IIU,IJU,IKU))
!
!! Compute Shape of sfc flux for Oceanic Deep Conv Case
!
IF (LOCEAN .AND. LDEEPOC) THEN
ALLOCATE(ZDIST(IIU,IJU))
!* 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
CALL GATHERALL_FIELD_ll('XX',XXHAT,ZXHAT_ll,IRESP)
CALL GATHERALL_FIELD_ll('YY',XYHAT,ZYHAT_ll,IRESP)
CALL GET_DIM_EXT_ll('B',IIU,IJU)
DO JJ = IJB,IJE
DO JI = IIB,IIE
ZDIST(JI,JJ) = SQRT( &
(( (XXHAT(JI)+XXHAT(JI+1))*0.5 - XCENTX_OC ) / XRADX_OC)**2 + &
(( (XYHAT(JJ)+XYHAT(JJ+1))*0.5 - XCENTY_OC ) / XRADY_OC)**2 &
)
END DO
END DO
DO JJ=IJB,IJE
DO JI=IIB,IIE
IF ( ZDIST(JI,JJ) > 1.) XSSTFL(JI,JJ)=0.
END DO
END DO
END IF !END DEEP OCEAN CONV CASE
!
! !
CALL TURB( CST,CSTURB, TBUCONF, TURBN,YLDIMPHYEX,& CALL TURB( CST,CSTURB, TBUCONF, TURBN,YLDIMPHYEX,&
IMI, NRR, NRRL, NRRI, CLBCX, CLBCY, 1, NMODEL_CLOUD, & IMI, NRR, NRRL, NRRI, CLBCX, CLBCY, 1, NMODEL_CLOUD, &
......
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