source: trunk/LMDZ.MARS/libf/phymars/lmdz_atke_turbulence_ini.F90 @ 3400

Last change on this file since 3400 was 3168, checked in by llange, 11 months ago

Mars PCM
Following previous commit, add the functions for ATKE turbulence in the svn brench (yes I forgot the svn add...)
LL

File size: 5.1 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  ! Read flag values in .def files
57  !-------------------------------
58
59
60  ! flag that controls options in atke_compute_km_kh
61  iflag_atke=0
62  CALL getin_p('iflag_atke',iflag_atke)
63
64  ! flag that controls the calculation of mixing length in atke
65  iflag_atke_lmix=0
66  CALL getin_p('iflag_atke_lmix',iflag_atke_lmix)
67
68  if (iflag_atke .eq. 0 .and. iflag_atke_lmix>0) then
69        call abort_physic("atke_turbulence_ini", &
70        'stationary scheme must use mixing length formulation not depending on tke', 1)
71  endif
72
73  ! activate vertical diffusion of TKE or not
74  atke_ok_vdiff=.false.
75  CALL getin_p('atke_ok_vdiff',atke_ok_vdiff)
76
77
78  ! account for vapor for flottability
79  atke_ok_virtual=.false.
80  CALL getin_p('atke_ok_virtual',atke_ok_virtual)
81
82
83  ! flag that controls the numerical treatment of diffusion coeffiient calculation
84  iflag_num_atke=0
85  CALL getin_p('iflag_num_atke',iflag_num_atke)
86
87  ! asymptotic mixing length in neutral conditions [m]
88  ! Sun et al 2011, JAMC
89  ! between 10 and 40
90  l0=15.0
91  CALL getin_p('atke_l0',l0)
92
93  ! critical Richardson number
94  ric=0.25
95  CALL getin_p('atke_ric',ric)
96
97
98  ! constant for tke dissipation calculation
99  cepsilon=5.87 ! default value as in yamada4
100  CALL getin_p('atke_cepsilon',cepsilon)
101
102
103  ! calculation of cn = Sm value at Ri=0
104  ! direct dependance on cepsilon to guarantee Fm=1 (first-order like stability function) at Ri=0
105  cn=(1./sqrt(cepsilon))**(2/3)
106
107  ! asymptotic value of Sm for Ri=-Inf
108  cinffac=2.0
109  CALL getin_p('atke_cinffac',cinffac)
110  cinf=cinffac*cn
111  if (cinf .le. cn) then
112        call abort_physic("atke_turbulence_ini", &
113        'cinf cannot be lower than cn', 1)
114  endif
115
116
117 ! coefficient for surface TKE
118 ! following Lenderink & Holtslag 2004, ctkes=(cepsilon)**(2/3)
119 ! (provided by limit condition in neutral conditions)
120  ctkes=(cepsilon)**(2./3.)
121
122  ! slope of Pr=f(Ri) for stable conditions
123  pr_slope=5.0 ! default value from Zilitinkevich et al. 2005
124  CALL getin_p('atke_pr_slope',pr_slope)
125  if (pr_slope .le. 1) then
126        call abort_physic("atke_turbulence_ini", &
127        'pr_slope has to be greater than 1 for consistency of the tke scheme', 1)
128  endif
129
130  ! value of turbulent prandtl number in neutral conditions (Ri=0)
131  pr_neut=0.8
132  CALL getin_p('atke_pr_neut',pr_neut)
133
134
135 ! asymptotic turbulent prandt number value for Ri=-Inf
136  pr_asym=0.4
137  CALL getin_p('atke_pr_asym',pr_asym)
138  if (pr_asym .ge. pr_neut) then
139        call abort_physic("atke_turbulence_ini", &
140        'pr_asym must be be lower than pr_neut', 1)
141  endif
142
143
144
145  ! coefficient for mixing length depending on local stratification
146  clmix=0.5
147  CALL getin_p('atke_clmix',clmix)
148 
149  ! coefficient for mixing length depending on local wind shear
150  clmixshear=0.5
151  CALL getin_p('atke_clmixshear',clmixshear)
152
153
154  ! minimum anisotropy coefficient (defined here as minsqrt(Ez/Ek)) at large Ri.
155  ! From Zilitinkevich et al. 2013, it equals sqrt(0.03)~0.17 
156  smmin=0.17
157  CALL getin_p('atke_smmin',smmin)
158
159
160  ! ratio between the eddy diffusivity coeff for tke wrt that for momentum
161  ! default value from Lenderink et al. 2004
162  cke=2.
163  CALL getin_p('atke_cke',cke)
164
165
166  ! calculation of Ri0 such that continuity in slope of Sm at Ri=0
167  ri0=2./rpi*(cinf - cn)*ric/cn
168
169  ! calculation of Ri1 to guarantee continuity in slope of Prandlt number at Ri=0
170  ri1 = -2./rpi * (pr_asym - pr_neut)
171
172
173 RETURN
174
175END SUBROUTINE atke_ini
176
177END MODULE  lmdz_atke_turbulence_ini
Note: See TracBrowser for help on using the repository browser.