source: LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_thermcell_ini.F90 @ 5209

Last change on this file since 5209 was 5158, checked in by abarral, 7 weeks ago

Add missing klon on strataer_emiss_mod.F90
Correct various missing explicit declarations
Replace tabs by spaces (tabs are not part of the fortran charset)
Continue cleaning modules
Removed unused arguments and variables

File size: 6.0 KB
Line 
1MODULE lmdz_thermcell_ini
2
3IMPLICIT NONE
4
5INTEGER, protected :: dvdq=1,dqimpl=-1,prt_level=0,lunout
6real   , protected :: RG,RD,RCPD,RKAPPA,RLVTT,RLvCp,RETV
7
8!$OMP THREADPRIVATE(dvdq,dqimpl,prt_level,lunout)
9!$OMP THREADPRIVATE(RG,RD,RCPD,RKAPPA,RLVTT,RLvCp)
10
11
12! Parameters that can be modified directly by a getin call
13REAL,    protected :: r_aspect_thermals=2.       ! Aspect ratio for thermal celles
14REAL,    protected :: tau_thermals = 0.          ! relaxation time constant
15REAL,    protected :: fact_thermals_ed_dz = 0.1  ! bouyancy computed with a delta
16REAL,    protected :: betalpha=0.9               !
17REAL,    protected :: afact=2./3.                !
18REAL,    protected :: fact_shell=1.              !
19REAL,    protected :: detr_min=1.e-5             !
20REAL,    protected :: entr_min=1.e-5             !
21REAL,    protected :: detr_q_coef=0.012          !
22REAL,    protected :: detr_q_power=0.5           !
23REAL,    protected :: mix0=0.                    !
24INTEGER, protected :: iflag_thermals_ed = 0      !
25INTEGER, protected :: iflag_thermals_optflux = 0 !
26INTEGER, protected :: iflag_thermals_closure = 1 !
27INTEGER, protected :: iflag_thermals_down = 0    !
28REAL, protected    :: fact_thermals_down = 0.5   !
29INTEGER, protected :: thermals_flag_alim=0       !
30INTEGER, protected :: iflag_thermals_tenv=0      !
31
32   ! WARNING !!! fact_epsilon is not protected. It can be modified in thermcell_plume*
33   ! depending on other flags.
34
35   REAL               :: fact_epsilon=0.002
36
37!$OMP THREADPRIVATE(r_aspect_thermals,tau_thermals,fact_thermals_ed_dz)
38!$OMP THREADPRIVATE(iflag_thermals_ed,iflag_thermals_optflux,iflag_thermals_closure)
39!$OMP THREADPRIVATE(iflag_thermals_down)
40!$OMP THREADPRIVATE(fact_thermals_down)
41!$OMP THREADPRIVATE(fact_epsilon, betalpha, afact, fact_shell)
42!$OMP THREADPRIVATE(detr_min, entr_min, detr_q_coef, detr_q_power)
43!$OMP THREADPRIVATE( mix0, thermals_flag_alim)
44!$OMP THREADPRIVATE(iflag_thermals_tenv)
45
46
47CONTAINS
48
49SUBROUTINE thermcell_ini(iflag_thermals,prt_level_in,tau_thermals_in,lunout_in, &
50      RG_in,RD_in,RCPD_in,RKAPPA_in,RLVTT_in,RETV_in)
51
52   USE lmdz_ioipsl_getin_p, ONLY: getin_p
53
54INTEGER, INTENT(IN) :: iflag_thermals,prt_level_in,lunout_in
55REAL, INTENT(IN) :: RG_in,RD_in,RCPD_in,RKAPPA_in,RLVTT_in,RETV_in,tau_thermals_in
56
57PRINT*,'thermcell_ini'
58      IF (iflag_thermals==15.OR.iflag_thermals==16) THEN
59         dvdq=0
60         dqimpl=-1
61      else
62         dvdq=1
63         dqimpl=1
64      endif
65   prt_level=prt_level_in
66   RG=RG_in
67   RD=RD_in
68   RCPD=RCPD_in
69   RKAPPA=RKAPPA_in
70   RLVTT=RLVTT_in
71   RLvCp = RLVTT/RCPD
72   RETV=RETV_in
73   tau_thermals=tau_thermals_in
74   lunout=lunout_in
75
76
77!=====================================================================
78! a la fois les vieilles param et thermcell_main :
79!=====================================================================
80
81   CALL getin_p('r_aspect_thermals',r_aspect_thermals)
82   CALL getin_p('tau_thermals',tau_thermals)
83   CALL getin_p('fact_thermals_ed_dz',fact_thermals_ed_dz)
84   CALL getin_p('iflag_thermals_ed',iflag_thermals_ed)
85   CALL getin_p('iflag_thermals_optflux',iflag_thermals_optflux)
86   CALL getin_p('iflag_thermals_closure',iflag_thermals_closure)
87   CALL getin_p('iflag_thermals_down',iflag_thermals_down)
88   CALL getin_p('fact_thermals_down',fact_thermals_down)
89   CALL getin_p('thermals_fact_epsilon',fact_epsilon)
90   CALL getin_p('thermals_betalpha',betalpha)
91   CALL getin_p('thermals_afact',afact)
92   CALL getin_p('thermals_fact_shell',fact_shell)
93   CALL getin_p('thermals_detr_min',detr_min)
94   CALL getin_p('thermals_entr_min',entr_min)
95   CALL getin_p('thermals_detr_q_coef',detr_q_coef)
96   CALL getin_p('thermals_detr_q_power',detr_q_power)
97   CALL getin_p('thermals_mix0',mix0)
98   CALL getin_p('thermals_flag_alim',thermals_flag_alim)
99   CALL getin_p('iflag_thermals_tenv',iflag_thermals_tenv)
100
101
102
103WRITE(lunout,*) 'thermcell_ini ,prt_level                =',  prt_level
104WRITE(lunout,*) 'thermcell_ini ,RG                       =',  RG
105WRITE(lunout,*) 'thermcell_ini ,RD                       =',  RD
106WRITE(lunout,*) 'thermcell_ini ,RCPD                     =',  RCPD
107WRITE(lunout,*) 'thermcell_ini ,RKAPPA                   =',  RKAPPA
108WRITE(lunout,*) 'thermcell_ini ,RLVTT                    =',  RLVTT
109WRITE(lunout,*) 'thermcell_ini ,RLvCp                    =',  RLvCp
110WRITE(lunout,*) 'thermcell_ini ,RETV                     =',  RETV
111WRITE(lunout,*) 'thermcell_ini ,tau_thermals             =',  tau_thermals
112WRITE(lunout,*) 'thermcell_ini ,lunout                   =',  lunout
113WRITE(lunout,*) 'thermcell_ini ,r_aspect_thermals        =',  r_aspect_thermals
114WRITE(lunout,*) 'thermcell_ini ,tau_thermals             =',  tau_thermals
115WRITE(lunout,*) 'thermcell_ini ,fact_thermals_ed_dz      =',  fact_thermals_ed_dz
116WRITE(lunout,*) 'thermcell_ini ,fact_thermals_ed_dz      =',  fact_thermals_ed_dz
117WRITE(lunout,*) 'thermcell_ini ,iflag_thermals_ed        =',  iflag_thermals_ed
118WRITE(lunout,*) 'thermcell_ini ,iflag_thermals_optflux   =',  iflag_thermals_optflux
119WRITE(lunout,*) 'thermcell_ini ,iflag_thermals_closure   =',  iflag_thermals_closure
120WRITE(lunout,*) 'thermcell_ini ,iflag_thermals_down      =',  iflag_thermals_down
121WRITE(lunout,*) 'thermcell_ini ,fact_thermals_down       =',  fact_thermals_down
122WRITE(lunout,*) 'thermcell_ini ,fact_epsilon             =',  fact_epsilon
123WRITE(lunout,*) 'thermcell_ini ,betalpha                 =',  betalpha
124WRITE(lunout,*) 'thermcell_ini ,afact                    =',  afact
125WRITE(lunout,*) 'thermcell_ini ,fact_shell               =',  fact_shell
126WRITE(lunout,*) 'thermcell_ini ,detr_min                 =',  detr_min
127WRITE(lunout,*) 'thermcell_ini ,entr_min                 =',  entr_min
128WRITE(lunout,*) 'thermcell_ini ,detr_q_coef              =',  detr_q_coef
129WRITE(lunout,*) 'thermcell_ini ,detr_q_power             =',  detr_q_power
130WRITE(lunout,*) 'thermcell_ini ,mix0                     =',  mix0
131WRITE(lunout,*) 'thermcell_ini ,thermals_flag_alim       =',  thermals_flag_alim
132WRITE(lunout,*) 'thermcell_ini ,iflag_thermals_tenv      =',  iflag_thermals_tenv
133
134
135
136END SUBROUTINE thermcell_ini
137END MODULE lmdz_thermcell_ini
Note: See TracBrowser for help on using the repository browser.