source: trunk/LMDZ.GENERIC/libf/phystd/thermcell_mod.F90 @ 2092

Last change on this file since 2092 was 2092, checked in by aboissinot, 6 years ago

Uncomment two "corrections" (or "bidouilles" ccording to the author) in thermcell_flux. They are used only if
iflag_thermals_optflux is set to 0

Remove useless parameter fact_shell in thermcell_mod.

File size: 4.1 KB
Line 
1MODULE thermcell_mod
2     
3      IMPLICIT NONE
4     
5     
6! Flags for computations
7                                                                  !  default
8      INTEGER,PARAMETER :: iflag_thermals_optflux     = 1         !  0        !
9      INTEGER,PARAMETER :: iflag_thermals_closure     = 2         !  2        !
10      INTEGER,PARAMETER :: iflag_thermals             = 18        !  18       !
11     
12! Flags for (terrestrial) diagnoses
13     
14      LOGICAL,PARAMETER :: sorties                    = .false.   !  false
15      INTEGER,PARAMETER :: iflag_trig_bl              = 1         !  1
16      INTEGER,PARAMETER :: iflag_clos_bl              = 1         !  1
17      INTEGER,PARAMETER :: iflag_coupl                = 5         !  5
18     
19! Physical parameters
20     
21      REAL,PARAMETER :: fact_thermals_ed_dz           = 0.007     !  0.007    !
22      REAL,PARAMETER :: r_aspect_thermals             = 1.0       !           Aspect ratio of the thermals (width / height)
23      REAL,PARAMETER :: tau_thermals                  = 0.        !  0.       Relaxation time
24      REAL,PARAMETER :: betalpha                      = 0.9       !  0.9      !
25      REAL,PARAMETER :: afact                         = 2./3.     !  2./3.    !
26      REAL,PARAMETER :: fact_epsilon                  = 0.000     !  0.002    !
27      REAL,PARAMETER :: detr_q_power                  = 0.5       !  0.5      !
28      REAL,PARAMETER :: detr_q_coef                   = 0.012     !  0.012    !
29      REAL,PARAMETER :: mix0                          = 0.        !  0.       !
30      REAL,PARAMETER :: detr_min                      = 1.d-5     !  1.e-5    Minimal detrainment value
31      REAL,PARAMETER :: entr_min                      = 1.d-5     !  1.e-5    Maximal detrainment value
32      REAL,PARAMETER :: alphamax                      = 0.7       !           Maximal permitted updraft fraction
33      REAL,PARAMETER :: fomass_max                    = 0.5       !           Maximal permitted outgoing layer mass fraction
34      REAL,PARAMETER :: pres_limit                    = 1.e5      !  1.e5     !
35     
36!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
37! AB : linf is used to set the lowest possible first level because we allow it
38!      to begin higher than the surface. It is set to 2 in order to remove the
39!      first layer for gas giant.
40!      If there is a surface, it has to be set to 1.
41!      If someone want to call more than once the thermal plume model in some
42!      grid points, this variable may become a saved array of INTEGER with size
43!      ngrid.
44!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
45      INTEGER,PARAMETER :: linf                       = 2         !     1
46     
47!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
48! AB : d_temp is an artificial virtual potential temperature offset added in
49!      layer linf which can be used to force convection to begin in it.
50!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
51      REAL,PARAMETER :: d_temp                        = 0.        !     0.
52     
53! Parameters for diagnoses
54     
55      REAL,PARAMETER :: alp_bl_k                      = 0.5       !     0.5
56     
57! Physical constants
58     
59      REAL,SAVE :: RTT
60      REAL,SAVE :: RG
61      REAL,SAVE :: RKAPPA
62      REAL,SAVE :: RPI
63      REAL,SAVE :: RD
64     
65!$OMP THREADPRIVATE(RTT, RG, RKAPPA, RPI, RD)
66     
67!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
68! AB : Parameters needed only for a loop in thermcell_alp (diagnoses).
69!      Maybe to be removed.
70!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
71      INTEGER,PARAMETER :: nbsrf                      = 1
72     
73     
74      CONTAINS
75     
76      SUBROUTINE init_thermcell_mod(g, rcp, r, pi, T_h2o_ice_liq, RV)
77         
78         IMPLICIT NONE
79         
80         REAL g
81         REAL rcp
82         REAL r
83         REAL pi
84         REAL T_h2o_ice_liq
85         REAL RV
86         
87         RTT = T_h2o_ice_liq
88         RG = g
89         RKAPPA = rcp
90         RPI = pi
91         RD = r
92         
93         RETURN
94      END SUBROUTINE init_thermcell_mod
95     
96END MODULE thermcell_mod
Note: See TracBrowser for help on using the repository browser.