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

Last change on this file since 5428 was 5412, checked in by evignon, 10 days ago

mise sous flag d'un bug sur la phase des nuages dans lscp
identifie par A. Borella

File size: 26.0 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  REAL, SAVE, PROTECTED :: seuil_neb=0.001      ! cloud fraction threshold: a cloud can precipitate when exceeded
12  !$OMP THREADPRIVATE(seuil_neb)
13
14  REAL, SAVE, PROTECTED :: min_neb_th=1e-10      ! a cloud produced by bi-gaussian really exists when exceeded
15  !$OMP THREADPRIVATE(min_neb_th)
16
17  REAL, SAVE, PROTECTED :: min_frac_thermals=1.e-10   ! minimum thermals fraction for use of bigaussian distribution
18  !$OMP THREADPRIVATE(min_frac_thermals)
19
20  INTEGER, SAVE :: lunout, prt_level            ! Logical unit number and level for standard output
21  !$OMP THREADPRIVATE(lunout,prt_level)
22
23  INTEGER, SAVE, PROTECTED :: niter_lscp=5      ! number of iterations to calculate autoconversion to precipitation
24  !$OMP THREADPRIVATE(niter_lscp)
25
26  INTEGER, SAVE, PROTECTED :: iflag_evap_prec=1 ! precipitation evaporation flag. 0: nothing, 1: "old way",
27                                                ! 2: Max cloud fraction above to calculate the max of reevaporation
28                                                ! >=4: LTP'method i.e. evaporation in the clear-sky fraction of the mesh only
29                                                ! pay attention that iflag_evap_prec=4 may lead to unrealistic and overestimated
30                                                ! evaporation. Use 5 instead
31  !$OMP THREADPRIVATE(iflag_evap_prec)
32
33  REAL, SAVE, PROTECTED :: t_coup=234.0         ! temperature threshold which determines the phase
34                                                ! for which the saturation vapor pressure is calculated
35  !$OMP THREADPRIVATE(t_coup)
36  REAL, SAVE, PROTECTED :: DDT0=0.01            ! iteration parameter
37  !$OMP THREADPRIVATE(DDT0)
38
39  REAL, SAVE, PROTECTED :: ztfondue=278.15      ! parameter to calculate melting fraction of precipitation
40  !$OMP THREADPRIVATE(ztfondue)
41
42  REAL, SAVE, PROTECTED :: temp_nowater=235.15  ! temperature below which liquid water no longer exists
43  !$OMP THREADPRIVATE(temp_nowater)
44
45  REAL, SAVE, PROTECTED :: a_tr_sca(4)          ! Variables for tracers temporary: alpha parameter for scavenging, 4 possible scavenging processes
46  !$OMP THREADPRIVATE(a_tr_sca)
47 
48  REAL, SAVE, PROTECTED ::  min_frac_th_cld=1.e-10   ! minimum thermal fraction to compute a thermal cloud fraction
49  !$OMP THREADPRIVATE(min_frac_th_cld)
50
51  LOGICAL, SAVE, PROTECTED :: ok_radocond_snow=.false. ! take into account the mass of ice precip in the cloud ice content seen by radiation
52  !$OMP THREADPRIVATE(ok_radocond_snow)
53
54  REAL, SAVE, PROTECTED :: t_glace_min=258.0    ! lower-bound temperature parameter for cloud phase determination
55  !$OMP THREADPRIVATE(t_glace_min)
56
57  REAL, SAVE, PROTECTED :: t_glace_max=273.15   ! upper-bound temperature parameter for cloud phase determination
58  !$OMP THREADPRIVATE(t_glace_max)
59
60  REAL, SAVE, PROTECTED :: exposant_glace=1.0   ! parameter for cloud phase determination
61  !$OMP THREADPRIVATE(exposant_glace)
62
63  INTEGER, SAVE, PROTECTED :: iflag_vice=0      ! which expression for ice crystall fall velocity
64  !$OMP THREADPRIVATE(iflag_vice)
65
66  INTEGER, SAVE, PROTECTED :: iflag_t_glace=0   ! which expression for cloud phase partitioning
67  !$OMP THREADPRIVATE(iflag_t_glace)
68
69  INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert=0          ! option for determining cloud fraction and content in convective boundary layers
70  !$OMP THREADPRIVATE(iflag_cloudth_vert)
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
136  !$OMP THREADPRIVATE(cice_velo)
137
138  REAL, SAVE, PROTECTED ::  dice_velo=0.16                  ! exponent in the ice fall velocity formulation
139  !$OMP THREADPRIVATE(dice_velo)
140
141  REAL, SAVE, PROTECTED :: dist_liq=300.                    ! typical deph of cloud-top liquid layer in mpcs
142  !$OMP THREADPRIVATE(dist_liq)
143
144  REAL, SAVE, PROTECTED  :: tresh_cl=0.0                  ! cloud fraction threshold for cloud top search
145  !$OMP THREADPRIVATE(tresh_cl)
146
147  !--Parameters for condensation and ice supersaturation
148
149  LOGICAL, SAVE, PROTECTED :: ok_ice_supersat=.FALSE.        ! activates the condensation scheme that allows for ice supersaturation
150  !$OMP THREADPRIVATE(ok_ice_supersat)
151
152  LOGICAL, SAVE, PROTECTED :: ok_unadjusted_clouds=.FALSE.   ! if True, relax the saturation adjustment assumption for ice clouds
153  !$OMP THREADPRIVATE(ok_unadjusted_clouds)
154
155  LOGICAL, SAVE, PROTECTED :: ok_weibull_warm_clouds=.FALSE. ! if True, the weibull condensation scheme replaces the lognormal condensation scheme at positive temperatures
156  !$OMP THREADPRIVATE(ok_weibull_warm_clouds)
157
158  INTEGER, SAVE, PROTECTED :: iflag_cloud_sublim_pdf=4       ! iflag for the distribution of water inside ice clouds
159  !$OMP THREADPRIVATE(iflag_cloud_sublim_pdf)
160
161  REAL, SAVE, PROTECTED :: depo_coef_cirrus=.7               ! [-] deposition coefficient for growth of ice crystals in cirrus clouds
162  !$OMP THREADPRIVATE(depo_coef_cirrus)
163
164  REAL, SAVE, PROTECTED :: capa_cond_cirrus=.5               ! [-] capacitance factor for growth/sublimation of ice crystals in cirrus clouds
165  !$OMP THREADPRIVATE(capa_cond_cirrus)
166
167  REAL, SAVE, PROTECTED :: std_subl_pdf_lscp=2.              ! [%] standard deviation of the gaussian distribution of water inside ice clouds
168  !$OMP THREADPRIVATE(std_subl_pdf_lscp)
169
170  REAL, SAVE, PROTECTED :: mu_subl_pdf_lscp=1./3.            ! [-] shape factor of the gamma distribution of water inside ice clouds
171  !$OMP THREADPRIVATE(mu_subl_pdf_lscp)
172 
173  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
174  !$OMP THREADPRIVATE(beta_pdf_lscp)
175 
176  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
177  !$OMP THREADPRIVATE(temp_thresh_pdf_lscp)
178 
179  REAL, SAVE, PROTECTED :: k0_pdf_lscp=3.01                  ! [-] factor for the PDF fit of water vapor in UTLS
180  !$OMP THREADPRIVATE(k0_pdf_lscp)
181 
182  REAL, SAVE, PROTECTED :: kappa_pdf_lscp=0.0192             ! [] factor for the PDF fit of water vapor in UTLS
183  !$OMP THREADPRIVATE(kappa_pdf_lscp)
184 
185  REAL, SAVE, PROTECTED :: std100_pdf_lscp=4.08              ! [%] standard deviation at RHliq=100% of the PDF fit of water vapor in UTLS
186  !$OMP THREADPRIVATE(std100_pdf_lscp)
187 
188  REAL, SAVE, PROTECTED :: a_homofreez=2.349                 ! [-] factor for the Koop homogeneous freezing fit
189  !$OMP THREADPRIVATE(a_homofreez)
190 
191  REAL, SAVE, PROTECTED :: b_homofreez=259.                  ! [K] factor for the Koop homogeneous freezing fit
192  !$OMP THREADPRIVATE(b_homofreez)
193
194  REAL, SAVE, PROTECTED :: delta_hetfreez=1.                 ! [-] value between 0 and 1 to simulate for heterogeneous freezing.
195  !$OMP THREADPRIVATE(delta_hetfreez)
196 
197  REAL, SAVE, PROTECTED :: coef_mixing_lscp=9.E-8            ! [-] tuning coefficient for the mixing process
198  !$OMP THREADPRIVATE(coef_mixing_lscp)
199 
200  REAL, SAVE, PROTECTED :: coef_shear_lscp=0.72              ! [-] additional coefficient for the shearing process (subprocess of the mixing process)
201  !$OMP THREADPRIVATE(coef_shear_lscp)
202 
203  REAL, SAVE, PROTECTED :: chi_mixing_lscp=1.                ! [-] factor for the macro distribution of ISSRs wrt clouds in a gridbox
204  !$OMP THREADPRIVATE(chi_mixing_lscp)
205  !--End of the parameters for condensation and ice supersaturation
206
207  !--Parameters for poprecip
208  LOGICAL, SAVE, PROTECTED :: ok_poprecip=.FALSE.           ! use the processes-oriented formulation of precipitations
209  !$OMP THREADPRIVATE(ok_poprecip)
210
211  LOGICAL, SAVE, PROTECTED :: ok_corr_vap_evasub=.FALSE.    ! use the corrected version of clear-sky water vapor for the evap / subl processes
212  !$OMP THREADPRIVATE(ok_corr_vap_evasub)
213
214  REAL, SAVE, PROTECTED :: cld_lc_lsc_snow=2.e-5            ! snow autoconversion coefficient, stratiform. default from  Chaboureau and PInty 2006
215  !$OMP THREADPRIVATE(cld_lc_lsc_snow)
216
217  REAL, SAVE, PROTECTED :: cld_lc_con_snow=2.e-5            ! snow autoconversion coefficient, convective
218  !$OMP THREADPRIVATE(cld_lc_con_snow)
219
220  REAL, SAVE, PROTECTED :: rain_int_min=1.e-5               ! Minimum local rain intensity [mm/s] before the decrease in associated precipitation fraction
221  !$OMP THREADPRIVATE(rain_int_min)
222
223  REAL, SAVE, PROTECTED :: thresh_precip_frac=1.E-6         ! precipitation fraction threshold [-]
224  !$OMP THREADPRIVATE(thresh_precip_frac)
225
226  REAL, SAVE, PROTECTED :: capa_crystal=1.                  ! Crystal capacitance (shape factor) for lscp_icefrac_turb [-]
227  !$OMP THREADPRIVATE(capa_crystal)
228
229  REAL, SAVE, PROTECTED :: naero5=0.5                       ! Number concentration of aerosol larger than 0.5 microns [scm-3]
230  !$OMP THREADPRIVATE(naero5)
231
232  REAL, SAVE, PROTECTED :: gamma_snwretro = 0.              ! Proportion of snow taken into account in ice retroaction in lscp_icefrac_turb [-]
233  !$OMP THREADPRIVATE(gamma_snwretro)
234
235  REAL, SAVE, PROTECTED :: gamma_taud = 1.                  ! Tuning coeff for Lagrangian decorrelation timescale in lscp_icefrac_turb [-]
236  !$OMP THREADPRIVATE(gamma_taud)
237
238  REAL, SAVE, PROTECTED :: gamma_col=1.                     ! Tuning coefficient for rain collection efficiency (poprecip) [-]
239  !$OMP THREADPRIVATE(gamma_col)
240
241  REAL, SAVE, PROTECTED :: gamma_agg=1.                     ! Tuning coefficient for snow aggregation efficiency (poprecip) [-]
242  !$OMP THREADPRIVATE(gamma_agg)
243
244  REAL, SAVE, PROTECTED :: gamma_rim=1.                     ! Tuning coefficient for riming efficiency (poprecip) [-]
245  !$OMP THREADPRIVATE(gamma_rim)
246
247  REAL, SAVE, PROTECTED :: gamma_melt=1.                    ! Tuning coefficient for snow melting efficiency (poprecip) [-]
248  !$OMP THREADPRIVATE(gamma_melt)
249 
250  REAL, SAVE, PROTECTED :: gamma_freez=1.                   ! Tuning coefficient for rain collision freezing efficiency (poprecip) [-]
251  !$OMP THREADPRIVATE(gamma_freez)
252
253  REAL, SAVE, PROTECTED :: rho_rain=1000.                   ! Rain density [kg/m3]
254  !$OMP THREADPRIVATE(rho_rain)
255
256  REAL, SAVE, PROTECTED :: rho_ice=920.                     ! Ice density  [kg/m3]
257  !$OMP THREADPRIVATE(rho_ice)
258
259  REAL, SAVE, PROTECTED :: r_rain=500.E-6                   ! Rain droplets radius (poprecip) [m]
260  !$OMP THREADPRIVATE(r_rain)
261
262  REAL, SAVE, PROTECTED :: r_snow=1.E-3                     ! Ice crystals radius (poprecip) [m]
263  !$OMP THREADPRIVATE(r_snow)
264
265  REAL, SAVE, PROTECTED :: tau_auto_snow_min=100.           ! Snow autoconversion minimal timescale (when liquid) [s]
266  !$OMP THREADPRIVATE(tau_auto_snow_min)
267
268  REAL, SAVE, PROTECTED :: tau_auto_snow_max=1000.          ! Snow autoconversion minimal timescale (when only ice) [s]
269  !$OMP THREADPRIVATE(tau_auto_snow_max)
270
271  REAL, SAVE, PROTECTED :: eps=1.E-10                       ! Treshold 0 [-]
272  !$OMP THREADPRIVATE(eps)
273
274  REAL, SAVE, PROTECTED :: alpha_freez=4.                   ! Slope of exponential for immersion freezing timescale [-]
275  !$OMP THREADPRIVATE(alpha_freez)
276
277  REAL, SAVE, PROTECTED :: beta_freez=0.1                   ! Inv.time immersion freezing [s-1]
278  !$OMP THREADPRIVATE(beta_freez)
279
280  REAL, SAVE, PROTECTED :: rain_fallspeed=4.                ! Rain fall velocity [m/s]
281  !$OMP THREADPRIVATE(rain_fallspeed)
282
283  REAL, SAVE, PROTECTED :: rain_fallspeed_clr               ! Rain fall velocity in clear sky [m/s]
284  !$OMP THREADPRIVATE(rain_fallspeed_clr)
285
286  REAL, SAVE, PROTECTED :: rain_fallspeed_cld               ! Rain fall velocity in cloudy sky [m/s]
287  !$OMP THREADPRIVATE(rain_fallspeed_cld)
288
289  REAL, SAVE, PROTECTED :: snow_fallspeed=1.                ! Snow fall velocity [m/s]
290  !$OMP THREADPRIVATE(snow_fallspeed)
291
292  REAL, SAVE, PROTECTED :: snow_fallspeed_clr               ! Snow fall velocity in clear sky [m/s]
293  !$OMP THREADPRIVATE(snow_fallspeed_clr)
294
295  REAL, SAVE, PROTECTED :: snow_fallspeed_cld               ! Snow fall velocity in cloudy sky [m/s]
296  !$OMP THREADPRIVATE(snow_fallspeed_cld)
297  !--End of the parameters for poprecip
298
299! Two parameters used for lmdz_lscp_old only
300  INTEGER, SAVE, PROTECTED :: iflag_oldbug_fisrtilp=0, fl_cor_ebil
301  !$OMP THREADPRIVATE(iflag_oldbug_fisrtilp,fl_cor_ebil)
302
303CONTAINS
304
305SUBROUTINE lscp_ini(dtime,lunout_in,prt_level_in,ok_ice_supersat_in, iflag_ratqs, fl_cor_ebil_in, &
306                    RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in, RVTMP2_in, &
307                    RTT_in, RD_in, RV_in, RG_in, RPI_in, EPS_W_in)
308
309
310   USE ioipsl_getin_p_mod, ONLY : getin_p
311   USE lmdz_cloudth_ini, ONLY : cloudth_ini
312
313   REAL, INTENT(IN)      :: dtime
314   INTEGER, INTENT(IN)   :: lunout_in,prt_level_in,iflag_ratqs,fl_cor_ebil_in
315   LOGICAL, INTENT(IN)   :: ok_ice_supersat_in
316
317   REAL, INTENT(IN)      :: RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in
318   REAL, INTENT(IN)      :: RVTMP2_in, RTT_in, RD_in, RV_in, RG_in, RPI_in, EPS_W_in
319   character (len=20) :: modname='lscp_ini_mod'
320   character (len=80) :: abort_message
321
322
323    lunout=lunout_in
324    prt_level=prt_level_in
325    fl_cor_ebil=fl_cor_ebil_in
326
327    ok_ice_supersat=ok_ice_supersat_in
328
329    RG=RG_in
330    RD=RD_in
331    RV=RV_in
332    RCPD=RCPD_in
333    RLVTT=RLVTT_in
334    RLSTT=RLSTT_in
335    RLMLT=RLMLT_in
336    RTT=RTT_in
337    RV=RV_in
338    RVTMP2=RVTMP2_in
339    RPI=RPI_in
340    EPS_W=EPS_W_in
341
342
343
344    CALL getin_p('niter_lscp',niter_lscp)
345    CALL getin_p('iflag_evap_prec',iflag_evap_prec)
346    CALL getin_p('seuil_neb',seuil_neb)
347    CALL getin_p('ok_radocond_snow',ok_radocond_snow)
348    CALL getin_p('t_glace_max',t_glace_max)
349    CALL getin_p('t_glace_min',t_glace_min)
350    CALL getin_p('exposant_glace',exposant_glace)
351    CALL getin_p('iflag_vice',iflag_vice)
352    CALL getin_p('iflag_t_glace',iflag_t_glace)
353    CALL getin_p('iflag_cloudth_vert',iflag_cloudth_vert)
354    CALL getin_p('iflag_gammasat',iflag_gammasat)
355    CALL getin_p('iflag_rain_incloud_vol',iflag_rain_incloud_vol)
356    CALL getin_p('iflag_bergeron',iflag_bergeron)
357    CALL getin_p('iflag_fisrtilp_qsat',iflag_fisrtilp_qsat)
358    CALL getin_p('iflag_pdf',iflag_pdf)
359    CALL getin_p('iflag_icefrac',iflag_icefrac)
360    CALL getin_p('reevap_ice',reevap_ice)
361    CALL getin_p('cld_lc_lsc',cld_lc_lsc)
362    CALL getin_p('cld_lc_con',cld_lc_con)
363    CALL getin_p('cld_lc_lsc_snow',cld_lc_lsc_snow)
364    CALL getin_p('cld_lc_con_snow',cld_lc_con_snow)
365    CALL getin_p('cld_tau_lsc',cld_tau_lsc)
366    CALL getin_p('cld_tau_con',cld_tau_con)
367    CALL getin_p('cld_expo_lsc',cld_expo_lsc)
368    CALL getin_p('cld_expo_con',cld_expo_con)
369    CALL getin_p('ffallv_lsc',ffallv_lsc)
370    CALL getin_p('ffallv_lsc',ffallv_con)
371    CALL getin_p('coef_eva',coef_eva)
372    coef_sub=coef_eva
373    CALL getin_p('coef_eva_i',coef_sub)
374    CALL getin_p('coef_sub',coef_sub)
375    CALL getin_p('expo_eva',expo_eva)
376    expo_sub=expo_eva
377    CALL getin_p('expo_sub',expo_sub)
378    CALL getin_p('iflag_autoconversion',iflag_autoconversion)
379    CALL getin_p('dist_liq',dist_liq)
380    CALL getin_p('tresh_cl',tresh_cl)
381    CALL getin_p('capa_crystal',capa_crystal)
382    CALL getin_p('naero5',naero5)
383    CALL getin_p('gamma_snwretro',gamma_snwretro)
384    CALL getin_p('gamma_taud',gamma_taud)
385    CALL getin_p('iflag_oldbug_fisrtilp',iflag_oldbug_fisrtilp)
386    CALL getin_p('temp_nowater',temp_nowater)
387    CALL getin_p('ok_bug_phase_lscp',ok_bug_phase_lscp)
388    ! for poprecip
389    CALL getin_p('ok_poprecip',ok_poprecip)
390    CALL getin_p('ok_corr_vap_evasub',ok_corr_vap_evasub)
391    CALL getin_p('rain_int_min',rain_int_min)
392    CALL getin_p('gamma_agg',gamma_agg)
393    CALL getin_p('gamma_col',gamma_col)
394    CALL getin_p('gamma_rim',gamma_rim)
395    CALL getin_p('gamma_freez',gamma_freez)
396    CALL getin_p('gamma_melt',gamma_melt)
397    CALL getin_p('tau_auto_snow_max',tau_auto_snow_max)
398    CALL getin_p('tau_auto_snow_min',tau_auto_snow_min)
399    CALL getin_p('r_snow',r_snow)
400    CALL getin_p('rain_fallspeed',rain_fallspeed)
401    rain_fallspeed_clr=rain_fallspeed
402    rain_fallspeed_cld=rain_fallspeed
403    CALL getin_p('rain_fallspeed_clr',rain_fallspeed_clr)
404    CALL getin_p('rain_fallspeed_cld',rain_fallspeed_cld)
405    CALL getin_p('snow_fallspeed',snow_fallspeed)
406    snow_fallspeed_clr=snow_fallspeed
407    snow_fallspeed_cld=snow_fallspeed
408    CALL getin_p('snow_fallspeed_clr',snow_fallspeed_clr)
409    CALL getin_p('snow_fallspeed_cld',snow_fallspeed_cld)
410    ! for condensation and ice supersaturation
411    CALL getin_p('ok_unadjusted_clouds',ok_unadjusted_clouds)
412    CALL getin_p('ok_weibull_warm_clouds',ok_weibull_warm_clouds)
413    CALL getin_p('iflag_cloud_sublim_pdf',iflag_cloud_sublim_pdf)
414    CALL getin_p('depo_coef_cirrus',depo_coef_cirrus)
415    CALL getin_p('capa_cond_cirrus',capa_cond_cirrus)
416    CALL getin_p('std_subl_pdf_lscp',std_subl_pdf_lscp)
417    CALL getin_p('mu_subl_pdf_lscp',mu_subl_pdf_lscp)
418    CALL getin_p('beta_pdf_lscp',beta_pdf_lscp)
419    CALL getin_p('temp_thresh_pdf_lscp',temp_thresh_pdf_lscp)
420    CALL getin_p('k0_pdf_lscp',k0_pdf_lscp)
421    CALL getin_p('kappa_pdf_lscp',kappa_pdf_lscp)
422    CALL getin_p('std100_pdf_lscp',std100_pdf_lscp)
423    CALL getin_p('a_homofreez',a_homofreez)
424    CALL getin_p('b_homofreez',b_homofreez)
425    CALL getin_p('delta_hetfreez',delta_hetfreez)
426    CALL getin_p('coef_mixing_lscp',coef_mixing_lscp)
427    CALL getin_p('coef_shear_lscp',coef_shear_lscp)
428    CALL getin_p('chi_mixing_lscp',chi_mixing_lscp)
429
430
431
432    WRITE(lunout,*) 'lscp_ini, niter_lscp:', niter_lscp
433    WRITE(lunout,*) 'lscp_ini, iflag_evap_prec:', iflag_evap_prec
434    WRITE(lunout,*) 'lscp_ini, seuil_neb:', seuil_neb
435    WRITE(lunout,*) 'lscp_ini, ok_radocond_snow:', ok_radocond_snow
436    WRITE(lunout,*) 'lscp_ini, t_glace_max:', t_glace_max
437    WRITE(lunout,*) 'lscp_ini, t_glace_min:', t_glace_min
438    WRITE(lunout,*) 'lscp_ini, exposant_glace:', exposant_glace
439    WRITE(lunout,*) 'lscp_ini, iflag_vice:', iflag_vice
440    WRITE(lunout,*) 'lscp_ini, iflag_t_glace:', iflag_t_glace
441    WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert:', iflag_cloudth_vert
442    WRITE(lunout,*) 'lscp_ini, iflag_gammasat:', iflag_gammasat
443    WRITE(lunout,*) 'lscp_ini, iflag_rain_incloud_vol:', iflag_rain_incloud_vol
444    WRITE(lunout,*) 'lscp_ini, iflag_bergeron:', iflag_bergeron
445    WRITE(lunout,*) 'lscp_ini, iflag_fisrtilp_qsat:', iflag_fisrtilp_qsat
446    WRITE(lunout,*) 'lscp_ini, iflag_pdf', iflag_pdf
447    WRITE(lunout,*) 'lscp_ini, iflag_icefrac', iflag_icefrac
448    WRITE(lunout,*) 'lscp_ini, reevap_ice', reevap_ice
449    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc', cld_lc_lsc
450    WRITE(lunout,*) 'lscp_ini, cld_lc_con', cld_lc_con
451    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc_snow', cld_lc_lsc_snow
452    WRITE(lunout,*) 'lscp_ini, cld_lc_con_snow', cld_lc_con_snow
453    WRITE(lunout,*) 'lscp_ini, cld_tau_lsc', cld_tau_lsc
454    WRITE(lunout,*) 'lscp_ini, cld_tau_con', cld_tau_con
455    WRITE(lunout,*) 'lscp_ini, cld_expo_lsc', cld_expo_lsc
456    WRITE(lunout,*) 'lscp_ini, cld_expo_con', cld_expo_con
457    WRITE(lunout,*) 'lscp_ini, ffallv_lsc', ffallv_lsc
458    WRITE(lunout,*) 'lscp_ini, ffallv_con', ffallv_con
459    WRITE(lunout,*) 'lscp_ini, coef_eva', coef_eva
460    WRITE(lunout,*) 'lscp_ini, coef_sub', coef_sub
461    WRITE(lunout,*) 'lscp_ini, expo_eva', expo_eva
462    WRITE(lunout,*) 'lscp_ini, expo_sub', expo_sub
463    WRITE(lunout,*) 'lscp_ini, iflag_autoconversion', iflag_autoconversion
464    WRITE(lunout,*) 'lscp_ini, dist_liq', dist_liq
465    WRITE(lunout,*) 'lscp_ini, tresh_cl', tresh_cl
466    WRITE(lunout,*) 'lscp_ini, capa_crystal', capa_crystal
467    WRITE(lunout,*) 'lscp_ini, naero5', naero5
468    WRITE(lunout,*) 'lscp_ini, gamma_snwretro', gamma_snwretro
469    WRITE(lunout,*) 'lscp_ini, gamma_taud', gamma_taud
470    WRITE(lunout,*) 'lscp_ini, iflag_oldbug_fisrtilp', iflag_oldbug_fisrtilp
471    WRITE(lunout,*) 'lscp_ini, fl_cor_ebil', fl_cor_ebil
472    WRITE(lunout,*) 'lscp_ini, temp_nowater', temp_nowater
473    WRITE(lunout,*) 'lscp_ini, ok_bug_phase_lscp', ok_bug_phase_lscp
474    ! for poprecip
475    WRITE(lunout,*) 'lscp_ini, ok_poprecip', ok_poprecip
476    WRITE(lunout,*) 'lscp_ini, ok_corr_vap_evasub', ok_corr_vap_evasub
477    WRITE(lunout,*) 'lscp_ini, rain_int_min:', rain_int_min
478    WRITE(lunout,*) 'lscp_ini, gamma_agg:', gamma_agg
479    WRITE(lunout,*) 'lscp_ini, gamma_col:', gamma_col
480    WRITE(lunout,*) 'lscp_ini, gamma_rim:', gamma_rim
481    WRITE(lunout,*) 'lscp_ini, gamma_freez:', gamma_freez
482    WRITE(lunout,*) 'lscp_ini, gamma_melt:', gamma_melt
483    WRITE(lunout,*) 'lscp_ini, tau_auto_snow_max:',tau_auto_snow_max
484    WRITE(lunout,*) 'lscp_ini, tau_auto_snow_min:',tau_auto_snow_min
485    WRITE(lunout,*) 'lscp_ini, r_snow:', r_snow
486    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_clr:', rain_fallspeed_clr
487    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_cld:', rain_fallspeed_cld
488    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_clr:', snow_fallspeed_clr
489    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_cld:', snow_fallspeed_cld
490    ! for condensation and ice supersaturation
491    WRITE(lunout,*) 'lscp_ini, ok_ice_supersat:', ok_ice_supersat
492    WRITE(lunout,*) 'lscp_ini, ok_unadjusted_clouds:', ok_unadjusted_clouds
493    WRITE(lunout,*) 'lscp_ini, ok_weibull_warm_clouds:', ok_weibull_warm_clouds
494    WRITE(lunout,*) 'lscp_ini, iflag_cloud_sublim_pdf:', iflag_cloud_sublim_pdf
495    WRITE(lunout,*) 'lscp_ini, depo_coef_cirrus:', depo_coef_cirrus
496    WRITE(lunout,*) 'lscp_ini, capa_cond_cirrus:', capa_cond_cirrus
497    WRITE(lunout,*) 'lscp_ini, std_subl_pdf_lscp:', std_subl_pdf_lscp
498    WRITE(lunout,*) 'lscp_ini, mu_subl_pdf_lscp:', mu_subl_pdf_lscp
499    WRITE(lunout,*) 'lscp_ini, beta_pdf_lscp:', beta_pdf_lscp
500    WRITE(lunout,*) 'lscp_ini, temp_thresh_pdf_lscp:', temp_thresh_pdf_lscp
501    WRITE(lunout,*) 'lscp_ini, k0_pdf_lscp:', k0_pdf_lscp
502    WRITE(lunout,*) 'lscp_ini, kappa_pdf_lscp:', kappa_pdf_lscp
503    WRITE(lunout,*) 'lscp_ini, std100_pdf_lscp:', std100_pdf_lscp
504    WRITE(lunout,*) 'lscp_ini, a_homofreez:', a_homofreez
505    WRITE(lunout,*) 'lscp_ini, b_homofreez:', b_homofreez
506    WRITE(lunout,*) 'lscp_ini, delta_hetfreez', delta_hetfreez
507    WRITE(lunout,*) 'lscp_ini, coef_mixing_lscp:', coef_mixing_lscp
508    WRITE(lunout,*) 'lscp_ini, coef_shear_lscp:', coef_shear_lscp
509    WRITE(lunout,*) 'lscp_ini, chi_mixing_lscp:', chi_mixing_lscp
510
511
512
513
514
515    ! check for precipitation sub-time steps
516    IF (ABS(dtime/REAL(niter_lscp)-360.0).GT.0.001) THEN
517        WRITE(lunout,*) 'lscp: it is not expected, see Z.X.Li', dtime
518        WRITE(lunout,*) 'I would prefer a 6 min sub-timestep'
519    ENDIF
520
521    ! check consistency between numerical resolution of autoconversion
522    ! and other options
523   
524    IF (iflag_autoconversion .EQ. 2) THEN
525        IF ((iflag_vice .NE. 0) .OR. (niter_lscp .GT. 1)) THEN
526           abort_message = 'in lscp, iflag_autoconversion=2 requires iflag_vice=0 and niter_lscp=1'
527           CALL abort_physic (modname,abort_message,1)
528        ENDIF
529    ENDIF
530
531
532    IF ( ok_weibull_warm_clouds .AND. .NOT. ok_ice_supersat ) THEN
533      abort_message = 'in lscp, ok_weibull_warm_clouds=y needs ok_ice_supersat=y'
534      CALL abort_physic (modname,abort_message,1)
535    ENDIF
536
537    IF ( ok_unadjusted_clouds .AND. .NOT. ok_ice_supersat ) THEN
538      abort_message = 'in lscp, ok_unadjusted_clouds=y needs ok_ice_supersat=y'
539      CALL abort_physic (modname,abort_message,1)
540    ENDIF
541
542
543    !AA Temporary initialisation
544    a_tr_sca(1) = -0.5
545    a_tr_sca(2) = -0.5
546    a_tr_sca(3) = -0.5
547    a_tr_sca(4) = -0.5
548   
549    CALL cloudth_ini(iflag_cloudth_vert,iflag_ratqs)
550
551RETURN
552
553END SUBROUTINE lscp_ini
554
555END MODULE lmdz_lscp_ini
Note: See TracBrowser for help on using the repository browser.