Newer
Older
!MNH_LIC Copyright 1994-2020 CNRS, Meteo-France and Universite Paul Sabatier
!MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1.
!-----------------------------------------------------------------
! ####################
MODULE MODE_PRANDTL
USE PARKIND1, ONLY : JPRB
USE YOMHOOK , ONLY : LHOOK, DR_HOOK
! ####################
!
!* modification 08/2010 V. Masson smoothing of the discontinuity in functions
! used for implicitation of exchange coefficients
! 05/2020 V. Masson and C. Lac : bug in D_PHI3DTDZ2_O_DDTDZ

RODIER Quentin
committed
USE MODD_CTURB, ONLY : CSTURB_t
USE MODD_TURB_n, ONLY : TURB_t
USE MODD_DIMPHYEX, ONLY : DIMPHYEX_t

RODIER Quentin
committed
USE MODD_PARAMETERS, ONLY : JPVEXT_TURB
USE MODE_SHUMAN_PHY, ONLY: MZM_PHY,MZF_PHY

RODIER Quentin
committed
USE MODE_GRADIENT_M_PHY
IMPLICIT NONE
!----------------------------------------------------------------------------
CONTAINS
!----------------------------------------------------------------------------
SUBROUTINE PRANDTL(D,CST,CSTURB,TURBN,KRR,KSV,KRRI,OTURB_DIAG,&
HTURBDIM,OOCEAN,OHARAT,O2D,OCOMPUTE_SRC,&

RODIER Quentin
committed
TPFILE, OFLAT, &
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
PDXX,PDYY,PDZZ,PDZX,PDZY, &
PTHVREF,PLOCPEXNM,PATHETA,PAMOIST, &
PLM,PLEPS,PTKEM,PTHLM,PRM,PSVM,PSRCM, &
PREDTH1,PREDR1, &
PRED2TH3, PRED2R3, PRED2THR3, &
PREDS1,PRED2THS3, PRED2RS3, &
PBLL_O_E, &
PETHETA, PEMOIST )
! ###########################################################
!
!
!!**** *PRANDTL* - routine to compute the Prandtl turbulent numbers
!!
!! PURPOSE
!! -------
! The purpose of this routine is to compute the Redelsperger
! numbers and then get the turbulent Prandtl and Schmidt numbers:
! * for the heat fluxes - PHI3 = 1/ Prandtl
! * for the moisture fluxes - PSI3 = 1/ Schmidt
!
!!** METHOD
!! ------
!! The following steps are performed:
!!
!! 1 - default values of 1 are taken for phi3 and psi3 and different masks
!! are defined depending on the presence of turbulence, stratification and
!! humidity. The 1D Redelsperger numbers are computed
!! * ZREDTH1 : (g / THVREF ) (LT**2 / TKE ) ETHETA (D Theta / Dz)
!! * ZREDR1 : (g / THVREF ) (LT**2 / TKE ) EMOIST (D TW / Dz)
!! 2 - 3D Redelsperger numbers are computed only for turbulent
!! grid points where ZREDTH1 or ZREDR1 are > 0.
!! 3 - PHI3 is computed only for turbulent grid points where ZREDTH1 > 0
!! (turbulent thermally stratified points)
!! 4 - PSI3 is computed only for turbulent grid points where ZREDR1 > 0
!! (turbulent moist points)
!!
!!
!! EXTERNAL
!! --------
!! FUNCTIONs ETHETA and EMOIST :
!! allows to compute the coefficients
!! for the turbulent correlation between any variable
!! and the virtual potential temperature, of its correlations
!! with the conservative potential temperature and the humidity
!! conservative variable:
!! ------- ------- -------
!! A' Thv' = ETHETA A' Thl' + EMOIST A' Rnp'
!!
!! GX_M_M, GY_M_M, GZ_M_M : Cartesian gradient operators
!! MZM : Shuman function (mean operator in the z direction)
!! Module MODI_ETHETA : interface module for ETHETA
!! Module MODI_EMOIST : interface module for EMOIST
!! Module MODI_SHUMAN : interface module for Shuman operators
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!! Module MODD_CST : contains physical constants

RODIER Quentin
committed
!! CST%XG : gravity constant
!!
!! Module MODD_CTURB: contains the set of constants for
!! the turbulence scheme
!! TURBN%XCTV,XCPR2 : constants for the turbulent prandtl numbers
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
!! XTKEMIN : minimum value allowed for the TKE
!!
!! Module MODD_PARAMETERS
!! JPVEXT_TURB : number of vertical marginal points
!!
!! REFERENCE
!! ---------
!! Book 2 of documentation (routine PRANDTL)
!! Book 1 of documentation (Chapter: Turbulence)
!!
!! AUTHOR
!! ------
!! Joan Cuxart * INM and Meteo-France *
!!
!! MODIFICATIONS
!! -------------
!! Original 18/10/94
!! Modifications: Feb 14, 1995 (J.Cuxart and J.Stein)
!! Doctorization and Optimization
!! Modifications: March 21, 1995 (J.M. Carriere)
!! Introduction of cloud water
!! Modifications: March 21, 1995 (J. Cuxart and J.Stein)
!! Phi3 and Psi3 at w point + cleaning
!! Modifications: July 2, 1995 (J.Cuxart and Ph.Bougeault)
!! change the value of Phi3 and Psi3 if negative
!! Modifications: Sept 20, 1995 (J. Stein, J. Cuxart, J.L. Redelsperger)
!! remove the Where + use REDTH1+REDR1 for the tests
!! Modifications: October 10, 1995 (J. Cuxart and J.Stein)
!! Psi3 for tPREDS1he scalar variables
!! Modifications: February 27, 1996 (J.Stein) optimization
!! Modifications: June 15, 1996 (P.Jabouille) return to the previous
!! computation of Phi3 and Psi3
!! Modifications: October 10, 1996 (J. Stein) change the temporal
!! discretization
!! Modifications: May 23, 1997 (J. Stein) bug in 3D Redels number at ground
!! with orography
!! Modifications: Feb 20, 1998 (J. Stein) bug in all the 3D cases due to
!! the use of ZW1 instead of ZW2
!! Feb 20, 2003 (JP Pinty) Add PFRAC_ICE
!! July 2005 (Tomas, Masson) implicitation of PHI3 and PSI3
!! October 2009 (G. Tanguy) add ILENCH=LEN(YCOMMENT) after
!! change of YCOMMENT
!! 2012-02 Y. Seity, add possibility to run with reversed
!! vertical levels

