source: LMDZ6/trunk/libf/phylmd/lmdz_atke_turbulence_ini.F90 @ 4781

Last change on this file since 4781 was 4781, checked in by evignon, 10 months ago

petite correction commit precedent

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