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

Last change on this file since 4640 was 4632, checked in by evignon, 12 months ago

petits ajustements suite a la derniere commission

File size: 2.8 KB
RevLine 
[4449]1MODULE atke_turbulence_ini_mod
2
3implicit none
4
5save
6
[4631]7integer :: iflag_atke, iflag_num_atke, iflag_atke_lmix
8  !$OMP THREADPRIVATE(iflag_atke, iflag_num_atke, iflag_atke_lmix)
[4449]9  real :: kappa = 0.4 ! Von Karman constant
10  !$OMP THREADPRIVATE(kappa)
[4631]11  real :: l0, ric, ri0, cinf, cepsilon, pr_slope, pr_asym, pr_neut, clmix
12  !$OMP THREADPRIVATE(l0, ric, cinf, cepsilon, pr_slope, pr_asym, pr_neut, clmix)
[4449]13  integer :: lunout,prt_level
14  !$OMP THREADPRIVATE(lunout,prt_level)
[4478]15  real :: rg, rd, rpi, rcpd
16  !$OMP THREADPRIVATE(rg, rd, rpi, rcpd)
[4449]17
[4478]18  real :: viscom, viscoh
19  !$OMP THREADPRIVATE(viscom,viscoh)
[4449]20
[4631]21  real :: lmin=0.001              ! minimum mixing length
22  !$OMP THREADPRIVATE(lmin)
[4478]23
24
[4449]25CONTAINS
26
[4478]27SUBROUTINE atke_ini(prt_level_in, lunout_in, rg_in, rd_in, rpi_in, rcpd_in)
[4449]28
29   USE ioipsl_getin_p_mod, ONLY : getin_p
30
31  integer, intent(in) :: lunout_in,prt_level_in
[4478]32  real, intent(in) :: rg_in, rd_in, rpi_in, rcpd_in
[4449]33
34
35  lunout=lunout_in
36  prt_level=prt_level_in
37  rd=rd_in
38  rg=rg_in
39  rpi=rpi_in
[4478]40  rcpd=rcpd_in
[4449]41
[4478]42  viscom=1.46E-5
43  viscoh=2.06E-5
44
[4449]45  ! flag that controls options in atke_compute_km_kh
46  iflag_atke=0
47  CALL getin_p('iflag_atke',iflag_atke)
48
[4631]49  ! flag that controls the calculation of mixing length in atke
50  iflag_atke_lmix=0
51  CALL getin_p('iflag_atke_lmix',iflag_atke_lmix)
52
53  if (iflag_atke .eq. 0 .and. iflag_atke_lmix>0) then
54        call abort_physic("atke_turbulence_ini", &
55        'stationary scheme must use mixing length formulation not depending on tke', 1)
56  endif
57
58
[4545]59  ! flag that controls the numerical treatment of diffusion coeffiient calculation
60  iflag_num_atke=0
61  CALL getin_p('iflag_num_atke',iflag_num_atke)
62
[4631]63  ! asymptotic mixing length in neutral conditions [m]
64  ! Sun et al 2011, JAMC
65  ! between 10 and 40
66
67  l0=15.0
[4449]68  CALL getin_p('atke_l0',l0)
69
70  ! critical Richardson number
71  ric=0.25
72  CALL getin_p('atke_ric',ric)
73
74  ! asymptotic value of Sm for Ri=-Inf
75  cinf=1.5
76  CALL getin_p('atke_cinf',cinf)
77
78  ! constant for tke dissipation calculation
[4631]79  cepsilon=16.6/2./sqrt(2.) ! default value as in yamada4
[4449]80  CALL getin_p('atke_cepsilon',cepsilon)
81
82  ! slope of Pr=f(Ri) for stable conditions
83  pr_slope=5.0 ! default value from Zilitinkevich et al. 2005
84  CALL getin_p('atke_pr_slope',pr_slope)
[4631]85  if (pr_slope .le. 1) then
86        call abort_physic("atke_turbulence_ini", &
87        'pr_slope has to be greater than 1 for consistency of the tke scheme', 1)
88  endif
[4449]89
90  ! asymptotic turbulent prandt number value for Ri=-Inf
91  pr_asym=0.4
92  CALL getin_p('atke_pr_asym',pr_asym)
93
[4478]94  ! value of turbulent prandtl number in neutral conditions (Ri=0)
[4481]95  pr_neut=0.8
[4478]96  CALL getin_p('atke_pr_neut',pr_neut)
97
[4631]98  ! coefficient for mixing length depending on local stratification
[4632]99  clmix=0.5
[4631]100  CALL getin_p('atke_clmix',clmix)
[4449]101   
102 RETURN
103
104END SUBROUTINE atke_ini
105
106END MODULE  atke_turbulence_ini_mod
Note: See TracBrowser for help on using the repository browser.