source: LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_atke_turbulence_ini.F90 @ 5136

Last change on this file since 5136 was 5117, checked in by abarral, 2 months ago

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

File size: 8.2 KB
Line 
1MODULE lmdz_atke_turbulence_ini
2
3  IMPLICIT NONE
4
5  ! declaration of constants and parameters
6
7  REAL, SAVE, protected :: rg, rd, rpi, rcpd, rv, viscom, viscoh
8  !$OMP THREADPRIVATE(rg, rd, rpi, rcpd, rv, viscom, viscoh)
9
10  INTEGER, SAVE, protected :: iflag_atke        ! flag that controls options in atke_compute_km_kh
11  INTEGER, SAVE, protected :: iflag_atke_lmix   ! flag that controls the calculation of mixing length in atke
12  INTEGER, SAVE, protected :: iflag_num_atke    ! flag that controls the numerical treatment of diffusion coeffiient calculation
13  !$OMP THREADPRIVATE(iflag_atke, iflag_atke_lmix, iflag_num_atke)
14
15  logical, SAVE, protected :: atke_ok_vdiff    ! activate vertical diffusion of TKE or not
16  logical, SAVE, protected :: atke_ok_virtual  ! account for vapor for flottability
17  !$OMP THREADPRIVATE(atke_ok_vdiff, atke_ok_virtual)
18
19  REAL, SAVE, protected :: kappa = 0.4         ! Von Karman constant
20  REAL, SAVE, protected :: cn                  ! Sm value at Ri=0
21  REAL, SAVE, protected :: cinf                ! Sm value at Ri=-Inf
22  REAL, SAVE, protected :: ri0                 ! Richardson number near zero to guarantee continuity in slope of Sm (stability function) at Ri=0
23  REAL, SAVE, protected :: ri1                 ! Richardson number near zero to guarantee continuity in slope of Pr (Prandlt's number) at Ri=0
24  REAL, SAVE, protected :: lmin = 0.01         ! minimum mixing length corresponding to the Kolmogov dissipation scale  in planetary atmospheres (Chen et al 2016, JGR Atmos)
25  REAL, SAVE, protected :: ctkes               ! coefficient for surface TKE
26  REAL, SAVE, protected :: clmixshear          ! coefficient for mixing length depending on local wind shear
27  !$OMP THREADPRIVATE(kappa, cn, cinf, ri0, ri1, lmin, ctkes, clmixshear)
28
29
30  ! Tunable parameters for the ATKE scheme and their range of values
31  !!-------------------------------------------------------------------------------------------------------------
32  REAL, SAVE, protected :: cepsilon            ! controls the value of the dissipation length scale, range [1.2 - 10]
33  REAL, SAVE, protected :: cke                 ! controls the value of the diffusion coefficient of TKE, range [1 - 5]
34  REAL, SAVE, protected :: l0                  ! asymptotic mixing length far from the ground [m] (Sun et al 2011, JAMC), range [15 - 75]
35  REAL, SAVE, protected :: clmix               ! controls the value of the mixing length in stratified conditions, range [0.1 - 2]
36  REAL, SAVE, protected :: ric                 ! critical Richardson number controlling the slope of Sm in stable conditions, range [0.19 - 0.25]
37  REAL, SAVE, protected :: smmin               ! minimum value of Sm in very stable conditions (defined here as minsqrt(Ez/Ek)) at large Ri, range [0.025 - 0.1]
38  REAL, SAVE, protected :: pr_neut             ! neutral value of the Prandtl number (Ri=0), range [0.7 - 1]
39  REAL, SAVE, protected :: pr_slope            ! linear slope of Pr with Ri in the very stable regime, range [3 - 5]
40  REAL, SAVE, protected :: cinffac             ! ratio between cinf and cn controlling the convective limit of Sm, range [1.2 - 5.0]
41  REAL, SAVE, protected :: pr_asym             ! value of Prandlt in the convective limit(Ri=-Inf), range [0.3 - 0.5]
42  !$OMP THREADPRIVATE(cepsilon, cke, l0, clmix, ric, smmin, pr_neut, pr_slope, cinffac, pr_asym)
43  !!-------------------------------------------------------------------------------------------------------------
44
45CONTAINS
46
47  SUBROUTINE atke_ini(rg_in, rd_in, rpi_in, rcpd_in, rv_in, viscom_in, viscoh_in)
48    !!----------------------------------------------------------------------
49    !!                  ***  ROUTINE  atke_ini  ***
50    !!
51    !! ** Purpose :   Initialization of the atke module and choice of some constants
52    !!
53    !!----------------------------------------------------------------------
54
55    USE lmdz_ioipsl_getin_p, ONLY: getin_p
56    USE lmdz_abort_physic, ONLY: abort_physic
57
58    ! input arguments (universal constants for planet)
59    !-------------------------------------------------
60    REAL, INTENT(IN) :: rg_in, rd_in, rpi_in, rcpd_in, rv_in, viscom_in, viscoh_in
61    !!----------------------------------------------------------------------
62
63    rg = rg_in          ! gravity acceleration
64    rd = rd_in          ! dry gas constant (R/M, R=perfect gas constant and M is the molar mass of the fluid)
65    rpi = rpi_in        ! Pi number
66    rcpd = rcpd_in      ! cp per unit mass of the gas
67    rv = rv_in          ! water vapor constant (for simulations in Earth's atmosphere)
68    viscom = viscom_in  ! kinematic molecular viscosity for momentum
69    viscoh = viscoh_in  ! kinematic molecular viscosity for heat
70
71
72    ! Read flag values in .def files
73    !-------------------------------
74
75    ! flag that controls options in atke_compute_km_kh
76    iflag_atke = 0
77    CALL getin_p('iflag_atke', iflag_atke)
78
79    ! flag that controls the calculation of mixing length in atke
80    iflag_atke_lmix = 0
81    CALL getin_p('iflag_atke_lmix', iflag_atke_lmix)
82
83    IF (iflag_atke == 0 .AND. iflag_atke_lmix>0) THEN
84      CALL abort_physic("atke_turbulence_ini", &
85              'stationary scheme must use mixing length formulation not depending on tke', 1)
86    endif
87
88    ! activate vertical diffusion of TKE or not
89    atke_ok_vdiff = .FALSE.
90    CALL getin_p('atke_ok_vdiff', atke_ok_vdiff)
91
92    ! account for vapor for flottability
93    atke_ok_virtual = .TRUE.
94    CALL getin_p('atke_ok_virtual', atke_ok_virtual)
95
96
97    ! flag that controls the numerical treatment of diffusion coeffiient calculation
98    iflag_num_atke = 0
99    CALL getin_p('iflag_num_atke', iflag_num_atke)
100
101    ! asymptotic mixing length in neutral conditions [m]
102    ! Sun et al 2011, JAMC
103    ! between 10 and 40
104    l0 = 15.0
105    CALL getin_p('atke_l0', l0)
106
107    ! critical Richardson number
108    ric = 0.25
109    CALL getin_p('atke_ric', ric)
110
111    ! constant for tke dissipation calculation
112    cepsilon = 5.87 ! default value as in yamada4
113    CALL getin_p('atke_cepsilon', cepsilon)
114
115    ! calculation of cn = Sm value at Ri=0
116    ! direct dependance on cepsilon to guarantee Fm=1 (first-order like stability function) at Ri=0
117    cn = (1. / sqrt(cepsilon))**(2 / 3)
118
119    ! asymptotic value of Sm for Ri=-Inf
120    cinffac = 2.0
121    CALL getin_p('atke_cinffac', cinffac)
122    cinf = cinffac * cn
123    IF (cinf <= cn) THEN
124      CALL abort_physic("atke_turbulence_ini", &
125              'cinf cannot be lower than cn', 1)
126    endif
127
128    ! coefficient for surface TKE
129    ! following Lenderink & Holtslag 2004, ctkes=(cepsilon)**(2/3)
130    ! (provided by limit condition in neutral conditions)
131    ctkes = (cepsilon)**(2. / 3.)
132
133    ! slope of Pr=f(Ri) for stable conditions
134    pr_slope = 5.0 ! default value from Zilitinkevich et al. 2005
135    CALL getin_p('atke_pr_slope', pr_slope)
136    IF (pr_slope <= 1) THEN
137      CALL abort_physic("atke_turbulence_ini", &
138              'pr_slope has to be greater than 1 for consistency of the tke scheme', 1)
139    endif
140
141    ! value of turbulent prandtl number in neutral conditions (Ri=0)
142    pr_neut = 0.8
143    CALL getin_p('atke_pr_neut', pr_neut)
144
145    ! asymptotic turbulent prandt number value for Ri=-Inf
146    pr_asym = 0.4
147    CALL getin_p('atke_pr_asym', pr_asym)
148    IF (pr_asym >= pr_neut) THEN
149      CALL abort_physic("atke_turbulence_ini", &
150              'pr_asym must be be lower than pr_neut', 1)
151    endif
152
153    ! coefficient for mixing length depending on local stratification
154    clmix = 0.5
155    CALL getin_p('atke_clmix', clmix)
156
157    ! coefficient for mixing length depending on local wind shear
158    clmixshear = 0.5
159    CALL getin_p('atke_clmixshear', clmixshear)
160
161    ! minimum anisotropy coefficient (defined here as minsqrt(Ez/Ek)) at large Ri.
162    ! From Zilitinkevich et al. 2013, it equals sqrt(0.03)~0.17
163    smmin = 0.17
164    CALL getin_p('atke_smmin', smmin)
165
166    ! ratio between the eddy diffusivity coeff for tke wrt that for momentum
167    ! default value from Lenderink et al. 2004
168    cke = 2.
169    CALL getin_p('atke_cke', cke)
170
171    ! calculation of Ri0 such that continuity in slope of Sm at Ri=0
172    ri0 = 2. / rpi * (cinf - cn) * ric / cn
173
174    ! calculation of Ri1 to guarantee continuity in slope of Prandlt number at Ri=0
175    ri1 = -2. / rpi * (pr_asym - pr_neut)
176
177  END SUBROUTINE atke_ini
178
179END MODULE  lmdz_atke_turbulence_ini
Note: See TracBrowser for help on using the repository browser.