source: LMDZ6/branches/cirrus/libf/phylmd/lmdz_lscp_ini.F90 @ 5396

Last change on this file since 5396 was 5202, checked in by Laurent Fairhead, 4 months ago

Updating cirrus branch to trunk revision 5171

File size: 26.6 KB
RevLine 
[4664]1MODULE lmdz_lscp_ini
[4380]2
[4654]3IMPLICIT NONE
[4380]4
5  ! PARAMETERS for lscp:
6  !--------------------
[4535]7 
[4951]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
[5019]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
[5202]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
[5202]72  INTEGER, SAVE, PROTECTED :: iflag_gammasat=0              ! which threshold for homogeneous nucleation below -40oC
[4535]73  !$OMP THREADPRIVATE(iflag_gammasat)
74
[5202]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
[5202]78  INTEGER, SAVE, PROTECTED :: iflag_bergeron=0              ! bergeron effect for liquid precipitation treatment 
[4535]79  !$OMP THREADPRIVATE(iflag_bergeron)
80
[5202]81  INTEGER, SAVE, PROTECTED :: iflag_fisrtilp_qsat=0         ! qsat adjustment (iterative) during autoconversion
[4535]82  !$OMP THREADPRIVATE(iflag_fisrtilp_qsat)
83
[5202]84  INTEGER, SAVE, PROTECTED :: iflag_pdf=0                   ! type of subgrid scale qtot pdf
[4535]85  !$OMP THREADPRIVATE(iflag_pdf)
86
[5202]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
[5202]93
94  LOGICAL, SAVE, PROTECTED :: reevap_ice=.false.            ! no liquid precip for T< threshold
[4535]95  !$OMP THREADPRIVATE(reevap_ice)
96
[5202]97  REAL, SAVE, PROTECTED :: cld_lc_lsc=2.6e-4                ! liquid autoconversion coefficient, stratiform rain
[4535]98  !$OMP THREADPRIVATE(cld_lc_lsc)
99
[4803]100  REAL, SAVE, PROTECTED :: cld_lc_con=2.6e-4                ! liquid autoconversion coefficient, convective rain
[4535]101  !$OMP THREADPRIVATE(cld_lc_con)
102
[4803]103  REAL, SAVE, PROTECTED :: cld_tau_lsc=3600.                ! liquid autoconversion timescale, stratiform rain
[4535]104  !$OMP THREADPRIVATE(cld_tau_lsc)
105
[4803]106  REAL, SAVE, PROTECTED :: cld_tau_con=3600.                ! liquid autoconversion timescale, convective rain
[4535]107  !$OMP THREADPRIVATE(cld_tau_con)
108
[4803]109  REAL, SAVE, PROTECTED :: cld_expo_lsc=2.                  ! liquid autoconversion threshold exponent, stratiform rain
[4559]110  !$OMP THREADPRIVATE(cld_expo_lsc)
111
[4803]112  REAL, SAVE, PROTECTED :: cld_expo_con=2.                  ! liquid autoconversion threshold exponent, convective rain
[4559]113  !$OMP THREADPRIVATE(cld_expo_con)
114
[4803]115  REAL, SAVE, PROTECTED :: ffallv_lsc=1.                    ! tuning coefficient crystal fall velocity, stratiform
[4535]116  !$OMP THREADPRIVATE(ffallv_lsc)
117
[4803]118  REAL, SAVE, PROTECTED :: ffallv_con=1.                    ! tuning coefficient crystal fall velocity, convective
[4535]119  !$OMP THREADPRIVATE(ffallv_con)
120
[4803]121  REAL, SAVE, PROTECTED :: coef_eva=2e-5                    ! tuning coefficient liquid precip evaporation
[4535]122  !$OMP THREADPRIVATE(coef_eva)
123
[5202]124  REAL, SAVE, PROTECTED :: coef_sub                         ! tuning coefficient ice precip sublimation
[4830]125  !$OMP THREADPRIVATE(coef_sub)
[4535]126
[4803]127  REAL, SAVE, PROTECTED :: expo_eva=0.5                     ! tuning coefficient liquid precip evaporation
128  !$OMP THREADPRIVATE(expo_eva)
[4535]129
[5202]130  REAL, SAVE, PROTECTED :: expo_sub                         ! tuning coefficient ice precip sublimation
[4830]131  !$OMP THREADPRIVATE(expo_sub)
[4535]132
[4803]133  REAL, SAVE, PROTECTED :: cice_velo=1.645                  ! factor in the ice fall velocity formulation
134  !$OMP THREADPRIVATE(cice_velo)
135
136  REAL, SAVE, PROTECTED ::  dice_velo=0.16                  ! exponent in the ice fall velocity formulation
137  !$OMP THREADPRIVATE(dice_velo)
138
139  REAL, SAVE, PROTECTED :: dist_liq=300.                    ! typical deph of cloud-top liquid layer in mpcs
[4562]140  !$OMP THREADPRIVATE(dist_liq)
[4535]141
[4951]142  REAL, SAVE, PROTECTED  :: tresh_cl=0.0                  ! cloud fraction threshold for cloud top search
[4562]143  !$OMP THREADPRIVATE(tresh_cl)
144
[4951]145  !--Parameters for condensation and ice supersaturation
146  LOGICAL, SAVE, PROTECTED :: ok_external_lognormal=.FALSE.  ! if True, the lognormal condensation scheme is calculated in the lmdz_lscp_condensation routine
147  !$OMP THREADPRIVATE(ok_external_lognormal)
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=3       ! iflag for the distribution of water inside ice clouds
159  !$OMP THREADPRIVATE(iflag_cloud_sublim_pdf)
160
[5165]161  REAL, SAVE, PROTECTED :: depo_coef_cirrus=.5               ! [-] deposition coefficient for growth of ice crystals in cirrus clouds
162  !$OMP THREADPRIVATE(depo_coef_cirrus)
163
[5162]164  REAL, SAVE, PROTECTED :: capa_cond_cirrus=.5               ! [-] capacitance factor for growth/sublimation of ice crystals in cirrus clouds
[5041]165  !$OMP THREADPRIVATE(capa_cond_cirrus)
166
[4951]167  REAL, SAVE, PROTECTED :: mu_subl_pdf_lscp=1./3.            ! [-] shape factor of the gamma distribution of water inside ice clouds
168  !$OMP THREADPRIVATE(mu_subl_pdf_lscp)
169 
[5025]170  REAL, SAVE, PROTECTED :: beta_pdf_lscp=8.75E-4             ! [] tuning coefficient for the standard deviation of the PDF of water vapor in the clear sky region
[4951]171  !$OMP THREADPRIVATE(beta_pdf_lscp)
172 
[5025]173  REAL, SAVE, PROTECTED :: temp_thresh_pdf_lscp=188.         ! [K] factor for the PDF fit of water vapor in UTLS - below this temperature, water vapor is homogeneously distributed in the clear sky region
[4951]174  !$OMP THREADPRIVATE(temp_thresh_pdf_lscp)
175 
[5025]176  REAL, SAVE, PROTECTED :: rhlmid_pdf_lscp=52.8              ! [%] factor for the PDF fit of water vapor in UTLS - below this rel hum wrt liq, std increases with RHliq, above it decreases with RHliq
[4951]177  !$OMP THREADPRIVATE(rhlmid_pdf_lscp)
178 
[5025]179  REAL, SAVE, PROTECTED :: k0_pdf_lscp=2.80                  ! [-] factor for the PDF fit of water vapor in UTLS
[4951]180  !$OMP THREADPRIVATE(k0_pdf_lscp)
181 
[5025]182  REAL, SAVE, PROTECTED :: kappa_pdf_lscp=0.0236             ! [] factor for the PDF fit of water vapor in UTLS
[4951]183  !$OMP THREADPRIVATE(kappa_pdf_lscp)
184 
[5025]185  REAL, SAVE, PROTECTED :: rhl0_pdf_lscp=88.7                ! [%] factor for the PDF fit of water vapor in UTLS
[4951]186  !$OMP THREADPRIVATE(rhl0_pdf_lscp)
187 
[5025]188  REAL, SAVE, PROTECTED :: cond_thresh_pdf_lscp=1.E-10       ! [-] threshold for the formation of new cloud
[4951]189  !$OMP THREADPRIVATE(cond_thresh_pdf_lscp)
190 
[5025]191  REAL, SAVE, PROTECTED :: a_homofreez=2.349                 ! [-] factor for the Koop homogeneous freezing fit
[4951]192  !$OMP THREADPRIVATE(a_homofreez)
193 
[5025]194  REAL, SAVE, PROTECTED :: b_homofreez=259.                  ! [K] factor for the Koop homogeneous freezing fit
[4951]195  !$OMP THREADPRIVATE(b_homofreez)
196
197  REAL, SAVE, PROTECTED :: delta_hetfreez=1.                 ! [-] value between 0 and 1 to simulate for heterogeneous freezing.
198  !$OMP THREADPRIVATE(delta_hetfreez)
199 
[5025]200  REAL, SAVE, PROTECTED :: coef_mixing_lscp=1e-7             ! [-] tuning coefficient for the mixing process
[4951]201  !$OMP THREADPRIVATE(coef_mixing_lscp)
202 
[5025]203  REAL, SAVE, PROTECTED :: coef_shear_lscp=0.1               ! [-] additional coefficient for the shearing process (subprocess of the mixing process)
[4951]204  !$OMP THREADPRIVATE(coef_shear_lscp)
205 
[5025]206  REAL, SAVE, PROTECTED :: chi_mixing_lscp=1.1               ! [-] factor for the macro distribution of ISSRs wrt clouds in a gridbox
[4951]207  !$OMP THREADPRIVATE(chi_mixing_lscp)
208
209!  REAL, SAVE, PROTECTED :: contrail_cross_section=200000.
210!  !$OMP THREADPRIVATE(contrail_cross_section)
211  !--End of the parameters for condensation and ice supersaturation
212
[4803]213  !--Parameters for poprecip
214  LOGICAL, SAVE, PROTECTED :: ok_poprecip=.FALSE.           ! use the processes-oriented formulation of precipitations
215  !$OMP THREADPRIVATE(ok_poprecip)
216
[4913]217  LOGICAL, SAVE, PROTECTED :: ok_corr_vap_evasub=.FALSE.    ! use the corrected version of clear-sky water vapor for the evap / subl processes
218  !$OMP THREADPRIVATE(ok_corr_vap_evasub)
219
[4898]220  REAL, SAVE, PROTECTED :: cld_lc_lsc_snow=2.e-5            ! snow autoconversion coefficient, stratiform. default from  Chaboureau and PInty 2006
[4830]221  !$OMP THREADPRIVATE(cld_lc_lsc_snow)
222
[4898]223  REAL, SAVE, PROTECTED :: cld_lc_con_snow=2.e-5            ! snow autoconversion coefficient, convective
[4830]224  !$OMP THREADPRIVATE(cld_lc_con_snow)
225
[4885]226  REAL, SAVE, PROTECTED :: rain_int_min=1.e-5               ! Minimum local rain intensity [mm/s] before the decrease in associated precipitation fraction
[4803]227  !$OMP THREADPRIVATE(rain_int_min)
228
229  REAL, SAVE, PROTECTED :: thresh_precip_frac=1.E-6         ! precipitation fraction threshold TODO [-]
230  !$OMP THREADPRIVATE(thresh_precip_frac)
231
[5202]232  REAL, SAVE, PROTECTED :: tau_mixenv=100000                ! Homogeneization time of mixed phase clouds [s]
233  !$OMP THREADPRIVATE(tau_mixenv)
234
235    REAL, SAVE, PROTECTED :: capa_crystal=1.                ! Sursaturation of ice part in mixed phase clouds [-]
236  !$OMP THREADPRIVATE(capa_crystal)
237
238  REAL, SAVE, PROTECTED :: lmix_mpc=1000                    ! Length of turbulent zones in Mixed Phase Clouds [m]
239  !$OMP THREADPRIVATE(lmix_mpc)
240
241  REAL, SAVE, PROTECTED :: naero5=0.5                       ! Number concentration of aerosol larger than 0.5 microns [scm-3]
242  !$OMP THREADPRIVATE(naero5)
243
244  REAL, SAVE, PROTECTED :: gamma_snwretro = 0.              ! Proportion of snow taken into account in ice retroaction in icefrac_turb [-]
245  !$OMP THREADPRIVATE(gamma_snwretro)
246
247  REAL, SAVE, PROTECTED :: gamma_taud = 1.                  ! Tuning coeff for tau_dissipturb [-]
248  !$OMP THREADPRIVATE(gamma_taud)
249
[4803]250  REAL, SAVE, PROTECTED :: gamma_col=1.                     ! A COMMENTER TODO [-]
251  !$OMP THREADPRIVATE(gamma_col)
252
253  REAL, SAVE, PROTECTED :: gamma_agg=1.                     ! A COMMENTER TODO [-]
254  !$OMP THREADPRIVATE(gamma_agg)
255
256  REAL, SAVE, PROTECTED :: gamma_rim=1.                     ! A COMMENTER TODO [-]
257  !$OMP THREADPRIVATE(gamma_rim)
258
[5202]259  REAL, SAVE, PROTECTED :: rho_rain=1000.                   ! Rain density [kg/m3]
[4803]260  !$OMP THREADPRIVATE(rho_rain)
261
[5202]262  REAL, SAVE, PROTECTED :: rho_ice=920.                     ! Ice density  [kg/m3]
[4832]263  !$OMP THREADPRIVATE(rho_ice)
264
[5202]265  REAL, SAVE, PROTECTED :: r_rain=500.E-6                   ! Rain droplets radius for POPRECIP [m]
[4803]266  !$OMP THREADPRIVATE(r_rain)
267
[5202]268  REAL, SAVE, PROTECTED :: r_snow=1.E-3                     ! Ice crystals radius for POPRECIP [m]
[4803]269  !$OMP THREADPRIVATE(r_snow)
270
[5202]271  REAL, SAVE, PROTECTED :: tau_auto_snow_min=100.           ! A COMMENTER TODO [s]
[4803]272  !$OMP THREADPRIVATE(tau_auto_snow_min)
273
[4830]274  REAL, SAVE, PROTECTED :: tau_auto_snow_max=1000.          ! A COMMENTER TODO [s]
[4803]275  !$OMP THREADPRIVATE(tau_auto_snow_max)
276
277  REAL, SAVE, PROTECTED :: eps=1.E-10                       ! A COMMENTER TODO [-]
278  !$OMP THREADPRIVATE(eps)
[4818]279
[5202]280  REAL, SAVE, PROTECTED :: gamma_melt=1.                    ! A COMMENTER TODO [-]
[4895]281  !$OMP THREADPRIVATE(gamma_melt)
[4818]282
[5202]283  REAL, SAVE, PROTECTED :: alpha_freez=4.                   ! A COMMENTER TODO [-]
[4818]284  !$OMP THREADPRIVATE(alpha_freez)
285
[5202]286  REAL, SAVE, PROTECTED :: beta_freez=0.1                   ! A COMMENTER TODO [m-3.s-1]
[4830]287  !$OMP THREADPRIVATE(beta_freez)
288
[5202]289  REAL, SAVE, PROTECTED :: gamma_freez=1.                   ! A COMMENTER TODO [-]
[4818]290  !$OMP THREADPRIVATE(gamma_freez)
[4830]291
[5202]292  REAL, SAVE, PROTECTED :: rain_fallspeed=4.                ! A COMMENTER TODO [m/s]
[4830]293  !$OMP THREADPRIVATE(rain_fallspeed)
294
[5202]295  REAL, SAVE, PROTECTED :: rain_fallspeed_clr                ! A COMMENTER TODO [m/s]
[4830]296  !$OMP THREADPRIVATE(rain_fallspeed_clr)
297
[5202]298  REAL, SAVE, PROTECTED :: rain_fallspeed_cld               ! A COMMENTER TODO [m/s]
[4830]299  !$OMP THREADPRIVATE(rain_fallspeed_cld)
300
[5202]301  REAL, SAVE, PROTECTED :: snow_fallspeed=1.               ! A COMMENTER TODO [m/s]
[4830]302  !$OMP THREADPRIVATE(snow_fallspeed)
303
[5202]304  REAL, SAVE, PROTECTED :: snow_fallspeed_clr               ! A COMMENTER TODO [m/s]
[4830]305  !$OMP THREADPRIVATE(snow_fallspeed_clr)
306
[5202]307  REAL, SAVE, PROTECTED :: snow_fallspeed_cld               ! A COMMENTER TODO [m/s]
[4830]308  !$OMP THREADPRIVATE(snow_fallspeed_cld)
[4803]309  !--End of the parameters for poprecip
310
[4666]311! Two parameters used for lmdz_lscp_old only
[4803]312  INTEGER, SAVE, PROTECTED :: iflag_oldbug_fisrtilp=0, fl_cor_ebil
[4666]313  !$OMP THREADPRIVATE(iflag_oldbug_fisrtilp,fl_cor_ebil)
314
[4380]315CONTAINS
316
[4951]317SUBROUTINE lscp_ini(dtime,lunout_in,prt_level_in,ok_ice_supersat_in, iflag_ratqs, fl_cor_ebil_in, &
318                    RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in, RVTMP2_in, &
319                    RTT_in, RD_in, RV_in, RG_in, RPI_in, EPS_W_in)
[4380]320
321
322   USE ioipsl_getin_p_mod, ONLY : getin_p
[4651]323   USE lmdz_cloudth_ini, ONLY : cloudth_ini
[4380]324
325   REAL, INTENT(IN)      :: dtime
[4666]326   INTEGER, INTENT(IN)   :: lunout_in,prt_level_in,iflag_ratqs,fl_cor_ebil_in
[4951]327   LOGICAL, INTENT(IN)   :: ok_ice_supersat_in
[4380]328
[4535]329   REAL, INTENT(IN)      :: RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in
[4951]330   REAL, INTENT(IN)      :: RVTMP2_in, RTT_in, RD_in, RV_in, RG_in, RPI_in, EPS_W_in
[4559]331   character (len=20) :: modname='lscp_ini_mod'
332   character (len=80) :: abort_message
[4535]333
334
[4666]335    lunout=lunout_in
336    prt_level=prt_level_in
337    fl_cor_ebil=fl_cor_ebil_in
338
[4951]339    ok_ice_supersat=ok_ice_supersat_in
340
[4535]341    RG=RG_in
342    RD=RD_in
[4951]343    RV=RV_in
[4535]344    RCPD=RCPD_in
345    RLVTT=RLVTT_in
346    RLSTT=RLSTT_in
347    RLMLT=RLMLT_in
348    RTT=RTT_in
[5202]349    RV=RV_in
[4535]350    RVTMP2=RVTMP2_in
[4818]351    RPI=RPI_in
[4951]352    EPS_W=EPS_W_in
[4535]353
354
355
[4559]356    CALL getin_p('niter_lscp',niter_lscp)
[4380]357    CALL getin_p('iflag_evap_prec',iflag_evap_prec)
358    CALL getin_p('seuil_neb',seuil_neb)
[4420]359    CALL getin_p('ok_radocond_snow',ok_radocond_snow)
[4535]360    CALL getin_p('t_glace_max',t_glace_max)
361    CALL getin_p('t_glace_min',t_glace_min)
362    CALL getin_p('exposant_glace',exposant_glace)
363    CALL getin_p('iflag_vice',iflag_vice)
364    CALL getin_p('iflag_t_glace',iflag_t_glace)
365    CALL getin_p('iflag_cloudth_vert',iflag_cloudth_vert)
366    CALL getin_p('iflag_gammasat',iflag_gammasat)
367    CALL getin_p('iflag_rain_incloud_vol',iflag_rain_incloud_vol)
368    CALL getin_p('iflag_bergeron',iflag_bergeron)
369    CALL getin_p('iflag_fisrtilp_qsat',iflag_fisrtilp_qsat)
370    CALL getin_p('iflag_pdf',iflag_pdf)
[5202]371    CALL getin_p('iflag_icefrac',iflag_icefrac)
[4535]372    CALL getin_p('reevap_ice',reevap_ice)
373    CALL getin_p('cld_lc_lsc',cld_lc_lsc)
374    CALL getin_p('cld_lc_con',cld_lc_con)
[4830]375    CALL getin_p('cld_lc_lsc_snow',cld_lc_lsc_snow)
376    CALL getin_p('cld_lc_con_snow',cld_lc_con_snow)
[4535]377    CALL getin_p('cld_tau_lsc',cld_tau_lsc)
378    CALL getin_p('cld_tau_con',cld_tau_con)
[4559]379    CALL getin_p('cld_expo_lsc',cld_expo_lsc)
380    CALL getin_p('cld_expo_con',cld_expo_con)
[4535]381    CALL getin_p('ffallv_lsc',ffallv_lsc)
382    CALL getin_p('ffallv_lsc',ffallv_con)
383    CALL getin_p('coef_eva',coef_eva)
[4830]384    coef_sub=coef_eva
385    CALL getin_p('coef_eva_i',coef_sub)
386    CALL getin_p('coef_sub',coef_sub)
[4803]387    CALL getin_p('expo_eva',expo_eva)
[4830]388    expo_sub=expo_eva
389    CALL getin_p('expo_sub',expo_sub)
[4559]390    CALL getin_p('iflag_autoconversion',iflag_autoconversion)
[4562]391    CALL getin_p('dist_liq',dist_liq)
392    CALL getin_p('tresh_cl',tresh_cl)
[5202]393    CALL getin_p('tau_mixenv',tau_mixenv)
394    CALL getin_p('capa_crystal',capa_crystal)
395    CALL getin_p('lmix_mpc',lmix_mpc)
396    CALL getin_p('naero5',naero5)
397    CALL getin_p('gamma_snwretro',gamma_snwretro)
398    CALL getin_p('gamma_taud',gamma_taud)
[4666]399    CALL getin_p('iflag_oldbug_fisrtilp',iflag_oldbug_fisrtilp)
[5019]400    CALL getin_p('temp_nowater',temp_nowater)
[4951]401    ! for poprecip
[4803]402    CALL getin_p('ok_poprecip',ok_poprecip)
[4913]403    CALL getin_p('ok_corr_vap_evasub',ok_corr_vap_evasub)
[4803]404    CALL getin_p('rain_int_min',rain_int_min)
405    CALL getin_p('gamma_agg',gamma_agg)
406    CALL getin_p('gamma_col',gamma_col)
[4818]407    CALL getin_p('gamma_rim',gamma_rim)
[4830]408    CALL getin_p('gamma_freez',gamma_freez)
[4895]409    CALL getin_p('gamma_melt',gamma_melt)
[4830]410    CALL getin_p('r_snow',r_snow)
411    CALL getin_p('rain_fallspeed',rain_fallspeed)
412    rain_fallspeed_clr=rain_fallspeed
413    rain_fallspeed_cld=rain_fallspeed
414    CALL getin_p('rain_fallspeed_clr',rain_fallspeed_clr)
415    CALL getin_p('rain_fallspeed_cld',rain_fallspeed_cld)
416    CALL getin_p('snow_fallspeed',snow_fallspeed)
417    snow_fallspeed_clr=snow_fallspeed
418    snow_fallspeed_cld=snow_fallspeed
419    CALL getin_p('snow_fallspeed_clr',snow_fallspeed_clr)
420    CALL getin_p('snow_fallspeed_cld',snow_fallspeed_cld)
[4951]421    ! for condensation and ice supersaturation
422    CALL getin_p('ok_external_lognormal',ok_external_lognormal)
423    CALL getin_p('ok_unadjusted_clouds',ok_unadjusted_clouds)
424    CALL getin_p('ok_weibull_warm_clouds',ok_weibull_warm_clouds)
425    CALL getin_p('iflag_cloud_sublim_pdf',iflag_cloud_sublim_pdf)
[5165]426    CALL getin_p('depo_coef_cirrus',depo_coef_cirrus)
[5041]427    CALL getin_p('capa_cond_cirrus',capa_cond_cirrus)
[4951]428    CALL getin_p('mu_subl_pdf_lscp',mu_subl_pdf_lscp)
429    CALL getin_p('beta_pdf_lscp',beta_pdf_lscp)
430    CALL getin_p('temp_thresh_pdf_lscp',temp_thresh_pdf_lscp)
431    CALL getin_p('rhlmid_pdf_lscp',rhlmid_pdf_lscp)
432    CALL getin_p('k0_pdf_lscp',k0_pdf_lscp)
433    CALL getin_p('kappa_pdf_lscp',kappa_pdf_lscp)
434    CALL getin_p('rhl0_pdf_lscp',rhl0_pdf_lscp)
435    CALL getin_p('cond_thresh_pdf_lscp',cond_thresh_pdf_lscp)
436    CALL getin_p('a_homofreez',a_homofreez)
437    CALL getin_p('b_homofreez',b_homofreez)
438    CALL getin_p('delta_hetfreez',delta_hetfreez)
439    CALL getin_p('coef_mixing_lscp',coef_mixing_lscp)
440    CALL getin_p('coef_shear_lscp',coef_shear_lscp)
441    CALL getin_p('chi_mixing_lscp',chi_mixing_lscp)
442    !CALL getin_p('contrail_cross_section',contrail_cross_section)
[4535]443
444
445
[4666]446    WRITE(lunout,*) 'lscp_ini, niter_lscp:', niter_lscp
447    WRITE(lunout,*) 'lscp_ini, iflag_evap_prec:', iflag_evap_prec
448    WRITE(lunout,*) 'lscp_ini, seuil_neb:', seuil_neb
449    WRITE(lunout,*) 'lscp_ini, ok_radocond_snow:', ok_radocond_snow
450    WRITE(lunout,*) 'lscp_ini, t_glace_max:', t_glace_max
451    WRITE(lunout,*) 'lscp_ini, t_glace_min:', t_glace_min
452    WRITE(lunout,*) 'lscp_ini, exposant_glace:', exposant_glace
453    WRITE(lunout,*) 'lscp_ini, iflag_vice:', iflag_vice
454    WRITE(lunout,*) 'lscp_ini, iflag_t_glace:', iflag_t_glace
455    WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert:', iflag_cloudth_vert
456    WRITE(lunout,*) 'lscp_ini, iflag_gammasat:', iflag_gammasat
457    WRITE(lunout,*) 'lscp_ini, iflag_rain_incloud_vol:', iflag_rain_incloud_vol
458    WRITE(lunout,*) 'lscp_ini, iflag_bergeron:', iflag_bergeron
459    WRITE(lunout,*) 'lscp_ini, iflag_fisrtilp_qsat:', iflag_fisrtilp_qsat
460    WRITE(lunout,*) 'lscp_ini, iflag_pdf', iflag_pdf
[5202]461    WRITE(lunout,*) 'lscp_ini, iflag_icefrac', iflag_icefrac
[4666]462    WRITE(lunout,*) 'lscp_ini, reevap_ice', reevap_ice
463    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc', cld_lc_lsc
464    WRITE(lunout,*) 'lscp_ini, cld_lc_con', cld_lc_con
[4830]465    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc_snow', cld_lc_lsc_snow
466    WRITE(lunout,*) 'lscp_ini, cld_lc_con_snow', cld_lc_con_snow
[4666]467    WRITE(lunout,*) 'lscp_ini, cld_tau_lsc', cld_tau_lsc
468    WRITE(lunout,*) 'lscp_ini, cld_tau_con', cld_tau_con
469    WRITE(lunout,*) 'lscp_ini, cld_expo_lsc', cld_expo_lsc
470    WRITE(lunout,*) 'lscp_ini, cld_expo_con', cld_expo_con
471    WRITE(lunout,*) 'lscp_ini, ffallv_lsc', ffallv_lsc
472    WRITE(lunout,*) 'lscp_ini, ffallv_con', ffallv_con
473    WRITE(lunout,*) 'lscp_ini, coef_eva', coef_eva
[4830]474    WRITE(lunout,*) 'lscp_ini, coef_sub', coef_sub
[4803]475    WRITE(lunout,*) 'lscp_ini, expo_eva', expo_eva
[4830]476    WRITE(lunout,*) 'lscp_ini, expo_sub', expo_sub
[4666]477    WRITE(lunout,*) 'lscp_ini, iflag_autoconversion', iflag_autoconversion
478    WRITE(lunout,*) 'lscp_ini, dist_liq', dist_liq
479    WRITE(lunout,*) 'lscp_ini, tresh_cl', tresh_cl
[5202]480    WRITE(lunout,*) 'lscp_ini, tau_mixenv', tau_mixenv
481    WRITE(lunout,*) 'lscp_ini, capa_crystal', capa_crystal
482    WRITE(lunout,*) 'lscp_ini, lmix_mpc', lmix_mpc
483    WRITE(lunout,*) 'lscp_ini, naero5', naero5
484    WRITE(lunout,*) 'lscp_ini, gamma_snwretro', gamma_snwretro
485    WRITE(lunout,*) 'lscp_ini, gamma_taud', gamma_taud
[4666]486    WRITE(lunout,*) 'lscp_ini, iflag_oldbug_fisrtilp', iflag_oldbug_fisrtilp
487    WRITE(lunout,*) 'lscp_ini, fl_cor_ebil', fl_cor_ebil
[5019]488    WRITE(lunout,*) 'lscp_ini, temp_nowater', temp_nowater
[4951]489    ! for poprecip
[4803]490    WRITE(lunout,*) 'lscp_ini, ok_poprecip', ok_poprecip
[4913]491    WRITE(lunout,*) 'lscp_ini, ok_corr_vap_evasub', ok_corr_vap_evasub
[4803]492    WRITE(lunout,*) 'lscp_ini, rain_int_min:', rain_int_min
493    WRITE(lunout,*) 'lscp_ini, gamma_agg:', gamma_agg
494    WRITE(lunout,*) 'lscp_ini, gamma_col:', gamma_col
[4818]495    WRITE(lunout,*) 'lscp_ini, gamma_rim:', gamma_rim
[4830]496    WRITE(lunout,*) 'lscp_ini, gamma_freez:', gamma_freez
[4895]497    WRITE(lunout,*) 'lscp_ini, gamma_melt:', gamma_melt
[4830]498    WRITE(lunout,*) 'lscp_ini, r_snow:', r_snow
499    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_clr:', rain_fallspeed_clr
500    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_cld:', rain_fallspeed_cld
501    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_clr:', snow_fallspeed_clr
502    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_cld:', snow_fallspeed_cld
[4951]503    ! for condensation and ice supersaturation
504    WRITE(lunout,*) 'lscp_ini, ok_external_lognormal:', ok_external_lognormal
505    WRITE(lunout,*) 'lscp_ini, ok_ice_supersat:', ok_ice_supersat
506    WRITE(lunout,*) 'lscp_ini, ok_unadjusted_clouds:', ok_unadjusted_clouds
507    WRITE(lunout,*) 'lscp_ini, ok_weibull_warm_clouds:', ok_weibull_warm_clouds
508    WRITE(lunout,*) 'lscp_ini, iflag_cloud_sublim_pdf:', iflag_cloud_sublim_pdf
[5165]509    WRITE(lunout,*) 'lscp_ini, depo_coef_cirrus:', depo_coef_cirrus
[5041]510    WRITE(lunout,*) 'lscp_ini, capa_cond_cirrus:', capa_cond_cirrus
[4951]511    WRITE(lunout,*) 'lscp_ini, mu_subl_pdf_lscp:', mu_subl_pdf_lscp
512    WRITE(lunout,*) 'lscp_ini, beta_pdf_lscp:', beta_pdf_lscp
513    WRITE(lunout,*) 'lscp_ini, temp_thresh_pdf_lscp:', temp_thresh_pdf_lscp
514    WRITE(lunout,*) 'lscp_ini, rhlmid_pdf_lscp:', rhlmid_pdf_lscp
515    WRITE(lunout,*) 'lscp_ini, k0_pdf_lscp:', k0_pdf_lscp
516    WRITE(lunout,*) 'lscp_ini, kappa_pdf_lscp:', kappa_pdf_lscp
517    WRITE(lunout,*) 'lscp_ini, rhl0_pdf_lscp:', rhl0_pdf_lscp
518    WRITE(lunout,*) 'lscp_ini, a_homofreez:', a_homofreez
519    WRITE(lunout,*) 'lscp_ini, b_homofreez:', b_homofreez
520    WRITE(lunout,*) 'lscp_ini, delta_hetfreez', delta_hetfreez
521    WRITE(lunout,*) 'lscp_ini, coef_mixing_lscp:', coef_mixing_lscp
522    WRITE(lunout,*) 'lscp_ini, coef_shear_lscp:', coef_shear_lscp
523    WRITE(lunout,*) 'lscp_ini, chi_mixing_lscp:', chi_mixing_lscp
524!    WRITE(lunout,*) 'lscp_ini, contrail_cross_section:', contrail_cross_section
[4420]525
[4535]526
527
528
529
[4380]530    ! check for precipitation sub-time steps
[4559]531    IF (ABS(dtime/REAL(niter_lscp)-360.0).GT.0.001) THEN
[4380]532        WRITE(lunout,*) 'lscp: it is not expected, see Z.X.Li', dtime
533        WRITE(lunout,*) 'I would prefer a 6 min sub-timestep'
534    ENDIF
535
[4559]536    ! check consistency between numerical resolution of autoconversion
537    ! and other options
538   
539    IF (iflag_autoconversion .EQ. 2) THEN
540        IF ((iflag_vice .NE. 0) .OR. (niter_lscp .GT. 1)) THEN
541           abort_message = 'in lscp, iflag_autoconversion=2 requires iflag_vice=0 and niter_lscp=1'
542           CALL abort_physic (modname,abort_message,1)
543        ENDIF
544    ENDIF
[4380]545
[4559]546
[4951]547    !--Check flags for condensation and ice supersaturation
548    IF ( ok_external_lognormal .AND. ok_ice_supersat ) THEN
549      abort_message = 'in lscp, ok_external_lognormal=y is incompatible with ok_ice_supersat=y'
550      CALL abort_physic (modname,abort_message,1)
551    ENDIF
552
553    IF ( ok_weibull_warm_clouds .AND. .NOT. ok_ice_supersat ) THEN
554      abort_message = 'in lscp, ok_weibull_warm_clouds=y needs ok_ice_supersat=y'
555      CALL abort_physic (modname,abort_message,1)
556    ENDIF
557
558    IF ( ok_unadjusted_clouds .AND. .NOT. ok_ice_supersat ) THEN
559      abort_message = 'in lscp, ok_unadjusted_clouds=y needs ok_ice_supersat=y'
560      CALL abort_physic (modname,abort_message,1)
561    ENDIF
562
563
[4380]564    !AA Temporary initialisation
565    a_tr_sca(1) = -0.5
566    a_tr_sca(2) = -0.5
567    a_tr_sca(3) = -0.5
568    a_tr_sca(4) = -0.5
569   
[4651]570    CALL cloudth_ini(iflag_cloudth_vert,iflag_ratqs)
[4380]571
[4654]572RETURN
[4380]573
[4654]574END SUBROUTINE lscp_ini
575
[4664]576END MODULE lmdz_lscp_ini
Note: See TracBrowser for help on using the repository browser.