source: LMDZ6/trunk/libf/phylmd/lmdz_lscp_ini.f90 @ 5614

Last change on this file since 5614 was 5614, checked in by evignon, 8 weeks ago

Commission liée à un update majeur de la routine de condensation grande echelle suite au travail
de Lea, Audran et Etienne
Elle inclue une restructuration des routines pour clarifier le role "moniteur" de la routine lscp_main,
une mise à jour de la parametrisation de partitionnement de phase de Lea pour inclure les nuages de couche limite,
ainsi que des corrections des routines de precipitations "poprecip".
Convergence numerique verifiee en prod et debug pour les physiques NPv6.3 et 7.0.1c

File size: 30.7 KB
Line 
1MODULE lmdz_lscp_ini
2
3IMPLICIT NONE
4
5  ! PARAMETERS for lscp:
6  !--------------------
7 
8  REAL RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RV, RG, RPI, EPS_W
9  !$OMP THREADPRIVATE(RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RV, RG, RPI, EPS_W)
10 
11  INTEGER, SAVE, PROTECTED :: iflag_ratqs        ! control of ratqs option
12  !$OMP THREADPRIVATE(iflag_ratqs)
13 
14  REAL, SAVE, PROTECTED :: seuil_neb=0.001       ! cloud fraction threshold: a cloud can precipitate when exceeded
15  !$OMP THREADPRIVATE(seuil_neb)
16
17  REAL, SAVE, PROTECTED :: min_neb_th=1e-10      ! a cloud produced by bi-gaussian really exists when exceeded
18  !$OMP THREADPRIVATE(min_neb_th)
19
20  REAL, SAVE, PROTECTED :: min_frac_thermals=1.e-10   ! minimum thermals fraction for use of bigaussian distribution
21  !$OMP THREADPRIVATE(min_frac_thermals)
22
23  INTEGER, SAVE :: lunout, prt_level            ! Logical unit number and level for standard output
24  !$OMP THREADPRIVATE(lunout,prt_level)
25
26  INTEGER, SAVE, PROTECTED :: niter_lscp=5      ! number of iterations to calculate autoconversion to precipitation
27  !$OMP THREADPRIVATE(niter_lscp)
28
29  INTEGER, SAVE, PROTECTED :: iflag_evap_prec=1 ! precipitation evaporation flag. 0: nothing, 1: "old way",
30                                                ! 2: Max cloud fraction above to calculate the max of reevaporation
31                                                ! >=4: LTP'method i.e. evaporation in the clear-sky fraction of the mesh only
32                                                ! pay attention that iflag_evap_prec=4 may lead to unrealistic and overestimated
33                                                ! evaporation. Use 5 instead
34  !$OMP THREADPRIVATE(iflag_evap_prec)
35
36  REAL, SAVE, PROTECTED :: t_coup=234.0         ! temperature threshold which determines the phase
37                                                ! for which the saturation vapor pressure is calculated
38  !$OMP THREADPRIVATE(t_coup)
39  REAL, SAVE, PROTECTED :: DDT0=0.01            ! iteration parameter
40  !$OMP THREADPRIVATE(DDT0)
41
42  REAL, SAVE, PROTECTED :: ztfondue=278.15      ! parameter to calculate melting fraction of precipitation
43  !$OMP THREADPRIVATE(ztfondue)
44
45  REAL, SAVE, PROTECTED :: temp_nowater=235.15  ! temperature below which liquid water no longer exists
46  !$OMP THREADPRIVATE(temp_nowater)
47
48  REAL, SAVE, PROTECTED :: a_tr_sca(4)          ! Variables for tracers temporary: alpha parameter for scavenging, 4 possible scavenging processes
49  !$OMP THREADPRIVATE(a_tr_sca)
50 
51  REAL, SAVE, PROTECTED ::  min_frac_th_cld=1.e-10   ! minimum thermal fraction to compute a thermal cloud fraction
52  !$OMP THREADPRIVATE(min_frac_th_cld)
53
54  LOGICAL, SAVE, PROTECTED :: ok_radocond_snow=.false. ! take into account the mass of ice precip in the cloud ice content seen by radiation
55  !$OMP THREADPRIVATE(ok_radocond_snow)
56
57  REAL, SAVE, PROTECTED :: t_glace_min=258.0    ! lower-bound temperature parameter for cloud phase determination
58  !$OMP THREADPRIVATE(t_glace_min)
59
60  REAL, SAVE, PROTECTED :: t_glace_max=273.15   ! upper-bound temperature parameter for cloud phase determination
61  !$OMP THREADPRIVATE(t_glace_max)
62
63  REAL, SAVE, PROTECTED :: exposant_glace=1.0   ! parameter for cloud phase determination
64  !$OMP THREADPRIVATE(exposant_glace)
65
66  INTEGER, SAVE, PROTECTED :: iflag_vice=0      ! which expression for ice crystall fall velocity
67  !$OMP THREADPRIVATE(iflag_vice)
68
69  INTEGER, SAVE, PROTECTED :: iflag_t_glace=0   ! which expression for cloud phase partitioning
70  !$OMP THREADPRIVATE(iflag_t_glace)
71
72  INTEGER, SAVE, PROTECTED :: iflag_gammasat=0              ! which threshold for homogeneous nucleation below -40oC
73  !$OMP THREADPRIVATE(iflag_gammasat)
74
75  INTEGER, SAVE, PROTECTED :: iflag_rain_incloud_vol=0      ! use of volume cloud fraction for rain autoconversion
76  !$OMP THREADPRIVATE(iflag_rain_incloud_vol)
77
78  INTEGER, SAVE, PROTECTED :: iflag_bergeron=0              ! bergeron effect for liquid precipitation treatment 
79  !$OMP THREADPRIVATE(iflag_bergeron)
80
81  INTEGER, SAVE, PROTECTED :: iflag_fisrtilp_qsat=0         ! qsat adjustment (iterative) during autoconversion
82  !$OMP THREADPRIVATE(iflag_fisrtilp_qsat)
83
84  INTEGER, SAVE, PROTECTED :: iflag_pdf=0                   ! type of subgrid scale qtot pdf
85  !$OMP THREADPRIVATE(iflag_pdf)
86
87  INTEGER, SAVE, PROTECTED :: iflag_icefrac=0               ! which phase partitioning function to use
88  !$OMP THREADPRIVATE(iflag_icefrac)
89
90  INTEGER, SAVE, PROTECTED :: iflag_autoconversion=0        ! autoconversion option
91  !$OMP THREADPRIVATE(iflag_autoconversion)
92
93  LOGICAL, SAVE, PROTECTED :: ok_bug_phase_lscp=.true.      ! bug on phase partitioning after precipitation processes
94  !$OMP THREADPRIVATE(ok_bug_phase_lscp)
95
96  LOGICAL, SAVE, PROTECTED :: reevap_ice=.false.            ! no liquid precip for T< threshold
97  !$OMP THREADPRIVATE(reevap_ice)
98
99  REAL, SAVE, PROTECTED :: cld_lc_lsc=2.6e-4                ! liquid autoconversion coefficient, stratiform rain
100  !$OMP THREADPRIVATE(cld_lc_lsc)
101
102  REAL, SAVE, PROTECTED :: cld_lc_con=2.6e-4                ! liquid autoconversion coefficient, convective rain
103  !$OMP THREADPRIVATE(cld_lc_con)
104
105  REAL, SAVE, PROTECTED :: cld_tau_lsc=3600.                ! liquid autoconversion timescale, stratiform rain
106  !$OMP THREADPRIVATE(cld_tau_lsc)
107
108  REAL, SAVE, PROTECTED :: cld_tau_con=3600.                ! liquid autoconversion timescale, convective rain
109  !$OMP THREADPRIVATE(cld_tau_con)
110
111  REAL, SAVE, PROTECTED :: cld_expo_lsc=2.                  ! liquid autoconversion threshold exponent, stratiform rain
112  !$OMP THREADPRIVATE(cld_expo_lsc)
113
114  REAL, SAVE, PROTECTED :: cld_expo_con=2.                  ! liquid autoconversion threshold exponent, convective rain
115  !$OMP THREADPRIVATE(cld_expo_con)
116
117  REAL, SAVE, PROTECTED :: ffallv_lsc=1.                    ! tuning coefficient crystal fall velocity, stratiform
118  !$OMP THREADPRIVATE(ffallv_lsc)
119
120  REAL, SAVE, PROTECTED :: ffallv_con=1.                    ! tuning coefficient crystal fall velocity, convective
121  !$OMP THREADPRIVATE(ffallv_con)
122
123  REAL, SAVE, PROTECTED :: coef_eva=2e-5                    ! tuning coefficient liquid precip evaporation
124  !$OMP THREADPRIVATE(coef_eva)
125
126  REAL, SAVE, PROTECTED :: coef_sub                         ! tuning coefficient ice precip sublimation
127  !$OMP THREADPRIVATE(coef_sub)
128
129  REAL, SAVE, PROTECTED :: expo_eva=0.5                     ! tuning coefficient liquid precip evaporation
130  !$OMP THREADPRIVATE(expo_eva)
131
132  REAL, SAVE, PROTECTED :: expo_sub                         ! tuning coefficient ice precip sublimation
133  !$OMP THREADPRIVATE(expo_sub)
134
135  REAL, SAVE, PROTECTED :: cice_velo=1.645                  ! factor in the ice fall velocity formulation. It is half the value of
136                                                            ! Heymsfield and Donner 1990 to concur with previous LMDZ versions
137  !$OMP THREADPRIVATE(cice_velo)
138
139  REAL, SAVE, PROTECTED ::  dice_velo=0.16                  ! exponent in the ice fall velocity formulation
140  !$OMP THREADPRIVATE(dice_velo)
141
142  REAL, SAVE, PROTECTED :: dist_liq=300.                    ! typical deph of cloud-top liquid layer in mpcs
143  !$OMP THREADPRIVATE(dist_liq)
144
145  REAL, SAVE, PROTECTED  :: tresh_cl=0.0                  ! cloud fraction threshold for cloud top search
146  !$OMP THREADPRIVATE(tresh_cl)
147
148  !--Parameters for condensation and ice supersaturation
149
150  LOGICAL, SAVE, PROTECTED :: ok_ice_supersat=.FALSE.        ! activates the condensation scheme that allows for ice supersaturation
151  !$OMP THREADPRIVATE(ok_ice_supersat)
152
153  LOGICAL, SAVE, PROTECTED :: ok_unadjusted_clouds=.FALSE.   ! if True, relax the saturation adjustment assumption for ice clouds
154  !$OMP THREADPRIVATE(ok_unadjusted_clouds)
155
156  LOGICAL, SAVE, PROTECTED :: ok_weibull_warm_clouds=.FALSE. ! if True, the weibull condensation scheme replaces the lognormal condensation scheme at positive temperatures
157  !$OMP THREADPRIVATE(ok_weibull_warm_clouds)
158
159  INTEGER, SAVE, PROTECTED :: iflag_cloud_sublim_pdf=4       ! iflag for the distribution of water inside ice clouds
160  !$OMP THREADPRIVATE(iflag_cloud_sublim_pdf)
161
162  REAL, SAVE, PROTECTED :: depo_coef_cirrus=.7               ! [-] deposition coefficient for growth of ice crystals in cirrus clouds
163  !$OMP THREADPRIVATE(depo_coef_cirrus)
164
165  REAL, SAVE, PROTECTED :: capa_cond_cirrus=.5               ! [-] capacitance factor for growth/sublimation of ice crystals in cirrus clouds
166  !$OMP THREADPRIVATE(capa_cond_cirrus)
167
168  REAL, SAVE, PROTECTED :: std_subl_pdf_lscp=2.              ! [%] standard deviation of the gaussian distribution of water inside ice clouds
169  !$OMP THREADPRIVATE(std_subl_pdf_lscp)
170
171  REAL, SAVE, PROTECTED :: mu_subl_pdf_lscp=1./3.            ! [-] shape factor of the gamma distribution of water inside ice clouds
172  !$OMP THREADPRIVATE(mu_subl_pdf_lscp)
173 
174  REAL, SAVE, PROTECTED :: beta_pdf_lscp=1.E-3               ! [SI] tuning coefficient for the standard deviation of the PDF of water vapor in the clear sky region
175  !$OMP THREADPRIVATE(beta_pdf_lscp)
176 
177  REAL, SAVE, PROTECTED :: temp_thresh_pdf_lscp=189.         ! [K] factor for the PDF fit of water vapor in UTLS - below this temperature, water vapor is homogeneously distributed in the clear sky region
178  !$OMP THREADPRIVATE(temp_thresh_pdf_lscp)
179 
180  REAL, SAVE, PROTECTED :: k0_pdf_lscp=3.01                  ! [-] factor for the PDF fit of water vapor in UTLS
181  !$OMP THREADPRIVATE(k0_pdf_lscp)
182 
183  REAL, SAVE, PROTECTED :: kappa_pdf_lscp=0.0192             ! [] factor for the PDF fit of water vapor in UTLS
184  !$OMP THREADPRIVATE(kappa_pdf_lscp)
185 
186  REAL, SAVE, PROTECTED :: std100_pdf_lscp=4.08              ! [%] standard deviation at RHliq=100% of the PDF fit of water vapor in UTLS
187  !$OMP THREADPRIVATE(std100_pdf_lscp)
188 
189  REAL, SAVE, PROTECTED :: a_homofreez=2.349                 ! [-] factor for the Koop homogeneous freezing fit
190  !$OMP THREADPRIVATE(a_homofreez)
191 
192  REAL, SAVE, PROTECTED :: b_homofreez=259.                  ! [K] factor for the Koop homogeneous freezing fit
193  !$OMP THREADPRIVATE(b_homofreez)
194
195  REAL, SAVE, PROTECTED :: delta_hetfreez=1.                 ! [-] value between 0 and 1 to simulate for heterogeneous freezing.
196  !$OMP THREADPRIVATE(delta_hetfreez)
197 
198  REAL, SAVE, PROTECTED :: coef_mixing_lscp=1.E-3            ! [-] tuning coefficient for the mixing process
199  !$OMP THREADPRIVATE(coef_mixing_lscp)
200 
201  REAL, SAVE, PROTECTED :: coef_shear_lscp=0.72              ! [-] additional coefficient for the shearing process (subprocess of the mixing process)
202  !$OMP THREADPRIVATE(coef_shear_lscp)
203 
204  REAL, SAVE, PROTECTED :: chi_mixing_lscp=1.                ! [-] factor for the macro distribution of ISSRs wrt clouds in a gridbox
205  !$OMP THREADPRIVATE(chi_mixing_lscp)
206  !--End of the parameters for condensation and ice supersaturation
207
208  !--Parameters for poprecip and cloud phase
209  LOGICAL, SAVE, PROTECTED :: ok_poprecip=.FALSE.           ! use the processes-oriented formulation of precipitations
210  !$OMP THREADPRIVATE(ok_poprecip)
211
212  LOGICAL, SAVE, PROTECTED :: ok_corr_vap_evasub=.FALSE.    ! use the corrected version of clear-sky water vapor for the evap / subl processes
213  !$OMP THREADPRIVATE(ok_corr_vap_evasub)
214
215  LOGICAL, SAVE, PROTECTED :: ok_growth_precip_deposition=.FALSE. ! allows growth of snowfall through vapor deposition in supersat. regions
216  !$OMP THREADPRIVATE(ok_growth_precip_deposition)
217
218  REAL, SAVE, PROTECTED :: cld_lc_lsc_snow=2.e-5            ! snow autoconversion coefficient, stratiform. default from  Chaboureau and PInty 2006
219  !$OMP THREADPRIVATE(cld_lc_lsc_snow)
220
221  REAL, SAVE, PROTECTED :: cld_lc_con_snow=2.e-5            ! snow autoconversion coefficient, convective
222  !$OMP THREADPRIVATE(cld_lc_con_snow)
223
224  REAL, SAVE, PROTECTED :: rain_int_min=1.e-5               ! Minimum local rain intensity [mm/s] before the decrease in associated precipitation fraction
225  !$OMP THREADPRIVATE(rain_int_min)
226
227  REAL, SAVE, PROTECTED :: thresh_precip_frac=1.E-6         ! precipitation fraction threshold [-]
228  !$OMP THREADPRIVATE(thresh_precip_frac)
229
230  REAL, SAVE, PROTECTED :: capa_crystal=1.                  ! Crystal capacitance (shape factor) for lscp_icefrac_turb [-]
231  !$OMP THREADPRIVATE(capa_crystal)
232
233  REAL, SAVE, PROTECTED :: naero5=0.5                       ! Number concentration of aerosol larger than 0.5 microns [scm-3]
234  !$OMP THREADPRIVATE(naero5)
235
236  REAL, SAVE, PROTECTED :: gamma_snwretro = 0.              ! Proportion of snow taken into account in ice retroaction in lscp_icefrac_turb [-]
237  !$OMP THREADPRIVATE(gamma_snwretro)
238
239  REAL, SAVE, PROTECTED :: gamma_mixth = 1.                 ! Tuning coeff for mixing with thermals/env in lscp_icefrac_turb [-]
240  !$OMP THREADPRIVATE(gamma_mixth)
241
242  REAL, SAVE, PROTECTED :: gamma_taud = 1.                  ! Tuning coeff for Lagrangian decorrelation timescale in lscp_icefrac_turb [-]
243  !$OMP THREADPRIVATE(gamma_taud)
244
245  REAL, SAVE, PROTECTED :: gamma_col=1.                     ! Tuning coefficient for rain collection efficiency (poprecip) [-]
246  !$OMP THREADPRIVATE(gamma_col)
247
248  REAL, SAVE, PROTECTED :: gamma_agg=1.                     ! Tuning coefficient for snow aggregation efficiency (poprecip) [-]
249  !$OMP THREADPRIVATE(gamma_agg)
250
251  REAL, SAVE, PROTECTED :: gamma_rim=1.                     ! Tuning coefficient for riming efficiency (poprecip) [-]
252  !$OMP THREADPRIVATE(gamma_rim)
253
254  REAL, SAVE, PROTECTED :: gamma_melt=1.                    ! Tuning coefficient for snow melting efficiency (poprecip) [-]
255  !$OMP THREADPRIVATE(gamma_melt)
256 
257  REAL, SAVE, PROTECTED :: gamma_freez=1.                   ! Tuning coefficient for rain collision freezing efficiency (poprecip) [-]
258  !$OMP THREADPRIVATE(gamma_freez)
259
260  REAL, SAVE, PROTECTED :: rho_rain=1000.                   ! Rain density [kg/m3]
261  !$OMP THREADPRIVATE(rho_rain)
262
263  REAL, SAVE, PROTECTED :: rho_ice=920.                     ! Ice crystal density (assuming spherical geometry) [kg/m3]
264  !$OMP THREADPRIVATE(rho_ice)
265
266  REAL, SAVE, PROTECTED :: r_rain=500.E-6                   ! Rain droplets radius (poprecip) [m]
267  !$OMP THREADPRIVATE(r_rain)
268
269  REAL, SAVE, PROTECTED :: r_snow=1.E-3                     ! Ice crystals radius (poprecip) [m]
270  !$OMP THREADPRIVATE(r_snow)
271
272  REAL, SAVE, PROTECTED :: tau_auto_snow_min=100.           ! Snow autoconversion minimal timescale (when liquid) [s]
273  !$OMP THREADPRIVATE(tau_auto_snow_min)
274
275  REAL, SAVE, PROTECTED :: tau_auto_snow_max=1000.          ! Snow autoconversion minimal timescale (when only ice) [s]
276  !$OMP THREADPRIVATE(tau_auto_snow_max)
277
278  REAL, SAVE, PROTECTED :: expo_tau_auto_snow=0.1          ! Snow autoconversion timescale exponent for icefrac dependency
279  !$OMP THREADPRIVATE(expo_tau_auto_snow)
280
281  REAL, SAVE, PROTECTED :: eps=1.E-10                       ! Treshold 0 [-]
282  !$OMP THREADPRIVATE(eps)
283
284  REAL, SAVE, PROTECTED :: alpha_freez=4.                   ! Slope of exponential for immersion freezing timescale [-]
285  !$OMP THREADPRIVATE(alpha_freez)
286
287  REAL, SAVE, PROTECTED :: beta_freez=0.1                   ! Inv.time immersion freezing [s-1]
288  !$OMP THREADPRIVATE(beta_freez)
289
290  REAL, SAVE, PROTECTED :: rain_fallspeed=4.                ! Rain fall velocity [m/s]
291  !$OMP THREADPRIVATE(rain_fallspeed)
292
293  REAL, SAVE, PROTECTED :: rain_fallspeed_clr               ! Rain fall velocity in clear sky [m/s]
294  !$OMP THREADPRIVATE(rain_fallspeed_clr)
295
296  REAL, SAVE, PROTECTED :: rain_fallspeed_cld               ! Rain fall velocity in cloudy sky [m/s]
297  !$OMP THREADPRIVATE(rain_fallspeed_cld)
298
299  REAL, SAVE, PROTECTED :: snow_fallspeed=1.                ! Snow fall velocity [m/s]
300  !$OMP THREADPRIVATE(snow_fallspeed)
301
302  REAL, SAVE, PROTECTED :: snow_fallspeed_clr               ! Snow fall velocity in clear sky [m/s]
303  !$OMP THREADPRIVATE(snow_fallspeed_clr)
304
305  REAL, SAVE, PROTECTED :: snow_fallspeed_cld               ! Snow fall velocity in cloudy sky [m/s]
306  !$OMP THREADPRIVATE(snow_fallspeed_cld)
307  !--End of the parameters for poprecip
308
309  ! Parameters for cloudth routines
310  LOGICAL, SAVE, PROTECTED :: ok_lscp_mergecond=.false.     ! more consistent condensation stratiform and shallow convective clouds
311  !$OMP THREADPRIVATE(ok_lscp_mergecond)
312 
313  INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert=0          ! option for determining cloud fraction and content in convective boundary layers
314  !$OMP THREADPRIVATE(iflag_cloudth_vert)
315
316  INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert_noratqs=0  ! option to control the width of gaussian distrib in a specific case
317  !$OMP THREADPRIVATE(iflag_cloudth_vert_noratqs)
318
319  REAL, SAVE, PROTECTED :: cloudth_ratqsmin=-1.             ! minimum ratqs in cloudth
320  !$OMP THREADPRIVATE(cloudth_ratqsmin)
321
322  REAL, SAVE, PROTECTED :: sigma1s_factor=1.1               ! factor for standard deviation of gaussian distribution of environment
323  !$OMP THREADPRIVATE(sigma1s_factor)
324
325  REAL, SAVE, PROTECTED :: sigma2s_factor=0.09              ! factor for standard deviation of gaussian distribution of thermals
326  !$OMP THREADPRIVATE(sigma2s_factor)
327
328
329  REAL, SAVE, PROTECTED :: sigma1s_power=0.6                ! exponent for standard deviation of gaussian distribution of environment
330  !$OMP THREADPRIVATE(sigma1s_power)
331   
332  REAL, SAVE, PROTECTED :: sigma2s_power=0.5                ! exponent for standard deviation of gaussian distribution of thermals
333  !$OMP THREADPRIVATE(sigma2s_power)
334
335  REAL, SAVE, PROTECTED :: vert_alpha=0.5                   ! tuning coefficient for standard deviation of gaussian distribution of thermals
336  !$OMP THREADPRIVATE(vert_alpha)
337
338  REAL, SAVE, PROTECTED :: vert_alpha_th=0.5                ! tuning coefficient for standard deviation of gaussian distribution of thermals
339  !$OMP THREADPRIVATE(vert_alpha_th)
340  ! End of parameters for cloudth routines
341
342  ! Two parameters used for lmdz_lscp_old only
343  INTEGER, SAVE, PROTECTED :: iflag_oldbug_fisrtilp=0, fl_cor_ebil
344  !$OMP THREADPRIVATE(iflag_oldbug_fisrtilp,fl_cor_ebil)
345
346CONTAINS
347
348SUBROUTINE lscp_ini(dtime,lunout_in,prt_level_in,ok_ice_supersat_in, iflag_ratqs_in, fl_cor_ebil_in, &
349                    RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in, RVTMP2_in, &
350                    RTT_in, RD_in, RV_in, RG_in, RPI_in, EPS_W_in)
351
352
353   USE ioipsl_getin_p_mod, ONLY : getin_p
354
355   REAL, INTENT(IN)      :: dtime
356   INTEGER, INTENT(IN)   :: lunout_in,prt_level_in,iflag_ratqs_in,fl_cor_ebil_in
357   LOGICAL, INTENT(IN)   :: ok_ice_supersat_in
358
359   REAL, INTENT(IN)      :: RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in
360   REAL, INTENT(IN)      :: RVTMP2_in, RTT_in, RD_in, RV_in, RG_in, RPI_in, EPS_W_in
361   character (len=20) :: modname='lscp_ini_mod'
362   character (len=80) :: abort_message
363
364
365    lunout=lunout_in
366    prt_level=prt_level_in
367    fl_cor_ebil=fl_cor_ebil_in
368    iflag_ratqs=iflag_ratqs_in
369    ok_ice_supersat=ok_ice_supersat_in
370
371    RG=RG_in
372    RD=RD_in
373    RV=RV_in
374    RCPD=RCPD_in
375    RLVTT=RLVTT_in
376    RLSTT=RLSTT_in
377    RLMLT=RLMLT_in
378    RTT=RTT_in
379    RV=RV_in
380    RVTMP2=RVTMP2_in
381    RPI=RPI_in
382    EPS_W=EPS_W_in
383
384
385
386    CALL getin_p('niter_lscp',niter_lscp)
387    CALL getin_p('iflag_evap_prec',iflag_evap_prec)
388    CALL getin_p('seuil_neb',seuil_neb)
389    CALL getin_p('ok_radocond_snow',ok_radocond_snow)
390    CALL getin_p('t_glace_max',t_glace_max)
391    CALL getin_p('t_glace_min',t_glace_min)
392    CALL getin_p('exposant_glace',exposant_glace)
393    CALL getin_p('iflag_vice',iflag_vice)
394    CALL getin_p('iflag_t_glace',iflag_t_glace)
395    CALL getin_p('iflag_gammasat',iflag_gammasat)
396    CALL getin_p('iflag_rain_incloud_vol',iflag_rain_incloud_vol)
397    CALL getin_p('iflag_bergeron',iflag_bergeron)
398    CALL getin_p('iflag_fisrtilp_qsat',iflag_fisrtilp_qsat)
399    CALL getin_p('iflag_pdf',iflag_pdf)
400    CALL getin_p('iflag_icefrac',iflag_icefrac)
401    CALL getin_p('reevap_ice',reevap_ice)
402    CALL getin_p('cld_lc_lsc',cld_lc_lsc)
403    CALL getin_p('cld_lc_con',cld_lc_con)
404    CALL getin_p('cld_lc_lsc_snow',cld_lc_lsc_snow)
405    CALL getin_p('cld_lc_con_snow',cld_lc_con_snow)
406    CALL getin_p('cld_tau_lsc',cld_tau_lsc)
407    CALL getin_p('cld_tau_con',cld_tau_con)
408    CALL getin_p('cld_expo_lsc',cld_expo_lsc)
409    CALL getin_p('cld_expo_con',cld_expo_con)
410    CALL getin_p('ffallv_lsc',ffallv_lsc)
411    CALL getin_p('ffallv_lsc',ffallv_con)
412    ! for poprecip and cloud phase
413    CALL getin_p('coef_eva',coef_eva)
414    coef_sub=coef_eva
415    CALL getin_p('coef_eva_i',coef_sub)
416    CALL getin_p('coef_sub',coef_sub)
417    CALL getin_p('expo_eva',expo_eva)
418    expo_sub=expo_eva
419    CALL getin_p('expo_sub',expo_sub)
420    CALL getin_p('iflag_autoconversion',iflag_autoconversion)
421    CALL getin_p('dist_liq',dist_liq)
422    CALL getin_p('tresh_cl',tresh_cl)
423    CALL getin_p('capa_crystal',capa_crystal)
424    CALL getin_p('naero5',naero5)
425    CALL getin_p('gamma_snwretro',gamma_snwretro)
426    CALL getin_p('gamma_taud',gamma_taud)
427    CALL getin_p('gamma_mixth',gamma_mixth)
428    CALL getin_p('iflag_oldbug_fisrtilp',iflag_oldbug_fisrtilp)
429    CALL getin_p('temp_nowater',temp_nowater)
430    CALL getin_p('ok_bug_phase_lscp',ok_bug_phase_lscp)
431    CALL getin_p('ok_poprecip',ok_poprecip)
432    CALL getin_p('ok_corr_vap_evasub',ok_corr_vap_evasub)
433    CALL getin_p('ok_growth_precip_deposition',ok_growth_precip_deposition)
434    CALL getin_p('rain_int_min',rain_int_min)
435    CALL getin_p('gamma_agg',gamma_agg)
436    CALL getin_p('gamma_col',gamma_col)
437    CALL getin_p('gamma_rim',gamma_rim)
438    CALL getin_p('gamma_freez',gamma_freez)
439    CALL getin_p('gamma_melt',gamma_melt)
440    CALL getin_p('tau_auto_snow_max',tau_auto_snow_max)
441    CALL getin_p('tau_auto_snow_min',tau_auto_snow_min)
442    CALL getin_p('expo_tau_auto_snow', expo_tau_auto_snow)
443    CALL getin_p('alpha_freez',alpha_freez)
444    CALL getin_p('beta_freez',beta_freez)
445    CALL getin_p('r_snow',r_snow)
446    CALL getin_p('rain_fallspeed',rain_fallspeed)
447    rain_fallspeed_clr=rain_fallspeed
448    rain_fallspeed_cld=rain_fallspeed
449    CALL getin_p('rain_fallspeed_clr',rain_fallspeed_clr)
450    CALL getin_p('rain_fallspeed_cld',rain_fallspeed_cld)
451    CALL getin_p('snow_fallspeed',snow_fallspeed)
452    snow_fallspeed_clr=snow_fallspeed
453    snow_fallspeed_cld=snow_fallspeed
454    CALL getin_p('snow_fallspeed_clr',snow_fallspeed_clr)
455    CALL getin_p('snow_fallspeed_cld',snow_fallspeed_cld)
456    ! for condensation and ice supersaturation
457    CALL getin_p('ok_unadjusted_clouds',ok_unadjusted_clouds)
458    CALL getin_p('ok_weibull_warm_clouds',ok_weibull_warm_clouds)
459    CALL getin_p('iflag_cloud_sublim_pdf',iflag_cloud_sublim_pdf)
460    CALL getin_p('depo_coef_cirrus',depo_coef_cirrus)
461    CALL getin_p('capa_cond_cirrus',capa_cond_cirrus)
462    CALL getin_p('std_subl_pdf_lscp',std_subl_pdf_lscp)
463    CALL getin_p('mu_subl_pdf_lscp',mu_subl_pdf_lscp)
464    CALL getin_p('beta_pdf_lscp',beta_pdf_lscp)
465    CALL getin_p('temp_thresh_pdf_lscp',temp_thresh_pdf_lscp)
466    CALL getin_p('k0_pdf_lscp',k0_pdf_lscp)
467    CALL getin_p('kappa_pdf_lscp',kappa_pdf_lscp)
468    CALL getin_p('std100_pdf_lscp',std100_pdf_lscp)
469    CALL getin_p('a_homofreez',a_homofreez)
470    CALL getin_p('b_homofreez',b_homofreez)
471    CALL getin_p('delta_hetfreez',delta_hetfreez)
472    CALL getin_p('coef_mixing_lscp',coef_mixing_lscp)
473    CALL getin_p('coef_shear_lscp',coef_shear_lscp)
474    CALL getin_p('chi_mixing_lscp',chi_mixing_lscp)
475    ! for cloudth routines
476    CALL getin_p('ok_lscp_mergecond',ok_lscp_mergecond)
477    CALL getin_p('iflag_cloudth_vert',iflag_cloudth_vert)
478    CALL getin_p('cloudth_ratqsmin',cloudth_ratqsmin)
479    CALL getin_p('cloudth_sigma1s_factor',sigma1s_factor)
480    CALL getin_p('cloudth_sigma1s_power',sigma1s_power)
481    CALL getin_p('cloudth_sigma2s_factor',sigma2s_factor)
482    CALL getin_p('cloudth_sigma2s_power',sigma2s_power)
483    CALL getin_p('cloudth_vert_alpha',vert_alpha)
484    vert_alpha_th=vert_alpha
485    CALL getin_p('cloudth_vert_alpha_th',vert_alpha_th)
486    CALL getin_p('iflag_cloudth_vert_noratqs',iflag_cloudth_vert_noratqs)
487
488    WRITE(lunout,*) 'lscp_ini, niter_lscp:', niter_lscp
489    WRITE(lunout,*) 'lscp_ini, iflag_evap_prec:', iflag_evap_prec
490    WRITE(lunout,*) 'lscp_ini, seuil_neb:', seuil_neb
491    WRITE(lunout,*) 'lscp_ini, ok_radocond_snow:', ok_radocond_snow
492    WRITE(lunout,*) 'lscp_ini, t_glace_max:', t_glace_max
493    WRITE(lunout,*) 'lscp_ini, t_glace_min:', t_glace_min
494    WRITE(lunout,*) 'lscp_ini, exposant_glace:', exposant_glace
495    WRITE(lunout,*) 'lscp_ini, iflag_vice:', iflag_vice
496    WRITE(lunout,*) 'lscp_ini, iflag_t_glace:', iflag_t_glace
497    WRITE(lunout,*) 'lscp_ini, iflag_gammasat:', iflag_gammasat
498    WRITE(lunout,*) 'lscp_ini, iflag_rain_incloud_vol:', iflag_rain_incloud_vol
499    WRITE(lunout,*) 'lscp_ini, iflag_bergeron:', iflag_bergeron
500    WRITE(lunout,*) 'lscp_ini, iflag_fisrtilp_qsat:', iflag_fisrtilp_qsat
501    WRITE(lunout,*) 'lscp_ini, iflag_pdf', iflag_pdf
502    WRITE(lunout,*) 'lscp_ini, iflag_icefrac', iflag_icefrac
503    WRITE(lunout,*) 'lscp_ini, reevap_ice', reevap_ice
504    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc', cld_lc_lsc
505    WRITE(lunout,*) 'lscp_ini, cld_lc_con', cld_lc_con
506    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc_snow', cld_lc_lsc_snow
507    WRITE(lunout,*) 'lscp_ini, cld_lc_con_snow', cld_lc_con_snow
508    WRITE(lunout,*) 'lscp_ini, cld_tau_lsc', cld_tau_lsc
509    WRITE(lunout,*) 'lscp_ini, cld_tau_con', cld_tau_con
510    WRITE(lunout,*) 'lscp_ini, cld_expo_lsc', cld_expo_lsc
511    WRITE(lunout,*) 'lscp_ini, cld_expo_con', cld_expo_con
512    WRITE(lunout,*) 'lscp_ini, ffallv_lsc', ffallv_lsc
513    WRITE(lunout,*) 'lscp_ini, ffallv_con', ffallv_con
514    WRITE(lunout,*) 'lscp_ini, coef_eva', coef_eva
515    WRITE(lunout,*) 'lscp_ini, coef_sub', coef_sub
516    WRITE(lunout,*) 'lscp_ini, expo_eva', expo_eva
517    WRITE(lunout,*) 'lscp_ini, expo_sub', expo_sub
518    WRITE(lunout,*) 'lscp_ini, iflag_autoconversion', iflag_autoconversion
519    WRITE(lunout,*) 'lscp_ini, dist_liq', dist_liq
520    WRITE(lunout,*) 'lscp_ini, tresh_cl', tresh_cl
521    WRITE(lunout,*) 'lscp_ini, capa_crystal', capa_crystal
522    WRITE(lunout,*) 'lscp_ini, naero5', naero5
523    WRITE(lunout,*) 'lscp_ini, gamma_snwretro', gamma_snwretro
524    WRITE(lunout,*) 'lscp_ini, gamma_mixth', gamma_mixth
525    WRITE(lunout,*) 'lscp_ini, gamma_taud', gamma_taud
526    WRITE(lunout,*) 'lscp_ini, iflag_oldbug_fisrtilp', iflag_oldbug_fisrtilp
527    WRITE(lunout,*) 'lscp_ini, fl_cor_ebil', fl_cor_ebil
528    WRITE(lunout,*) 'lscp_ini, temp_nowater', temp_nowater
529    WRITE(lunout,*) 'lscp_ini, ok_bug_phase_lscp', ok_bug_phase_lscp
530    ! for poprecip
531    WRITE(lunout,*) 'lscp_ini, ok_poprecip', ok_poprecip
532    WRITE(lunout,*) 'lscp_ini, ok_corr_vap_evasub', ok_corr_vap_evasub
533    WRITE(lunout,*) 'lscp_ini, ok_growth_precip_deposition', ok_growth_precip_deposition
534    WRITE(lunout,*) 'lscp_ini, rain_int_min:', rain_int_min
535    WRITE(lunout,*) 'lscp_ini, gamma_agg:', gamma_agg
536    WRITE(lunout,*) 'lscp_ini, gamma_col:', gamma_col
537    WRITE(lunout,*) 'lscp_ini, gamma_rim:', gamma_rim
538    WRITE(lunout,*) 'lscp_ini, gamma_freez:', gamma_freez
539    WRITE(lunout,*) 'lscp_ini, gamma_melt:', gamma_melt
540    WRITE(lunout,*) 'lscp_ini, tau_auto_snow_max:',tau_auto_snow_max
541    WRITE(lunout,*) 'lscp_ini, tau_auto_snow_min:',tau_auto_snow_min
542    WRITE(lunout,*) 'lscp_ini, expo_tau_auto_snow:',expo_tau_auto_snow
543    WRITE(lunout,*) 'lscp_ini, r_snow:', r_snow
544    WRITE(lunout,*) 'lscp_ini, alpha_freez:', alpha_freez
545    WRITE(lunout,*) 'lscp_ini, beta_freez:', beta_freez
546    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_clr:', rain_fallspeed_clr
547    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_cld:', rain_fallspeed_cld
548    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_clr:', snow_fallspeed_clr
549    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_cld:', snow_fallspeed_cld
550    ! for condensation and ice supersaturation
551    WRITE(lunout,*) 'lscp_ini, ok_ice_supersat:', ok_ice_supersat
552    WRITE(lunout,*) 'lscp_ini, ok_unadjusted_clouds:', ok_unadjusted_clouds
553    WRITE(lunout,*) 'lscp_ini, ok_weibull_warm_clouds:', ok_weibull_warm_clouds
554    WRITE(lunout,*) 'lscp_ini, iflag_cloud_sublim_pdf:', iflag_cloud_sublim_pdf
555    WRITE(lunout,*) 'lscp_ini, depo_coef_cirrus:', depo_coef_cirrus
556    WRITE(lunout,*) 'lscp_ini, capa_cond_cirrus:', capa_cond_cirrus
557    WRITE(lunout,*) 'lscp_ini, std_subl_pdf_lscp:', std_subl_pdf_lscp
558    WRITE(lunout,*) 'lscp_ini, mu_subl_pdf_lscp:', mu_subl_pdf_lscp
559    WRITE(lunout,*) 'lscp_ini, beta_pdf_lscp:', beta_pdf_lscp
560    WRITE(lunout,*) 'lscp_ini, temp_thresh_pdf_lscp:', temp_thresh_pdf_lscp
561    WRITE(lunout,*) 'lscp_ini, k0_pdf_lscp:', k0_pdf_lscp
562    WRITE(lunout,*) 'lscp_ini, kappa_pdf_lscp:', kappa_pdf_lscp
563    WRITE(lunout,*) 'lscp_ini, std100_pdf_lscp:', std100_pdf_lscp
564    WRITE(lunout,*) 'lscp_ini, a_homofreez:', a_homofreez
565    WRITE(lunout,*) 'lscp_ini, b_homofreez:', b_homofreez
566    WRITE(lunout,*) 'lscp_ini, delta_hetfreez', delta_hetfreez
567    WRITE(lunout,*) 'lscp_ini, coef_mixing_lscp:', coef_mixing_lscp
568    WRITE(lunout,*) 'lscp_ini, coef_shear_lscp:', coef_shear_lscp
569    WRITE(lunout,*) 'lscp_ini, chi_mixing_lscp:', chi_mixing_lscp
570    ! for cloudth routines
571    WRITE(lunout,*) 'lscp_ini, ok_lscp_mergecond:', ok_lscp_mergecond
572    WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert:', iflag_cloudth_vert
573    WRITE(lunout,*) 'lscp_ini, cloudth_ratqsmin:', cloudth_ratqsmin
574    WRITE(lunout,*) 'lscp_ini, cloudth_sigma1s_factor:', sigma1s_factor
575    WRITE(lunout,*) 'lscp_ini, cloudth_sigma1s_power:', sigma1s_power
576    WRITE(lunout,*) 'lscp_ini, cloudth_sigma2s_factor:', sigma2s_factor
577    WRITE(lunout,*) 'lscp_ini, cloudth_sigma2s_power:', sigma2s_power
578    WRITE(lunout,*) 'lscp_ini, cloudth_vert_alpha:', vert_alpha
579    WRITE(lunout,*) 'lscp_ini, cloudth_vert_alpha_th:', vert_alpha_th
580    WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert_noratqs:', iflag_cloudth_vert_noratqs
581
582
583    ! check consistency for cloud phase partitioning options
584
585    IF ((iflag_icefrac .GE. 2) .AND. (.NOT. ok_lscp_mergecond)) THEN
586      abort_message = 'in lscp, iflag_icefrac .GE. 2 works only if ok_lscp_mergecond=.TRUE.'
587      CALL abort_physic (modname,abort_message,1)
588    ENDIF
589
590    ! check for precipitation sub-time steps
591    IF (ABS(dtime/REAL(niter_lscp)-360.0).GT.0.001) THEN
592        WRITE(lunout,*) 'lscp: it is not expected, see Z.X.Li', dtime
593        WRITE(lunout,*) 'I would prefer a 6 min sub-timestep'
594    ENDIF
595
596    ! check consistency between numerical resolution of autoconversion
597    ! and other options
598   
599    IF ((iflag_autoconversion .EQ. 2) .AND. .NOT. ok_poprecip) THEN
600        IF ((iflag_vice .NE. 0) .OR. (niter_lscp .GT. 1)) THEN
601           abort_message = 'in lscp, iflag_autoconversion=2 requires iflag_vice=0 and niter_lscp=1'
602           CALL abort_physic (modname,abort_message,1)
603        ENDIF
604    ENDIF
605
606
607    IF ( ok_weibull_warm_clouds .AND. .NOT. ok_ice_supersat ) THEN
608      abort_message = 'in lscp, ok_weibull_warm_clouds=y needs ok_ice_supersat=y'
609      CALL abort_physic (modname,abort_message,1)
610    ENDIF
611
612    IF ( ok_unadjusted_clouds .AND. .NOT. ok_ice_supersat ) THEN
613      abort_message = 'in lscp, ok_unadjusted_clouds=y needs ok_ice_supersat=y'
614      CALL abort_physic (modname,abort_message,1)
615    ENDIF
616
617    IF ( (iflag_icefrac .GE. 1) .AND. (.NOT. ok_poprecip .AND. (iflag_evap_prec .LT. 4)) ) THEN
618      abort_message = 'in lscp, icefracturb works with poprecip or with precip evap option >=4'
619      CALL abort_physic (modname,abort_message,1)
620    ENDIF
621
622
623
624    !AA Temporary initialisation
625    a_tr_sca(1) = -0.5
626    a_tr_sca(2) = -0.5
627    a_tr_sca(3) = -0.5
628    a_tr_sca(4) = -0.5
629   
630
631RETURN
632
633END SUBROUTINE lscp_ini
634
635END MODULE lmdz_lscp_ini
Note: See TracBrowser for help on using the repository browser.