source: LMDZ6/trunk/libf/phylmd/atke_turbulence_ini_mod.F90 @ 4660

Last change on this file since 4660 was 4653, checked in by evignon, 15 months ago

prise en compte de l'humidite pour le calcul du flux de flottabilite dans atke
+ petits ajustements

File size: 3.7 KB
Line 
1MODULE atke_turbulence_ini_mod
2
3implicit none
4
5save
6
7integer :: iflag_atke, iflag_num_atke, iflag_atke_lmix
8  !$OMP THREADPRIVATE(iflag_atke, iflag_num_atke, iflag_atke_lmix)
9  real :: kappa = 0.4 ! Von Karman constant
10  !$OMP THREADPRIVATE(kappa)
11  real :: l0, ric, ri0, cinf, cepsilon, pr_slope, pr_asym, pr_neut, clmix, smmin, ctkes,cke
12  !$OMP THREADPRIVATE(l0,ric,cinf,cepsilon,pr_slope,pr_asym,pr_neut,clmix,smmin,ctkes,cke)
13  integer :: lunout,prt_level
14  !$OMP THREADPRIVATE(lunout,prt_level)
15  real :: rg, rd, rpi, rcpd, rv
16  !$OMP THREADPRIVATE(rg, rd, rpi, rcpd, rv)
17
18  real :: viscom, viscoh
19  !$OMP THREADPRIVATE(viscom,viscoh)
20
21  real :: lmin=0.01              ! minimum mixing length
22  !$OMP THREADPRIVATE(lmin)
23
24  logical :: atke_ok_vdiff, atke_ok_virtual
25  !$OMP THREADPRIVATE(atke_ok_vdiff,atke_ok_virtual)
26
27CONTAINS
28
29SUBROUTINE atke_ini(prt_level_in, lunout_in, rg_in, rd_in, rpi_in, rcpd_in, rv_in)
30
31   USE ioipsl_getin_p_mod, ONLY : getin_p
32
33  integer, intent(in) :: lunout_in,prt_level_in
34  real, intent(in) :: rg_in, rd_in, rpi_in, rcpd_in, rv_in
35
36
37  lunout=lunout_in
38  prt_level=prt_level_in
39  rd=rd_in
40  rg=rg_in
41  rpi=rpi_in
42  rcpd=rcpd_in
43  rv=rv_in
44
45  viscom=1.46E-5
46  viscoh=2.06E-5
47
48  ! flag that controls options in atke_compute_km_kh
49  iflag_atke=0
50  CALL getin_p('iflag_atke',iflag_atke)
51
52  ! flag that controls the calculation of mixing length in atke
53  iflag_atke_lmix=0
54  CALL getin_p('iflag_atke_lmix',iflag_atke_lmix)
55
56  if (iflag_atke .eq. 0 .and. iflag_atke_lmix>0) then
57        call abort_physic("atke_turbulence_ini", &
58        'stationary scheme must use mixing length formulation not depending on tke', 1)
59  endif
60
61  ! activate vertical diffusion of TKE or not
62  atke_ok_vdiff=.false.
63  CALL getin_p('atke_ok_vdiff',atke_ok_vdiff)
64
65
66  ! account for vapor for flottability
67  atke_ok_virtual=.true.
68  CALL getin_p('atke_ok_virtual',atke_ok_virtual)
69
70
71  ! flag that controls the numerical treatment of diffusion coeffiient calculation
72  iflag_num_atke=0
73  CALL getin_p('iflag_num_atke',iflag_num_atke)
74
75  ! asymptotic mixing length in neutral conditions [m]
76  ! Sun et al 2011, JAMC
77  ! between 10 and 40
78
79  l0=15.0
80  CALL getin_p('atke_l0',l0)
81
82  ! critical Richardson number
83  ric=0.25
84  CALL getin_p('atke_ric',ric)
85
86  ! asymptotic value of Sm for Ri=-Inf
87  cinf=1.5
88  CALL getin_p('atke_cinf',cinf)
89
90  ! constant for tke dissipation calculation
91  cepsilon=5.87 ! default value as in yamada4
92  CALL getin_p('atke_cepsilon',cepsilon)
93
94
95 ! coefficient for surface TKE
96 ! following Lenderink & Holtslag 2004, ctkes=sqrt(cepsilon)
97 ! (provided by limit condition in neutral conditions)
98  ctkes=sqrt(cepsilon)
99
100
101  ! slope of Pr=f(Ri) for stable conditions
102  pr_slope=5.0 ! default value from Zilitinkevich et al. 2005
103  CALL getin_p('atke_pr_slope',pr_slope)
104  if (pr_slope .le. 1) then
105        call abort_physic("atke_turbulence_ini", &
106        'pr_slope has to be greater than 1 for consistency of the tke scheme', 1)
107  endif
108
109  ! asymptotic turbulent prandt number value for Ri=-Inf
110  pr_asym=0.4
111  CALL getin_p('atke_pr_asym',pr_asym)
112
113  ! value of turbulent prandtl number in neutral conditions (Ri=0)
114  pr_neut=0.8
115  CALL getin_p('atke_pr_neut',pr_neut)
116
117  ! coefficient for mixing length depending on local stratification
118  clmix=0.5
119  CALL getin_p('atke_clmix',clmix)
120 
121  ! minimum anisotropy coefficient (defined here as minsqrt(Ez/Ek)) at large Ri.
122  ! From Zilitinkevich et al. 2013, it equals sqrt(0.03)~0.17
123 
124  smmin=0.17
125  CALL getin_p('atke_smmin',smmin)
126
127
128  ! ratio between the eddy diffusivity coeff for tke wrt that for momentum
129  ! default value from Lenderink et al. 2004
130  cke=2.
131  CALL getin_p('atke_cke',cke)
132
133 RETURN
134
135END SUBROUTINE atke_ini
136
137END MODULE  atke_turbulence_ini_mod
Note: See TracBrowser for help on using the repository browser.