source: LMDZ6/trunk/libf/phylmd/lmdz_thermcell_ini.f90 @ 5512

Last change on this file since 5512 was 5512, checked in by yann meurdesoif, 2 days ago

Implement GPU automatic port for :

  • Thermics
  • acama_gwd_rando
  • flott_gwd_rando

YM

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