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

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