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

Last change on this file since 4768 was 4745, checked in by evignon, 11 months ago

nettoyage et corrections dans les routines atke pour utilisation en 3D (terre + mars)

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