RODIER Quentin
committed
!! Modifications: July 2015 (Wim de Rooy) OHARAT (Racmo turbulence) switch
!! 2017-09 J.Escobar, use epsilon XMNH_TINY_12 for R*4
!! Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O
!! JL Redelsperger 03/2021 : adding Ocean case for temperature only
!! --------------------------------------------------------------------------
!
!* 0. DECLARATIONS
! ------------
!
USE PARKIND1, ONLY : JPRB
USE YOMHOOK , ONLY : LHOOK, DR_HOOK
!
USE MODD_CST, ONLY: CST_t
USE MODD_CTURB, ONLY: CSTURB_t
USE MODD_DIMPHYEX, ONLY: DIMPHYEX_t
USE MODD_FIELD, ONLY: TFIELDMETADATA, TYPEREAL
USE MODD_TURB_n, ONLY: TURB_t
USE MODD_IO, ONLY: TFILEDATA
USE MODD_PARAMETERS, ONLY: JPVEXT_TURB
!
USE MODE_EMOIST, ONLY: EMOIST
USE MODE_ETHETA, ONLY: ETHETA

RODIER Quentin
committed
USE MODE_GRADIENT_M_PHY, ONLY: GX_M_M_PHY, GY_M_M_PHY

RODIER Quentin
committed
USE MODE_IO_FIELD_WRITE_PHY, ONLY: IO_FIELD_WRITE_PHY
!
IMPLICIT NONE
!
!
!* 0.1 declarations of arguments
!
TYPE(DIMPHYEX_t), INTENT(IN) :: D

RODIER Quentin
committed
TYPE(CST_t), INTENT(IN) :: CST
TYPE(CSTURB_t), INTENT(IN) :: CSTURB
TYPE(TURB_t), INTENT(IN) :: TURBN
INTEGER, INTENT(IN) :: KSV ! number of scalar variables
INTEGER, INTENT(IN) :: KRR ! number of moist var.
INTEGER, INTENT(IN) :: KRRI ! number of ice var.
!
LOGICAL, INTENT(IN) :: OTURB_DIAG ! switch to write some
! diagnostic fields in the syncronous FM-file
LOGICAL, INTENT(IN) :: OOCEAN ! switch for Ocean model version

RODIER Quentin
committed
LOGICAL, INTENT(IN) :: OHARAT
LOGICAL, INTENT(IN) :: OCOMPUTE_SRC ! flag to define dimensions of SIGS and
LOGICAL, INTENT(IN) :: O2D ! Logical for 2D model version (modd_conf)

RODIER Quentin
committed
LOGICAL, INTENT(IN) :: OFLAT ! Logical for zero ororography
CHARACTER(LEN=4), INTENT(IN) :: HTURBDIM ! Kind of turbulence param.
TYPE(TFILEDATA), INTENT(IN) :: TPFILE ! Output file
REAL, DIMENSION(D%NIJT,D%NKT), INTENT(IN) :: PDXX,PDYY,PDZZ,PDZX,PDZY
! metric coefficients
!
REAL, DIMENSION(D%NIJT,D%NKT), INTENT(IN) :: PTHVREF ! Virtual Potential Temp.
! of the reference state
REAL, DIMENSION(D%NIJT,D%NKT), INTENT(IN) :: PLOCPEXNM ! Lv(T)/Cp/Exner at t-1
REAL, DIMENSION(D%NIJT,D%NKT), INTENT(IN) :: PATHETA ! coefficients between
REAL, DIMENSION(D%NIJT,D%NKT), INTENT(IN) :: PAMOIST ! s and Thetal and Rnp
!
REAL, DIMENSION(D%NIJT,D%NKT), INTENT(IN) :: PLM ! Turbulent Mixing length
REAL, DIMENSION(D%NIJT,D%NKT), INTENT(IN) :: PLEPS ! Dissipative length
REAL, DIMENSION(D%NIJT,D%NKT), INTENT(IN) :: PTHLM,PTKEM! Conservative Potential
! Temperature and TKE at t-1
REAL, DIMENSION(D%NIJT,D%NKT,KRR), INTENT(IN) :: PRM ! Mixing ratios at t-1
! with PRM(:,:,:,1) = cons.
! mixing ratio
REAL, DIMENSION(D%NIJT,D%NKT,KSV), INTENT(IN) :: PSVM ! Scalars at t-1
Loading
Loading full blame...