source: LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp_ini.f90 @ 5760

Last change on this file since 5760 was 5717, checked in by aborella, 5 weeks ago

Merge with trunk r5653

File size: 38.4 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 :: ok_bug_ice_fallspeed=.true.   ! flag to activate the high clipping of iwc when calculating ice  fallspeed velocity
97  !$OMP THREADPRIVATE(ok_bug_ice_fallspeed)
98
99  LOGICAL, SAVE, PROTECTED :: reevap_ice=.false.            ! no liquid precip for T< threshold
100  !$OMP THREADPRIVATE(reevap_ice)
101
102  REAL, SAVE, PROTECTED :: cld_lc_lsc=2.6e-4                ! liquid autoconversion coefficient, stratiform rain
103  !$OMP THREADPRIVATE(cld_lc_lsc)
104
105  REAL, SAVE, PROTECTED :: cld_lc_con=2.6e-4                ! liquid autoconversion coefficient, convective rain
106  !$OMP THREADPRIVATE(cld_lc_con)
107
108  REAL, SAVE, PROTECTED :: cld_tau_lsc=3600.                ! liquid autoconversion timescale, stratiform rain
109  !$OMP THREADPRIVATE(cld_tau_lsc)
110
111  REAL, SAVE, PROTECTED :: cld_tau_con=3600.                ! liquid autoconversion timescale, convective rain
112  !$OMP THREADPRIVATE(cld_tau_con)
113
114  REAL, SAVE, PROTECTED :: cld_expo_lsc=2.                  ! liquid autoconversion threshold exponent, stratiform rain
115  !$OMP THREADPRIVATE(cld_expo_lsc)
116
117  REAL, SAVE, PROTECTED :: cld_expo_con=2.                  ! liquid autoconversion threshold exponent, convective rain
118  !$OMP THREADPRIVATE(cld_expo_con)
119
120  REAL, SAVE, PROTECTED :: ffallv_lsc=1.                    ! tuning coefficient crystal fall velocity, stratiform
121  !$OMP THREADPRIVATE(ffallv_lsc)
122
123  REAL, SAVE, PROTECTED :: ffallv_con=1.                    ! tuning coefficient crystal fall velocity, convective
124  !$OMP THREADPRIVATE(ffallv_con)
125
126  REAL, SAVE, PROTECTED :: coef_eva=2e-5                    ! tuning coefficient liquid precip evaporation
127  !$OMP THREADPRIVATE(coef_eva)
128
129  REAL, SAVE, PROTECTED :: coef_sub                         ! tuning coefficient ice precip sublimation
130  !$OMP THREADPRIVATE(coef_sub)
131
132  REAL, SAVE, PROTECTED :: expo_eva=0.5                     ! tuning coefficient liquid precip evaporation
133  !$OMP THREADPRIVATE(expo_eva)
134
135  REAL, SAVE, PROTECTED :: expo_sub                         ! tuning coefficient ice precip sublimation
136  !$OMP THREADPRIVATE(expo_sub)
137
138  REAL, SAVE, PROTECTED :: cice_velo=1.645                  ! factor in the ice fall velocity formulation. It is half the value of
139                                                            ! Heymsfield and Donner 1990 to concur with previous LMDZ versions
140  !$OMP THREADPRIVATE(cice_velo)
141
142  REAL, SAVE, PROTECTED ::  dice_velo=0.16                  ! exponent in the ice fall velocity formulation
143  !$OMP THREADPRIVATE(dice_velo)
144
145  REAL, SAVE, PROTECTED :: dist_liq=300.                    ! typical deph of cloud-top liquid layer in mpcs
146  !$OMP THREADPRIVATE(dist_liq)
147
148  REAL, SAVE, PROTECTED  :: tresh_cl=0.0                  ! cloud fraction threshold for cloud top search
149  !$OMP THREADPRIVATE(tresh_cl)
150
151  !--Parameters for condensation and ice supersaturation
152
153  LOGICAL, SAVE, PROTECTED :: ok_ice_supersat=.FALSE.        ! activates the condensation scheme that allows for ice supersaturation
154  !$OMP THREADPRIVATE(ok_ice_supersat)
155
156  LOGICAL, SAVE, PROTECTED :: ok_no_issr_strato=.FALSE.      ! deactivates the ice supersaturation scheme in the stratosphere
157  !$OMP THREADPRIVATE(ok_no_issr_strato)
158
159  LOGICAL, SAVE, PROTECTED :: ok_unadjusted_clouds=.FALSE.   ! if True, relax the saturation adjustment assumption for ice clouds
160  !$OMP THREADPRIVATE(ok_unadjusted_clouds)
161
162  LOGICAL, SAVE, PROTECTED :: ok_weibull_warm_clouds=.FALSE. ! if True, the weibull condensation scheme replaces the lognormal condensation scheme at positive temperatures
163  !$OMP THREADPRIVATE(ok_weibull_warm_clouds)
164
165  LOGICAL, SAVE, PROTECTED :: ok_nodeep_lscp=.FALSE.         ! if True, the deep convection clouds are removed from the lscp calculations
166  !$OMP THREADPRIVATE(ok_nodeep_lscp)
167
168  LOGICAL, SAVE, PROTECTED :: ok_nodeep_lscp_rad=.FALSE.     ! if True, the deep convection clouds are not accounted two times in radiative transfer
169  !$OMP THREADPRIVATE(ok_nodeep_lscp_rad)
170
171  REAL, SAVE, PROTECTED :: ffallv_issr                       ! tuning coefficient crystal fall velocity, cirrus clouds (with ISSR)
172  !$OMP THREADPRIVATE(ffallv_issr)
173
174  REAL, SAVE, PROTECTED :: cooling_rate_ice_thresh=2.e-5     ! [K/s] minimum virtual cooling rate before ice is sublimated
175  !$OMP THREADPRIVATE(cooling_rate_ice_thresh)
176
177  REAL, SAVE, PROTECTED :: depo_coef_cirrus=.7               ! [-] deposition coefficient for growth of ice crystals in cirrus clouds
178  !$OMP THREADPRIVATE(depo_coef_cirrus)
179
180  REAL, SAVE, PROTECTED :: capa_cond_cirrus=.5               ! [-] capacitance factor for growth/sublimation of ice crystals in cirrus clouds
181  !$OMP THREADPRIVATE(capa_cond_cirrus)
182
183  REAL, SAVE, PROTECTED :: N_ice_volume=3.E4                 ! [#/m3] ice crystal concentration in cirrus clouds (default value from  Kramer et al, 2020)
184  !$OMP THREADPRIVATE(N_ice_volume)
185
186  REAL, SAVE, PROTECTED :: nu_iwc_pdf_lscp=4./3.             ! [-] shape factor for the ice distribution inside cirrus clouds
187  !$OMP THREADPRIVATE(nu_iwc_pdf_lscp)
188
189  REAL, SAVE, PROTECTED :: corr_incld_depsub                 ! [-] correction factor for in-cloud IWC rather than local IWC in dep / sub process BEWARE NO GETIN (calculated automatically)
190  !$OMP THREADPRIVATE(corr_incld_depsub)
191 
192  REAL, SAVE, PROTECTED :: beta_pdf_lscp=8.46E-4             ! [SI] tuning coefficient for the standard deviation of the PDF of water vapor in the clear sky region
193  !$OMP THREADPRIVATE(beta_pdf_lscp)
194 
195  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
196  !$OMP THREADPRIVATE(temp_thresh_pdf_lscp)
197 
198  REAL, SAVE, PROTECTED :: k0_pdf_lscp=3.01                  ! [-] factor for the PDF fit of water vapor in UTLS
199  !$OMP THREADPRIVATE(k0_pdf_lscp)
200 
201  REAL, SAVE, PROTECTED :: kappa_pdf_lscp=0.0192             ! [K-1] factor for the PDF fit of water vapor in UTLS
202  !$OMP THREADPRIVATE(kappa_pdf_lscp)
203 
204  REAL, SAVE, PROTECTED :: std100_pdf_lscp=4.08              ! [%] standard deviation at RHliq=100% of the PDF fit of water vapor in UTLS
205  !$OMP THREADPRIVATE(std100_pdf_lscp)
206 
207  REAL, SAVE, PROTECTED :: a_homofreez=2.349                 ! [-] factor for the Koop homogeneous freezing fit
208  !$OMP THREADPRIVATE(a_homofreez)
209 
210  REAL, SAVE, PROTECTED :: b_homofreez=259.                  ! [K] factor for the Koop homogeneous freezing fit
211  !$OMP THREADPRIVATE(b_homofreez)
212
213  REAL, SAVE, PROTECTED :: delta_hetfreez=0.85               ! [-] value between 0 and 1 to simulate for heterogeneous freezing.
214  !$OMP THREADPRIVATE(delta_hetfreez)
215
216  REAL, SAVE, PROTECTED :: aspect_ratio_cirrus=1./9.         ! [-] aspect ratio of natural cirrus clouds
217  !$OMP THREADPRIVATE(aspect_ratio_cirrus)
218 
219  REAL, SAVE, PROTECTED :: coef_mixing_lscp=1.E-3            ! [-] tuning coefficient for the mixing process
220  !$OMP THREADPRIVATE(coef_mixing_lscp)
221 
222  REAL, SAVE, PROTECTED :: coef_shear_lscp=0.72              ! [-] additional coefficient for the shearing process (subprocess of the mixing process)
223  !$OMP THREADPRIVATE(coef_shear_lscp)
224 
225  REAL, SAVE, PROTECTED :: chi_mixing=1.5                    ! [-] factor for increasing the chance that moist air is surrounding  cirrus clouds
226  !$OMP THREADPRIVATE(chi_mixing)
227  !--End of the parameters for condensation and ice supersaturation
228
229  !--Parameters for aviation
230
231  LOGICAL, SAVE, PROTECTED :: ok_plane_contrail              ! activates the contrails parameterisation
232  !$OMP THREADPRIVATE(ok_plane_contrail)
233
234  LOGICAL, SAVE, PROTECTED :: ok_precip_contrails=.TRUE.     ! if True, contrails can be autoconverted to snow
235  !$OMP THREADPRIVATE(ok_precip_contrails)
236
237  REAL, SAVE, PROTECTED :: aspect_ratio_lincontrails=.1      ! [-] aspect ratio of linear contrails
238  !$OMP THREADPRIVATE(aspect_ratio_lincontrails)
239
240  REAL, SAVE, PROTECTED :: coef_mixing_lincontrails          ! [-] tuning coefficient for the linear contrails mixing process
241  !$OMP THREADPRIVATE(coef_mixing_lincontrails)
242 
243  REAL, SAVE, PROTECTED :: coef_shear_lincontrails           ! [-] additional coefficient for the linear contrails shearing process (subprocess of the contrails mixing process)
244  !$OMP THREADPRIVATE(coef_shear_lincontrails)
245 
246  REAL, SAVE, PROTECTED :: chi_mixing_lincontrails=3.        ! [-] factor for increasing the chance that moist air is surrounding linear contrails
247  !$OMP THREADPRIVATE(chi_mixing_lincontrails)
248
249  REAL, SAVE, PROTECTED :: EI_H2O_aviation=1.25              ! [kgH2O/kg] emission index of water vapor for a given fuel type
250  !$OMP THREADPRIVATE(EI_H2O_aviation)
251
252  REAL, SAVE, PROTECTED :: qheat_fuel_aviation=43.2E6        ! [J/kg] specific combustion heat for a given fuel type
253  !$OMP THREADPRIVATE(qheat_fuel_aviation)
254
255  REAL, SAVE, PROTECTED :: prop_efficiency_aviation=.3       ! [-] average propulsion efficiency of aircraft
256  !$OMP THREADPRIVATE(prop_efficiency_aviation)
257
258  REAL, SAVE, PROTECTED :: linear_contrails_lifetime=10800.  ! [s] timescale of the lifetime of linear contrails
259  !$OMP THREADPRIVATE(linear_contrails_lifetime)
260
261  REAL, SAVE, PROTECTED :: initial_width_contrails=200.      ! [m] initial width of the linear contrails formed
262  !$OMP THREADPRIVATE(initial_width_contrails)
263
264  REAL, SAVE, PROTECTED :: initial_height_contrails=200.     ! [m] initial height of the linear contrails formed
265  !$OMP THREADPRIVATE(initial_height_contrails)
266
267  REAL, SAVE, PROTECTED :: fallice_linear_contrails=1.       ! [m/s] Ice fallspeed velocity in linear contrails
268  !$OMP THREADPRIVATE(fallice_linear_contrails)
269
270  REAL, SAVE, PROTECTED :: fallice_cirrus_contrails=1.       ! [m/s] Ice fallspeed velocity in cirrus contrails
271  !$OMP THREADPRIVATE(fallice_cirrus_contrails)
272
273  REAL, SAVE, PROTECTED :: aviation_coef=1.                  ! [-] scaling factor for aviation emissions and flown distance
274  !$OMP THREADPRIVATE(aviation_coef)
275  !--End of the parameters for aviation
276
277  !--Parameters for poprecip and cloud phase
278  LOGICAL, SAVE, PROTECTED :: ok_poprecip=.FALSE.           ! use the processes-oriented formulation of precipitations
279  !$OMP THREADPRIVATE(ok_poprecip)
280
281  LOGICAL, SAVE, PROTECTED :: ok_corr_vap_evasub=.FALSE.    ! use the corrected version of clear-sky water vapor for the evap / subl processes
282  !$OMP THREADPRIVATE(ok_corr_vap_evasub)
283
284  LOGICAL, SAVE, PROTECTED :: ok_growth_precip_deposition=.FALSE. ! allows growth of snowfall through vapor deposition in supersat. regions
285  !$OMP THREADPRIVATE(ok_growth_precip_deposition)
286
287  REAL, SAVE, PROTECTED :: cld_lc_lsc_snow=2.e-5            ! snow autoconversion coefficient, stratiform. default from  Chaboureau and PInty 2006
288  !$OMP THREADPRIVATE(cld_lc_lsc_snow)
289
290  REAL, SAVE, PROTECTED :: cld_lc_con_snow=2.e-5            ! snow autoconversion coefficient, convective
291  !$OMP THREADPRIVATE(cld_lc_con_snow)
292
293  REAL, SAVE, PROTECTED :: rain_int_min=1.e-5               ! Minimum local rain intensity [mm/s] before the decrease in associated precipitation fraction
294  !$OMP THREADPRIVATE(rain_int_min)
295
296  REAL, SAVE, PROTECTED :: thresh_precip_frac=1.E-6         ! precipitation fraction threshold [-]
297  !$OMP THREADPRIVATE(thresh_precip_frac)
298
299  REAL, SAVE, PROTECTED :: capa_crystal=1.                  ! Crystal capacitance (shape factor) for lscp_icefrac_turb [-]
300  !$OMP THREADPRIVATE(capa_crystal)
301
302  REAL, SAVE, PROTECTED :: naero5=0.5                       ! Number concentration of aerosol larger than 0.5 microns [scm-3]
303  !$OMP THREADPRIVATE(naero5)
304
305  REAL, SAVE, PROTECTED :: gamma_snwretro = 0.              ! Proportion of snow taken into account in ice retroaction in lscp_icefrac_turb [-]
306  !$OMP THREADPRIVATE(gamma_snwretro)
307
308  REAL, SAVE, PROTECTED :: gamma_mixth = 1.                 ! Tuning coeff for mixing with thermals/env in lscp_icefrac_turb [-]
309  !$OMP THREADPRIVATE(gamma_mixth)
310
311  REAL, SAVE, PROTECTED :: gamma_taud = 1.                  ! Tuning coeff for Lagrangian decorrelation timescale in lscp_icefrac_turb [-]
312  !$OMP THREADPRIVATE(gamma_taud)
313
314  REAL, SAVE, PROTECTED :: gamma_col=1.                     ! Tuning coefficient for rain collection efficiency (poprecip) [-]
315  !$OMP THREADPRIVATE(gamma_col)
316
317  REAL, SAVE, PROTECTED :: gamma_agg=1.                     ! Tuning coefficient for snow aggregation efficiency (poprecip) [-]
318  !$OMP THREADPRIVATE(gamma_agg)
319
320  REAL, SAVE, PROTECTED :: gamma_rim=1.                     ! Tuning coefficient for riming efficiency (poprecip) [-]
321  !$OMP THREADPRIVATE(gamma_rim)
322
323  REAL, SAVE, PROTECTED :: gamma_melt=1.                    ! Tuning coefficient for snow melting efficiency (poprecip) [-]
324  !$OMP THREADPRIVATE(gamma_melt)
325 
326  REAL, SAVE, PROTECTED :: gamma_freez=1.                   ! Tuning coefficient for rain collision freezing efficiency (poprecip) [-]
327  !$OMP THREADPRIVATE(gamma_freez)
328
329  REAL, SAVE, PROTECTED :: rho_rain=1000.                   ! Rain density [kg/m3]
330  !$OMP THREADPRIVATE(rho_rain)
331
332  REAL, SAVE, PROTECTED :: rho_ice=920.                     ! Ice crystal density (assuming spherical geometry) [kg/m3]
333  !$OMP THREADPRIVATE(rho_ice)
334
335  REAL, SAVE, PROTECTED :: r_rain=500.E-6                   ! Rain droplets radius (poprecip) [m]
336  !$OMP THREADPRIVATE(r_rain)
337
338  REAL, SAVE, PROTECTED :: r_snow=1.E-3                     ! Ice crystals radius (poprecip) [m]
339  !$OMP THREADPRIVATE(r_snow)
340
341  REAL, SAVE, PROTECTED :: tau_auto_snow_min=100.           ! Snow autoconversion minimal timescale (when liquid) [s]
342  !$OMP THREADPRIVATE(tau_auto_snow_min)
343
344  REAL, SAVE, PROTECTED :: tau_auto_snow_max=1000.          ! Snow autoconversion minimal timescale (when only ice) [s]
345  !$OMP THREADPRIVATE(tau_auto_snow_max)
346
347  REAL, SAVE, PROTECTED :: expo_tau_auto_snow=0.1          ! Snow autoconversion timescale exponent for icefrac dependency
348  !$OMP THREADPRIVATE(expo_tau_auto_snow)
349
350  REAL, SAVE, PROTECTED :: eps=1.E-10                       ! Treshold 0 [-]
351  !$OMP THREADPRIVATE(eps)
352
353  REAL, SAVE, PROTECTED :: alpha_freez=4.                   ! Slope of exponential for immersion freezing timescale [-]
354  !$OMP THREADPRIVATE(alpha_freez)
355
356  REAL, SAVE, PROTECTED :: beta_freez=0.1                   ! Inv.time immersion freezing [s-1]
357  !$OMP THREADPRIVATE(beta_freez)
358
359  REAL, SAVE, PROTECTED :: rain_fallspeed=4.                ! Rain fall velocity [m/s]
360  !$OMP THREADPRIVATE(rain_fallspeed)
361
362  REAL, SAVE, PROTECTED :: rain_fallspeed_clr               ! Rain fall velocity in clear sky [m/s]
363  !$OMP THREADPRIVATE(rain_fallspeed_clr)
364
365  REAL, SAVE, PROTECTED :: rain_fallspeed_cld               ! Rain fall velocity in cloudy sky [m/s]
366  !$OMP THREADPRIVATE(rain_fallspeed_cld)
367
368  REAL, SAVE, PROTECTED :: snow_fallspeed=1.                ! Snow fall velocity [m/s]
369  !$OMP THREADPRIVATE(snow_fallspeed)
370
371  REAL, SAVE, PROTECTED :: snow_fallspeed_clr               ! Snow fall velocity in clear sky [m/s]
372  !$OMP THREADPRIVATE(snow_fallspeed_clr)
373
374  REAL, SAVE, PROTECTED :: snow_fallspeed_cld               ! Snow fall velocity in cloudy sky [m/s]
375  !$OMP THREADPRIVATE(snow_fallspeed_cld)
376
377  LOGICAL, SAVE, PROTECTED :: ok_ice_sedim=.FALSE.          ! Flag to activate the sedimentation of ice crystals
378  !$OMP THREADPRIVATE(ok_ice_sedim)
379
380  REAL, SAVE, PROTECTED :: fallice_sedim=1.                 ! Tuning factor for ice fallspeed velocity for sedimentation [-]
381  !$OMP THREADPRIVATE(fallice_sedim)
382 
383  REAL, SAVE, PROTECTED :: chi_sedim=1E5                    ! [-] factor for increasing the chance that sedimented ice falls into moist air
384  !$OMP THREADPRIVATE(chi_sedim)
385  !--End of the parameters for poprecip
386
387  ! Parameters for cloudth routines
388  LOGICAL, SAVE, PROTECTED :: ok_lscp_mergecond=.false.     ! more consistent condensation stratiform and shallow convective clouds
389  !$OMP THREADPRIVATE(ok_lscp_mergecond)
390 
391  INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert=0          ! option for determining cloud fraction and content in convective boundary layers
392  !$OMP THREADPRIVATE(iflag_cloudth_vert)
393
394  INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert_noratqs=0  ! option to control the width of gaussian distrib in a specific case
395  !$OMP THREADPRIVATE(iflag_cloudth_vert_noratqs)
396
397  REAL, SAVE, PROTECTED :: cloudth_ratqsmin=-1.             ! minimum ratqs in cloudth
398  !$OMP THREADPRIVATE(cloudth_ratqsmin)
399
400  REAL, SAVE, PROTECTED :: sigma1s_factor=1.1               ! factor for standard deviation of gaussian distribution of environment
401  !$OMP THREADPRIVATE(sigma1s_factor)
402
403  REAL, SAVE, PROTECTED :: sigma2s_factor=0.09              ! factor for standard deviation of gaussian distribution of thermals
404  !$OMP THREADPRIVATE(sigma2s_factor)
405
406
407  REAL, SAVE, PROTECTED :: sigma1s_power=0.6                ! exponent for standard deviation of gaussian distribution of environment
408  !$OMP THREADPRIVATE(sigma1s_power)
409   
410  REAL, SAVE, PROTECTED :: sigma2s_power=0.5                ! exponent for standard deviation of gaussian distribution of thermals
411  !$OMP THREADPRIVATE(sigma2s_power)
412
413  REAL, SAVE, PROTECTED :: vert_alpha=0.5                   ! tuning coefficient for standard deviation of gaussian distribution of thermals
414  !$OMP THREADPRIVATE(vert_alpha)
415
416  REAL, SAVE, PROTECTED :: vert_alpha_th=0.5                ! tuning coefficient for standard deviation of gaussian distribution of thermals
417  !$OMP THREADPRIVATE(vert_alpha_th)
418  ! End of parameters for cloudth routines
419
420  ! Two parameters used for lmdz_lscp_old only
421  INTEGER, SAVE, PROTECTED :: iflag_oldbug_fisrtilp=0, fl_cor_ebil
422  !$OMP THREADPRIVATE(iflag_oldbug_fisrtilp,fl_cor_ebil)
423
424CONTAINS
425
426SUBROUTINE lscp_ini(dtime, lunout_in, prt_level_in, ok_ice_supersat_in, &
427                    ok_no_issr_strato_in, ok_plane_contrail_in, &
428                    iflag_ratqs_in, fl_cor_ebil_in, &
429                    RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in, RVTMP2_in, &
430                    RTT_in, RD_in, RV_in, RG_in, RPI_in, EPS_W_in)
431
432
433   USE ioipsl_getin_p_mod, ONLY : getin_p
434
435   REAL, INTENT(IN)      :: dtime
436   INTEGER, INTENT(IN)   :: lunout_in,prt_level_in,iflag_ratqs_in,fl_cor_ebil_in
437   LOGICAL, INTENT(IN)   :: ok_ice_supersat_in, ok_no_issr_strato_in, ok_plane_contrail_in
438
439   REAL, INTENT(IN)      :: RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in
440   REAL, INTENT(IN)      :: RVTMP2_in, RTT_in, RD_in, RV_in, RG_in, RPI_in, EPS_W_in
441   character (len=20) :: modname='lscp_ini_mod'
442   character (len=80) :: abort_message
443
444
445    lunout=lunout_in
446    prt_level=prt_level_in
447    fl_cor_ebil=fl_cor_ebil_in
448    iflag_ratqs=iflag_ratqs_in
449    ok_ice_supersat=ok_ice_supersat_in
450    ok_no_issr_strato=ok_no_issr_strato_in
451    ok_plane_contrail=ok_plane_contrail_in
452
453    RG=RG_in
454    RD=RD_in
455    RV=RV_in
456    RCPD=RCPD_in
457    RLVTT=RLVTT_in
458    RLSTT=RLSTT_in
459    RLMLT=RLMLT_in
460    RTT=RTT_in
461    RV=RV_in
462    RVTMP2=RVTMP2_in
463    RPI=RPI_in
464    EPS_W=EPS_W_in
465
466
467
468    CALL getin_p('niter_lscp',niter_lscp)
469    CALL getin_p('iflag_evap_prec',iflag_evap_prec)
470    CALL getin_p('seuil_neb',seuil_neb)
471    CALL getin_p('ok_radocond_snow',ok_radocond_snow)
472    CALL getin_p('t_glace_max',t_glace_max)
473    CALL getin_p('t_glace_min',t_glace_min)
474    CALL getin_p('exposant_glace',exposant_glace)
475    CALL getin_p('iflag_vice',iflag_vice)
476    CALL getin_p('iflag_t_glace',iflag_t_glace)
477    CALL getin_p('iflag_gammasat',iflag_gammasat)
478    CALL getin_p('iflag_rain_incloud_vol',iflag_rain_incloud_vol)
479    CALL getin_p('iflag_bergeron',iflag_bergeron)
480    CALL getin_p('iflag_fisrtilp_qsat',iflag_fisrtilp_qsat)
481    CALL getin_p('iflag_pdf',iflag_pdf)
482    CALL getin_p('iflag_icefrac',iflag_icefrac)
483    CALL getin_p('reevap_ice',reevap_ice)
484    CALL getin_p('cld_lc_lsc',cld_lc_lsc)
485    CALL getin_p('cld_lc_con',cld_lc_con)
486    CALL getin_p('cld_lc_lsc_snow',cld_lc_lsc_snow)
487    CALL getin_p('cld_lc_con_snow',cld_lc_con_snow)
488    CALL getin_p('cld_tau_lsc',cld_tau_lsc)
489    CALL getin_p('cld_tau_con',cld_tau_con)
490    CALL getin_p('cld_expo_lsc',cld_expo_lsc)
491    CALL getin_p('cld_expo_con',cld_expo_con)
492    CALL getin_p('ffallv_lsc',ffallv_lsc)
493    CALL getin_p('ffallv_lsc',ffallv_con)
494    ! for poprecip and cloud phase
495    CALL getin_p('coef_eva',coef_eva)
496    coef_sub=coef_eva
497    CALL getin_p('coef_eva_i',coef_sub)
498    CALL getin_p('coef_sub',coef_sub)
499    CALL getin_p('expo_eva',expo_eva)
500    expo_sub=expo_eva
501    CALL getin_p('expo_sub',expo_sub)
502    CALL getin_p('iflag_autoconversion',iflag_autoconversion)
503    CALL getin_p('dist_liq',dist_liq)
504    CALL getin_p('tresh_cl',tresh_cl)
505    CALL getin_p('capa_crystal',capa_crystal)
506    CALL getin_p('naero5',naero5)
507    CALL getin_p('gamma_snwretro',gamma_snwretro)
508    CALL getin_p('gamma_taud',gamma_taud)
509    CALL getin_p('gamma_mixth',gamma_mixth)
510    CALL getin_p('iflag_oldbug_fisrtilp',iflag_oldbug_fisrtilp)
511    CALL getin_p('temp_nowater',temp_nowater)
512    CALL getin_p('ok_bug_phase_lscp',ok_bug_phase_lscp)
513    CALL getin_p('ok_bug_ice_fallspeed',ok_bug_ice_fallspeed)
514    CALL getin_p('ok_poprecip',ok_poprecip)
515    CALL getin_p('ok_corr_vap_evasub',ok_corr_vap_evasub)
516    CALL getin_p('ok_growth_precip_deposition',ok_growth_precip_deposition)
517    CALL getin_p('rain_int_min',rain_int_min)
518    CALL getin_p('gamma_agg',gamma_agg)
519    CALL getin_p('gamma_col',gamma_col)
520    CALL getin_p('gamma_rim',gamma_rim)
521    CALL getin_p('gamma_freez',gamma_freez)
522    CALL getin_p('gamma_melt',gamma_melt)
523    CALL getin_p('tau_auto_snow_max',tau_auto_snow_max)
524    CALL getin_p('tau_auto_snow_min',tau_auto_snow_min)
525    CALL getin_p('expo_tau_auto_snow', expo_tau_auto_snow)
526    CALL getin_p('alpha_freez',alpha_freez)
527    CALL getin_p('beta_freez',beta_freez)
528    CALL getin_p('r_snow',r_snow)
529    CALL getin_p('rain_fallspeed',rain_fallspeed)
530    rain_fallspeed_clr=rain_fallspeed
531    rain_fallspeed_cld=rain_fallspeed
532    CALL getin_p('rain_fallspeed_clr',rain_fallspeed_clr)
533    CALL getin_p('rain_fallspeed_cld',rain_fallspeed_cld)
534    CALL getin_p('snow_fallspeed',snow_fallspeed)
535    snow_fallspeed_clr=snow_fallspeed
536    snow_fallspeed_cld=snow_fallspeed
537    CALL getin_p('snow_fallspeed_clr',snow_fallspeed_clr)
538    CALL getin_p('snow_fallspeed_cld',snow_fallspeed_cld)
539    CALL getin_p('ok_ice_sedim',ok_ice_sedim)
540    CALL getin_p('fallice_sedim',fallice_sedim)
541    CALL getin_p('chi_sedim',chi_sedim)
542    ! for condensation and ice supersaturation
543    CALL getin_p('ok_unadjusted_clouds',ok_unadjusted_clouds)
544    CALL getin_p('ok_weibull_warm_clouds',ok_weibull_warm_clouds)
545    CALL getin_p('ok_nodeep_lscp',ok_nodeep_lscp)
546    CALL getin_p('ok_nodeep_lscp_rad',ok_nodeep_lscp_rad)
547    ffallv_issr=ffallv_lsc
548    CALL getin_p('ffallv_issr',ffallv_issr)
549    CALL getin_p('cooling_rate_ice_thresh',cooling_rate_ice_thresh)
550    CALL getin_p('depo_coef_cirrus',depo_coef_cirrus)
551    CALL getin_p('capa_cond_cirrus',capa_cond_cirrus)
552    CALL getin_p('N_ice_volume',N_ice_volume)
553    CALL getin_p('nu_iwc_pdf_lscp',nu_iwc_pdf_lscp)
554    CALL getin_p('beta_pdf_lscp',beta_pdf_lscp)
555    CALL getin_p('temp_thresh_pdf_lscp',temp_thresh_pdf_lscp)
556    CALL getin_p('k0_pdf_lscp',k0_pdf_lscp)
557    CALL getin_p('kappa_pdf_lscp',kappa_pdf_lscp)
558    CALL getin_p('std100_pdf_lscp',std100_pdf_lscp)
559    CALL getin_p('a_homofreez',a_homofreez)
560    CALL getin_p('b_homofreez',b_homofreez)
561    CALL getin_p('delta_hetfreez',delta_hetfreez)
562    CALL getin_p('aspect_ratio_cirrus',aspect_ratio_cirrus)
563    CALL getin_p('coef_mixing_lscp',coef_mixing_lscp)
564    CALL getin_p('coef_shear_lscp',coef_shear_lscp)
565    CALL getin_p('chi_mixing',chi_mixing)
566    ! for aviation
567    CALL getin_p('ok_precip_contrails',ok_precip_contrails)
568    CALL getin_p('aspect_ratio_lincontrails',aspect_ratio_lincontrails)
569    coef_mixing_lincontrails=coef_mixing_lscp
570    CALL getin_p('coef_mixing_lincontrails',coef_mixing_lincontrails)
571    coef_shear_lincontrails=coef_shear_lscp
572    CALL getin_p('coef_shear_lincontrails',coef_shear_lincontrails)
573    CALL getin_p('chi_mixing_lincontrails',chi_mixing_lincontrails)
574    CALL getin_p('EI_H2O_aviation',EI_H2O_aviation)
575    CALL getin_p('qheat_fuel_aviation',qheat_fuel_aviation)
576    CALL getin_p('prop_efficiency_aviation',prop_efficiency_aviation)
577    CALL getin_p('linear_contrails_lifetime',linear_contrails_lifetime)
578    CALL getin_p('initial_width_contrails',initial_width_contrails)
579    CALL getin_p('initial_height_contrails',initial_height_contrails)
580    CALL getin_p('fallice_linear_contrails',fallice_linear_contrails)
581    CALL getin_p('fallice_cirrus_contrails',fallice_cirrus_contrails)
582    CALL getin_p('aviation_coef',aviation_coef)
583    ! for cloudth routines
584    CALL getin_p('ok_lscp_mergecond',ok_lscp_mergecond)
585    CALL getin_p('iflag_cloudth_vert',iflag_cloudth_vert)
586    CALL getin_p('cloudth_ratqsmin',cloudth_ratqsmin)
587    CALL getin_p('cloudth_sigma1s_factor',sigma1s_factor)
588    CALL getin_p('cloudth_sigma1s_power',sigma1s_power)
589    CALL getin_p('cloudth_sigma2s_factor',sigma2s_factor)
590    CALL getin_p('cloudth_sigma2s_power',sigma2s_power)
591    CALL getin_p('cloudth_vert_alpha',vert_alpha)
592    vert_alpha_th=vert_alpha
593    CALL getin_p('cloudth_vert_alpha_th',vert_alpha_th)
594    CALL getin_p('iflag_cloudth_vert_noratqs',iflag_cloudth_vert_noratqs)
595
596    WRITE(lunout,*) 'lscp_ini, niter_lscp:', niter_lscp
597    WRITE(lunout,*) 'lscp_ini, iflag_evap_prec:', iflag_evap_prec
598    WRITE(lunout,*) 'lscp_ini, seuil_neb:', seuil_neb
599    WRITE(lunout,*) 'lscp_ini, ok_radocond_snow:', ok_radocond_snow
600    WRITE(lunout,*) 'lscp_ini, t_glace_max:', t_glace_max
601    WRITE(lunout,*) 'lscp_ini, t_glace_min:', t_glace_min
602    WRITE(lunout,*) 'lscp_ini, exposant_glace:', exposant_glace
603    WRITE(lunout,*) 'lscp_ini, iflag_vice:', iflag_vice
604    WRITE(lunout,*) 'lscp_ini, iflag_t_glace:', iflag_t_glace
605    WRITE(lunout,*) 'lscp_ini, iflag_gammasat:', iflag_gammasat
606    WRITE(lunout,*) 'lscp_ini, iflag_rain_incloud_vol:', iflag_rain_incloud_vol
607    WRITE(lunout,*) 'lscp_ini, iflag_bergeron:', iflag_bergeron
608    WRITE(lunout,*) 'lscp_ini, iflag_fisrtilp_qsat:', iflag_fisrtilp_qsat
609    WRITE(lunout,*) 'lscp_ini, iflag_pdf', iflag_pdf
610    WRITE(lunout,*) 'lscp_ini, iflag_icefrac', iflag_icefrac
611    WRITE(lunout,*) 'lscp_ini, reevap_ice', reevap_ice
612    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc', cld_lc_lsc
613    WRITE(lunout,*) 'lscp_ini, cld_lc_con', cld_lc_con
614    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc_snow', cld_lc_lsc_snow
615    WRITE(lunout,*) 'lscp_ini, cld_lc_con_snow', cld_lc_con_snow
616    WRITE(lunout,*) 'lscp_ini, cld_tau_lsc', cld_tau_lsc
617    WRITE(lunout,*) 'lscp_ini, cld_tau_con', cld_tau_con
618    WRITE(lunout,*) 'lscp_ini, cld_expo_lsc', cld_expo_lsc
619    WRITE(lunout,*) 'lscp_ini, cld_expo_con', cld_expo_con
620    WRITE(lunout,*) 'lscp_ini, ffallv_lsc', ffallv_lsc
621    WRITE(lunout,*) 'lscp_ini, ffallv_con', ffallv_con
622    WRITE(lunout,*) 'lscp_ini, coef_eva', coef_eva
623    WRITE(lunout,*) 'lscp_ini, coef_sub', coef_sub
624    WRITE(lunout,*) 'lscp_ini, expo_eva', expo_eva
625    WRITE(lunout,*) 'lscp_ini, expo_sub', expo_sub
626    WRITE(lunout,*) 'lscp_ini, iflag_autoconversion', iflag_autoconversion
627    WRITE(lunout,*) 'lscp_ini, dist_liq', dist_liq
628    WRITE(lunout,*) 'lscp_ini, tresh_cl', tresh_cl
629    WRITE(lunout,*) 'lscp_ini, capa_crystal', capa_crystal
630    WRITE(lunout,*) 'lscp_ini, naero5', naero5
631    WRITE(lunout,*) 'lscp_ini, gamma_snwretro', gamma_snwretro
632    WRITE(lunout,*) 'lscp_ini, gamma_mixth', gamma_mixth
633    WRITE(lunout,*) 'lscp_ini, gamma_taud', gamma_taud
634    WRITE(lunout,*) 'lscp_ini, iflag_oldbug_fisrtilp', iflag_oldbug_fisrtilp
635    WRITE(lunout,*) 'lscp_ini, fl_cor_ebil', fl_cor_ebil
636    WRITE(lunout,*) 'lscp_ini, temp_nowater', temp_nowater
637    WRITE(lunout,*) 'lscp_ini, ok_bug_phase_lscp', ok_bug_phase_lscp
638    WRITE(lunout,*) 'lscp_ini, ok_bug_ice_fallspeed', ok_bug_ice_fallspeed
639    ! for poprecip
640    WRITE(lunout,*) 'lscp_ini, ok_poprecip', ok_poprecip
641    WRITE(lunout,*) 'lscp_ini, ok_corr_vap_evasub', ok_corr_vap_evasub
642    WRITE(lunout,*) 'lscp_ini, ok_growth_precip_deposition', ok_growth_precip_deposition
643    WRITE(lunout,*) 'lscp_ini, rain_int_min:', rain_int_min
644    WRITE(lunout,*) 'lscp_ini, gamma_agg:', gamma_agg
645    WRITE(lunout,*) 'lscp_ini, gamma_col:', gamma_col
646    WRITE(lunout,*) 'lscp_ini, gamma_rim:', gamma_rim
647    WRITE(lunout,*) 'lscp_ini, gamma_freez:', gamma_freez
648    WRITE(lunout,*) 'lscp_ini, gamma_melt:', gamma_melt
649    WRITE(lunout,*) 'lscp_ini, tau_auto_snow_max:',tau_auto_snow_max
650    WRITE(lunout,*) 'lscp_ini, tau_auto_snow_min:',tau_auto_snow_min
651    WRITE(lunout,*) 'lscp_ini, expo_tau_auto_snow:',expo_tau_auto_snow
652    WRITE(lunout,*) 'lscp_ini, r_snow:', r_snow
653    WRITE(lunout,*) 'lscp_ini, alpha_freez:', alpha_freez
654    WRITE(lunout,*) 'lscp_ini, beta_freez:', beta_freez
655    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_clr:', rain_fallspeed_clr
656    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_cld:', rain_fallspeed_cld
657    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_clr:', snow_fallspeed_clr
658    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_cld:', snow_fallspeed_cld
659    WRITE(lunout,*) 'lscp_ini, ok_ice_sedim:', ok_ice_sedim
660    WRITE(lunout,*) 'lscp_ini, fallice_sedim:', fallice_sedim
661    WRITE(lunout,*) 'lscp_ini, chi_sedim:', chi_sedim
662    ! for condensation and ice supersaturation
663    WRITE(lunout,*) 'lscp_ini, ok_ice_supersat:', ok_ice_supersat
664    WRITE(lunout,*) 'lscp_ini, ok_unadjusted_clouds:', ok_unadjusted_clouds
665    WRITE(lunout,*) 'lscp_ini, ok_weibull_warm_clouds:', ok_weibull_warm_clouds
666    WRITE(lunout,*) 'lscp_ini, ok_nodeep_lscp:', ok_nodeep_lscp
667    WRITE(lunout,*) 'lscp_ini, ok_nodeep_lscp_rad:', ok_nodeep_lscp_rad
668    WRITE(lunout,*) 'lscp_ini, ffallv_issr', ffallv_issr
669    WRITE(lunout,*) 'lscp_ini, cooling_rate_ice_thresh', cooling_rate_ice_thresh
670    WRITE(lunout,*) 'lscp_ini, depo_coef_cirrus:', depo_coef_cirrus
671    WRITE(lunout,*) 'lscp_ini, capa_cond_cirrus:', capa_cond_cirrus
672    WRITE(lunout,*) 'lscp_ini, N_ice_volume:', N_ice_volume
673    WRITE(lunout,*) 'lscp_ini, nu_iwc_pdf_lscp:', nu_iwc_pdf_lscp
674    WRITE(lunout,*) 'lscp_ini, beta_pdf_lscp:', beta_pdf_lscp
675    WRITE(lunout,*) 'lscp_ini, temp_thresh_pdf_lscp:', temp_thresh_pdf_lscp
676    WRITE(lunout,*) 'lscp_ini, k0_pdf_lscp:', k0_pdf_lscp
677    WRITE(lunout,*) 'lscp_ini, kappa_pdf_lscp:', kappa_pdf_lscp
678    WRITE(lunout,*) 'lscp_ini, std100_pdf_lscp:', std100_pdf_lscp
679    WRITE(lunout,*) 'lscp_ini, a_homofreez:', a_homofreez
680    WRITE(lunout,*) 'lscp_ini, b_homofreez:', b_homofreez
681    WRITE(lunout,*) 'lscp_ini, delta_hetfreez', delta_hetfreez
682    WRITE(lunout,*) 'lscp_ini, aspect_ratio_cirrus:', aspect_ratio_cirrus
683    WRITE(lunout,*) 'lscp_ini, coef_mixing_lscp:', coef_mixing_lscp
684    WRITE(lunout,*) 'lscp_ini, coef_shear_lscp:', coef_shear_lscp
685    WRITE(lunout,*) 'lscp_ini, chi_mixing:', chi_mixing
686    ! for aviation
687    WRITE(lunout,*) 'lscp_ini, ok_precip_contrails:', ok_precip_contrails
688    WRITE(lunout,*) 'lscp_ini, aspect_ratio_lincontrails:', aspect_ratio_lincontrails
689    WRITE(lunout,*) 'lscp_ini, coef_mixing_lincontrails:', coef_mixing_lincontrails
690    WRITE(lunout,*) 'lscp_ini, coef_shear_lincontrails:', coef_shear_lincontrails
691    WRITE(lunout,*) 'lscp_ini, chi_mixing_lincontrails:', chi_mixing_lincontrails
692    WRITE(lunout,*) 'lscp_ini, EI_H2O_aviation:', EI_H2O_aviation
693    WRITE(lunout,*) 'lscp_ini, qheat_fuel_aviation:', qheat_fuel_aviation
694    WRITE(lunout,*) 'lscp_ini, prop_efficiency_aviation:', prop_efficiency_aviation
695    WRITE(lunout,*) 'lscp_ini, linear_contrails_lifetime:', linear_contrails_lifetime
696    WRITE(lunout,*) 'lscp_ini, initial_width_contrails:', initial_width_contrails
697    WRITE(lunout,*) 'lscp_ini, initial_height_contrails:', initial_height_contrails
698    WRITE(lunout,*) 'lscp_ini, fallice_linear_contrails:', fallice_linear_contrails
699    WRITE(lunout,*) 'lscp_ini, fallice_cirrus_contrails:', fallice_cirrus_contrails
700    WRITE(lunout,*) 'lscp_ini, aviation_coef:', aviation_coef
701    ! for cloudth routines
702    WRITE(lunout,*) 'lscp_ini, ok_lscp_mergecond:', ok_lscp_mergecond
703    WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert:', iflag_cloudth_vert
704    WRITE(lunout,*) 'lscp_ini, cloudth_ratqsmin:', cloudth_ratqsmin
705    WRITE(lunout,*) 'lscp_ini, cloudth_sigma1s_factor:', sigma1s_factor
706    WRITE(lunout,*) 'lscp_ini, cloudth_sigma1s_power:', sigma1s_power
707    WRITE(lunout,*) 'lscp_ini, cloudth_sigma2s_factor:', sigma2s_factor
708    WRITE(lunout,*) 'lscp_ini, cloudth_sigma2s_power:', sigma2s_power
709    WRITE(lunout,*) 'lscp_ini, cloudth_vert_alpha:', vert_alpha
710    WRITE(lunout,*) 'lscp_ini, cloudth_vert_alpha_th:', vert_alpha_th
711    WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert_noratqs:', iflag_cloudth_vert_noratqs
712
713
714    ! check consistency for cloud phase partitioning options
715
716    IF ((iflag_icefrac .GE. 2) .AND. (.NOT. ok_lscp_mergecond)) THEN
717      abort_message = 'in lscp, iflag_icefrac .GE. 2 works only if ok_lscp_mergecond=.TRUE.'
718      CALL abort_physic (modname,abort_message,1)
719    ENDIF
720
721    ! check for precipitation sub-time steps
722    IF (ABS(dtime/REAL(niter_lscp)-360.0).GT.0.001) THEN
723        WRITE(lunout,*) 'lscp: it is not expected, see Z.X.Li', dtime
724        WRITE(lunout,*) 'I would prefer a 6 min sub-timestep'
725    ENDIF
726
727    ! check consistency between numerical resolution of autoconversion
728    ! and other options
729   
730    IF ((iflag_autoconversion .EQ. 2) .AND. .NOT. ok_poprecip) THEN
731        IF ((iflag_vice .NE. 0) .OR. (niter_lscp .GT. 1)) THEN
732           abort_message = 'in lscp, iflag_autoconversion=2 requires iflag_vice=0 and niter_lscp=1'
733           CALL abort_physic (modname,abort_message,1)
734        ENDIF
735    ENDIF
736
737
738    IF ( ok_weibull_warm_clouds .AND. .NOT. ok_ice_supersat ) THEN
739      abort_message = 'in lscp, ok_weibull_warm_clouds=y needs ok_ice_supersat=y'
740      CALL abort_physic (modname,abort_message,1)
741    ENDIF
742
743    IF ( ok_unadjusted_clouds .AND. .NOT. ok_ice_supersat ) THEN
744      abort_message = 'in lscp, ok_unadjusted_clouds=y needs ok_ice_supersat=y'
745      CALL abort_physic (modname,abort_message,1)
746    ENDIF
747
748    IF ( (iflag_icefrac .GE. 1) .AND. (.NOT. ok_poprecip .AND. (iflag_evap_prec .LT. 4)) ) THEN
749      abort_message = 'in lscp, icefracturb works with poprecip or with precip evap option >=4'
750      CALL abort_physic (modname,abort_message,1)
751    ENDIF
752
753    !--Calculated here to lighten calculations
754    corr_incld_depsub = GAMMA(nu_iwc_pdf_lscp + 1./3.) / GAMMA(nu_iwc_pdf_lscp) &
755                      / nu_iwc_pdf_lscp**(1./3.)
756
757    !AA Temporary initialisation
758    a_tr_sca(1) = -0.5
759    a_tr_sca(2) = -0.5
760    a_tr_sca(3) = -0.5
761    a_tr_sca(4) = -0.5
762   
763
764RETURN
765
766END SUBROUTINE lscp_ini
767
768END MODULE lmdz_lscp_ini
Note: See TracBrowser for help on using the repository browser.