source: LMDZ6/trunk/libf/phylmd/lmdz_thermcell_ini.F90 @ 4678

Last change on this file since 4678 was 4664, checked in by fhourdin, 9 months ago

standardisatio des noms pour lscp et fisrtilp

fisrtilp passe dans le module lmdz_lscp_old.F90
Prepartation de la replaysation de fisrtilp (deja fait pour lscp)

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