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

Last change on this file since 5209 was 5172, checked in by abarral, 11 days ago

Merge r5164, r5166, r5167, r5168

File size: 8.3 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    !!Default values correspond to the  'best' configuration
53      !!                from tuning on GABLS1 in Vignon et al. 2024, JAMES
54    !!----------------------------------------------------------------------
55
56    USE lmdz_ioipsl_getin_p, ONLY: getin_p
57    USE lmdz_abort_physic, ONLY: abort_physic
58
59    ! input arguments (universal constants for planet)
60    !-------------------------------------------------
61    REAL, INTENT(IN) :: rg_in, rd_in, rpi_in, rcpd_in, rv_in, viscom_in, viscoh_in
62    !!----------------------------------------------------------------------
63
64    rg = rg_in          ! gravity acceleration
65    rd = rd_in          ! dry gas constant (R/M, R=perfect gas constant and M is the molar mass of the fluid)
66    rpi = rpi_in        ! Pi number
67    rcpd = rcpd_in      ! cp per unit mass of the gas
68    rv = rv_in          ! water vapor constant (for simulations in Earth's atmosphere)
69    viscom = viscom_in  ! kinematic molecular viscosity for momentum
70    viscoh = viscoh_in  ! kinematic molecular viscosity for heat
71
72
73    ! Read flag values in .def files
74    !-------------------------------
75
76    ! flag that controls options in atke_compute_km_kh
77    iflag_atke = 1
78    CALL getin_p('iflag_atke', iflag_atke)
79
80    ! flag that controls the calculation of mixing length in atke
81    iflag_atke_lmix = 3
82    CALL getin_p('iflag_atke_lmix', iflag_atke_lmix)
83
84    IF (iflag_atke == 0 .AND. iflag_atke_lmix>0) THEN
85      CALL abort_physic("atke_turbulence_ini", &
86              'stationary scheme must use mixing length formulation not depending on tke', 1)
87    endif
88
89      ! activate vertical diffusion of TKE or not
90      atke_ok_vdiff = .TRUE.
91      CALL getin_p('atke_ok_vdiff', atke_ok_vdiff)
92
93    ! account for vapor for flottability
94    atke_ok_virtual = .TRUE.
95    CALL getin_p('atke_ok_virtual', atke_ok_virtual)
96
97
98    ! flag that controls the numerical treatment of diffusion coeffiient calculation
99    iflag_num_atke = 0
100    CALL getin_p('iflag_num_atke', iflag_num_atke)
101
102    ! asymptotic mixing length in neutral conditions [m]
103    ! Sun et al 2011, JAMC
104    ! between 10 and 40
105    l0 = 42.5279652116005
106    CALL getin_p('atke_l0', l0)
107
108    ! critical Richardson number
109    ric = 0.190537327781655
110    CALL getin_p('atke_ric', ric)
111
112    ! constant for tke dissipation calculation
113    cepsilon = 8.89273387537601
114    CALL getin_p('atke_cepsilon', cepsilon)
115
116    ! calculation of cn = Sm value at Ri=0
117    ! direct dependance on cepsilon to guarantee Fm=1 (first-order like stability function) at Ri=0
118    cn = (1. / sqrt(cepsilon))**(2 / 3)
119
120    ! asymptotic value of Sm for Ri=-Inf
121    cinffac = 2.0
122    CALL getin_p('atke_cinffac', cinffac)
123    cinf = cinffac * cn
124    IF (cinf <= cn) THEN
125      CALL abort_physic("atke_turbulence_ini", &
126              'cinf cannot be lower than cn', 1)
127    endif
128
129    ! coefficient for surface TKE
130    ! following Lenderink & Holtslag 2004, ctkes=(cepsilon)**(2/3)
131    ! (provided by limit condition in neutral conditions)
132    ctkes = (cepsilon)**(2. / 3.)
133
134    ! slope of Pr=f(Ri) for stable conditions
135    pr_slope = 4.67885738180385
136    CALL getin_p('atke_pr_slope', pr_slope)
137    IF (pr_slope <= 1) THEN
138      CALL abort_physic("atke_turbulence_ini", &
139              'pr_slope has to be greater than 1 for consistency of the tke scheme', 1)
140    endif
141
142    ! value of turbulent prandtl number in neutral conditions (Ri=0)
143    pr_neut = 0.837372701768868
144    CALL getin_p('atke_pr_neut', pr_neut)
145
146    ! asymptotic turbulent prandt number value for Ri=-Inf
147    pr_asym = 0.4
148    CALL getin_p('atke_pr_asym', pr_asym)
149    IF (pr_asym >= pr_neut) THEN
150      CALL abort_physic("atke_turbulence_ini", &
151              'pr_asym must be be lower than pr_neut', 1)
152    endif
153
154    ! coefficient for mixing length depending on local stratification
155    clmix = 0.648055235325291
156    CALL getin_p('atke_clmix', clmix)
157
158    ! coefficient for mixing length depending on local wind shear
159    clmixshear = 0.5
160    CALL getin_p('atke_clmixshear', clmixshear)
161
162    ! minimum anisotropy coefficient (defined here as minsqrt(Ez/Ek)) at large Ri.
163    ! From Zilitinkevich et al. 2013, it equals sqrt(0.03)~0.17
164    smmin = 0.0960838631869678
165    CALL getin_p('atke_smmin', smmin)
166
167    ! ratio between the eddy diffusivity coeff for tke wrt that for momentum
168    ! default value from Lenderink et al. 2004
169    cke = 2.47069655134662
170    CALL getin_p('atke_cke', cke)
171
172    ! calculation of Ri0 such that continuity in slope of Sm at Ri=0
173    ri0 = 2. / rpi * (cinf - cn) * ric / cn
174
175    ! calculation of Ri1 to guarantee continuity in slope of Prandlt number at Ri=0
176    ri1 = -2. / rpi * (pr_asym - pr_neut)
177
178  END SUBROUTINE atke_ini
179
180END MODULE  lmdz_atke_turbulence_ini
Note: See TracBrowser for help on using the repository browser.