source: LMDZ6/trunk/libf/phylmd/lmdz_lscp_ini.F90 @ 4830

Last change on this file since 4830 was 4830, checked in by evignon, 3 months ago

changements suite à l'atelier nuage d'aujourd'hui.

File size: 17.6 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, RG, RPI
9  !$OMP THREADPRIVATE(RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG, RPI)
10
11  REAL, SAVE, PROTECTED :: seuil_neb=0.001      ! cloud fraction threshold: a cloud really exists when exceeded
12  !$OMP THREADPRIVATE(seuil_neb)
13
14  INTEGER, SAVE :: lunout, prt_level            ! Logical unit number and level for standard output
15  !$OMP THREADPRIVATE(lunout,prt_level)
16
17  INTEGER, SAVE, PROTECTED :: niter_lscp=5      ! number of iterations to calculate autoconversion to precipitation
18  !$OMP THREADPRIVATE(niter_lscp)
19
20  INTEGER, SAVE, PROTECTED :: iflag_evap_prec=1 ! precipitation evaporation flag. 0: nothing, 1: "old way",
21                                                ! 2: Max cloud fraction above to calculate the max of reevaporation
22                                                ! >=4: LTP'method i.e. evaporation in the clear-sky fraction of the mesh only
23                                                ! pay attention that iflag_evap_prec=4 may lead to unrealistic and overestimated
24                                                ! evaporation. Use 5 instead
25  !$OMP THREADPRIVATE(iflag_evap_prec)
26
27  REAL, SAVE, PROTECTED :: t_coup=234.0         ! temperature threshold which determines the phase
28                                                ! for which the saturation vapor pressure is calculated
29  !$OMP THREADPRIVATE(t_coup)
30  REAL, SAVE, PROTECTED :: DDT0=0.01            ! iteration parameter
31  !$OMP THREADPRIVATE(DDT0)
32
33  REAL, SAVE, PROTECTED :: ztfondue=278.15      ! parameter to calculate melting fraction of precipitation
34  !$OMP THREADPRIVATE(ztfondue)
35
36  REAL, SAVE, PROTECTED :: temp_nowater=233.15  ! temperature below which liquid water no longer exists
37  !$OMP THREADPRIVATE(temp_nowater)
38
39  REAL, SAVE, PROTECTED :: a_tr_sca(4)          ! Variables for tracers temporary: alpha parameter for scavenging, 4 possible scavenging processes
40  !$OMP THREADPRIVATE(a_tr_sca)
41 
42  INTEGER, SAVE, PROTECTED ::  iflag_mpc_bl=0   ! flag to activate boundary layer mixed phase cloud param
43  !$OMP THREADPRIVATE(iflag_mpc_bl)
44 
45  LOGICAL, SAVE, PROTECTED :: ok_radocond_snow=.false. ! take into account the mass of ice precip in the cloud ice content seen by radiation
46  !$OMP THREADPRIVATE(ok_radocond_snow)
47
48  REAL, SAVE, PROTECTED :: t_glace_min=258.0    ! lower-bound temperature parameter for cloud phase determination
49  !$OMP THREADPRIVATE(t_glace_min)
50
51  REAL, SAVE, PROTECTED :: t_glace_max=273.15   ! upper-bound temperature parameter for cloud phase determination
52  !$OMP THREADPRIVATE(t_glace_max)
53
54  REAL, SAVE, PROTECTED :: exposant_glace=1.0   ! parameter for cloud phase determination
55  !$OMP THREADPRIVATE(exposant_glace)
56
57  INTEGER, SAVE, PROTECTED :: iflag_vice=0      ! which expression for ice crystall fall velocity
58  !$OMP THREADPRIVATE(iflag_vice)
59
60  INTEGER, SAVE, PROTECTED :: iflag_t_glace=0   ! which expression for cloud phase partitioning
61  !$OMP THREADPRIVATE(iflag_t_glace)
62
63  INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert=0         ! option for determining cloud fraction and content in convective boundary layers
64  !$OMP THREADPRIVATE(iflag_cloudth_vert)
65
66  INTEGER, SAVE, PROTECTED :: iflag_gammasat=0             ! which threshold for homogeneous nucleation below -40oC
67  !$OMP THREADPRIVATE(iflag_gammasat)
68
69  INTEGER, SAVE, PROTECTED :: iflag_rain_incloud_vol=0     ! use of volume cloud fraction for rain autoconversion
70  !$OMP THREADPRIVATE(iflag_rain_incloud_vol)
71
72  INTEGER, SAVE, PROTECTED :: iflag_bergeron=0             ! bergeron effect for liquid precipitation treatment 
73  !$OMP THREADPRIVATE(iflag_bergeron)
74
75  INTEGER, SAVE, PROTECTED :: iflag_fisrtilp_qsat=0        ! qsat adjustment (iterative) during autoconversion
76  !$OMP THREADPRIVATE(iflag_fisrtilp_qsat)
77
78  INTEGER, SAVE, PROTECTED :: iflag_pdf=0                  ! type of subgrid scale qtot pdf
79  !$OMP THREADPRIVATE(iflag_pdf)
80
81  INTEGER, SAVE, PROTECTED :: iflag_autoconversion=0       ! autoconversion option
82  !$OMP THREADPRIVATE(iflag_autoconversion)
83
84  LOGICAL, SAVE, PROTECTED :: reevap_ice=.false.           ! no liquid precip for T< threshold
85  !$OMP THREADPRIVATE(reevap_ice)
86
87  REAL, SAVE, PROTECTED :: cld_lc_lsc=2.6e-4               ! liquid autoconversion coefficient, stratiform rain
88  !$OMP THREADPRIVATE(cld_lc_lsc)
89
90  REAL, SAVE, PROTECTED :: cld_lc_con=2.6e-4                ! liquid autoconversion coefficient, convective rain
91  !$OMP THREADPRIVATE(cld_lc_con)
92
93  REAL, SAVE, PROTECTED :: cld_tau_lsc=3600.                ! liquid autoconversion timescale, stratiform rain
94  !$OMP THREADPRIVATE(cld_tau_lsc)
95
96  REAL, SAVE, PROTECTED :: cld_tau_con=3600.                ! liquid autoconversion timescale, convective rain
97  !$OMP THREADPRIVATE(cld_tau_con)
98
99  REAL, SAVE, PROTECTED :: cld_expo_lsc=2.                  ! liquid autoconversion threshold exponent, stratiform rain
100  !$OMP THREADPRIVATE(cld_expo_lsc)
101
102  REAL, SAVE, PROTECTED :: cld_expo_con=2.                  ! liquid autoconversion threshold exponent, convective rain
103  !$OMP THREADPRIVATE(cld_expo_con)
104
105  REAL, SAVE, PROTECTED :: ffallv_lsc=1.                    ! tuning coefficient crystal fall velocity, stratiform
106  !$OMP THREADPRIVATE(ffallv_lsc)
107
108  REAL, SAVE, PROTECTED :: ffallv_con=1.                    ! tuning coefficient crystal fall velocity, convective
109  !$OMP THREADPRIVATE(ffallv_con)
110
111  REAL, SAVE, PROTECTED :: coef_eva=2e-5                    ! tuning coefficient liquid precip evaporation
112  !$OMP THREADPRIVATE(coef_eva)
113
114  REAL, SAVE, PROTECTED :: coef_sub                        ! tuning coefficient ice precip sublimation
115  !$OMP THREADPRIVATE(coef_sub)
116
117  REAL, SAVE, PROTECTED :: expo_eva=0.5                     ! tuning coefficient liquid precip evaporation
118  !$OMP THREADPRIVATE(expo_eva)
119
120  REAL, SAVE, PROTECTED :: expo_sub                       ! tuning coefficient ice precip sublimation
121  !$OMP THREADPRIVATE(expo_sub)
122
123  REAL, SAVE, PROTECTED :: cice_velo=1.645                  ! factor in the ice fall velocity formulation
124  !$OMP THREADPRIVATE(cice_velo)
125
126  REAL, SAVE, PROTECTED ::  dice_velo=0.16                  ! exponent in the ice fall velocity formulation
127  !$OMP THREADPRIVATE(dice_velo)
128
129  REAL, SAVE, PROTECTED :: dist_liq=300.                    ! typical deph of cloud-top liquid layer in mpcs
130  !$OMP THREADPRIVATE(dist_liq)
131
132  REAL, SAVE, PROTECTED    :: tresh_cl=0.0                  ! cloud fraction threshold for cloud top search
133  !$OMP THREADPRIVATE(tresh_cl)
134
135  !--Parameters for poprecip
136  LOGICAL, SAVE, PROTECTED :: ok_poprecip=.FALSE.           ! use the processes-oriented formulation of precipitations
137  !$OMP THREADPRIVATE(ok_poprecip)
138
139  REAL, SAVE, PROTECTED :: cld_lc_lsc_snow               ! snow autoconversion coefficient, stratiform rain
140  !$OMP THREADPRIVATE(cld_lc_lsc_snow)
141
142  REAL, SAVE, PROTECTED :: cld_lc_con_snow                ! snow autoconversion coefficient, convective rain
143  !$OMP THREADPRIVATE(cld_lc_con_snow)
144
145  REAL, SAVE, PROTECTED :: rain_int_min=0.001               ! Minimum local rain intensity [mm/s] before the decrease in associated precipitation fraction
146  !$OMP THREADPRIVATE(rain_int_min)
147
148  REAL, SAVE, PROTECTED :: thresh_precip_frac=1.E-6         ! precipitation fraction threshold TODO [-]
149  !$OMP THREADPRIVATE(thresh_precip_frac)
150
151  REAL, SAVE, PROTECTED :: gamma_col=1.                     ! A COMMENTER TODO [-]
152  !$OMP THREADPRIVATE(gamma_col)
153
154  REAL, SAVE, PROTECTED :: gamma_agg=1.                     ! A COMMENTER TODO [-]
155  !$OMP THREADPRIVATE(gamma_agg)
156
157  REAL, SAVE, PROTECTED :: gamma_rim=1.                     ! A COMMENTER TODO [-]
158  !$OMP THREADPRIVATE(gamma_rim)
159
160  REAL, SAVE, PROTECTED :: rho_rain=1000.                    ! A COMMENTER TODO [kg/m3]
161  !$OMP THREADPRIVATE(rho_rain)
162
163  REAL, SAVE, PROTECTED :: rho_snow                        ! A COMMENTER TODO [kg/m3]
164  !$OMP THREADPRIVATE(rho_snow)
165
166  REAL, SAVE, PROTECTED :: r_rain=500.E-6                   ! A COMMENTER TODO [m]
167  !$OMP THREADPRIVATE(r_rain)
168
169  REAL, SAVE, PROTECTED :: r_snow=1.E-3                    ! A COMMENTER TODO [m]
170  !$OMP THREADPRIVATE(r_snow)
171
172  REAL, SAVE, PROTECTED :: tau_auto_snow_min=100.          ! A COMMENTER TODO [s]
173  !$OMP THREADPRIVATE(tau_auto_snow_min)
174
175  REAL, SAVE, PROTECTED :: tau_auto_snow_max=1000.          ! A COMMENTER TODO [s]
176  !$OMP THREADPRIVATE(tau_auto_snow_max)
177
178  REAL, SAVE, PROTECTED :: eps=1.E-10                       ! A COMMENTER TODO [-]
179  !$OMP THREADPRIVATE(eps)
180
181  REAL, SAVE, PROTECTED :: air_thermal_conduct=2.4e-2      ! A COMMENTER TODO [-]
182  !$OMP THREADPRIVATE(air_thermal_conduct)
183
184  REAL, SAVE, PROTECTED :: coef_ventil=1.                   ! A COMMENTER TODO [-]
185  !$OMP THREADPRIVATE(coef_ventil)
186
187  REAL, SAVE, PROTECTED :: alpha_freez=4.                 ! A COMMENTER TODO [-]
188  !$OMP THREADPRIVATE(alpha_freez)
189
190  REAL, SAVE, PROTECTED :: beta_freez=0.1                 ! A COMMENTER TODO [m-3.s-1]
191  !$OMP THREADPRIVATE(beta_freez)
192
193  REAL, SAVE, PROTECTED :: gamma_freez=1.                 ! A COMMENTER TODO [-]
194  !$OMP THREADPRIVATE(gamma_freez)
195
196  REAL, SAVE, PROTECTED :: rain_fallspeed=4.              ! A COMMENTER TODO [m/s]
197  !$OMP THREADPRIVATE(rain_fallspeed)
198
199  REAL, SAVE, PROTECTED :: rain_fallspeed_clr              ! A COMMENTER TODO [m/s]
200  !$OMP THREADPRIVATE(rain_fallspeed_clr)
201
202  REAL, SAVE, PROTECTED :: rain_fallspeed_cld             ! A COMMENTER TODO [m/s]
203  !$OMP THREADPRIVATE(rain_fallspeed_cld)
204
205  REAL, SAVE, PROTECTED :: snow_fallspeed=1.             ! A COMMENTER TODO [m/s]
206  !$OMP THREADPRIVATE(snow_fallspeed)
207
208  REAL, SAVE, PROTECTED :: snow_fallspeed_clr             ! A COMMENTER TODO [m/s]
209  !$OMP THREADPRIVATE(snow_fallspeed_clr)
210
211  REAL, SAVE, PROTECTED :: snow_fallspeed_cld             ! A COMMENTER TODO [m/s]
212  !$OMP THREADPRIVATE(snow_fallspeed_cld)
213  !--End of the parameters for poprecip
214
215! Two parameters used for lmdz_lscp_old only
216  INTEGER, SAVE, PROTECTED :: iflag_oldbug_fisrtilp=0, fl_cor_ebil
217  !$OMP THREADPRIVATE(iflag_oldbug_fisrtilp,fl_cor_ebil)
218
219CONTAINS
220
221SUBROUTINE lscp_ini(dtime,lunout_in,prt_level_in,ok_ice_sursat, iflag_ratqs, fl_cor_ebil_in, RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in, &
222                    RVTMP2_in, RTT_in,RD_in,RG_in,RPI_in)
223
224
225   USE ioipsl_getin_p_mod, ONLY : getin_p
226   USE ice_sursat_mod, ONLY: ice_sursat_init
227   USE lmdz_cloudth_ini, ONLY : cloudth_ini
228
229   REAL, INTENT(IN)      :: dtime
230   INTEGER, INTENT(IN)   :: lunout_in,prt_level_in,iflag_ratqs,fl_cor_ebil_in
231   LOGICAL, INTENT(IN)   :: ok_ice_sursat
232
233   REAL, INTENT(IN)      :: RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in
234   REAL, INTENT(IN)      ::  RVTMP2_in, RTT_in, RD_in, RG_in, RPI_in
235   character (len=20) :: modname='lscp_ini_mod'
236   character (len=80) :: abort_message
237
238
239    lunout=lunout_in
240    prt_level=prt_level_in
241    fl_cor_ebil=fl_cor_ebil_in
242
243    RG=RG_in
244    RD=RD_in
245    RCPD=RCPD_in
246    RLVTT=RLVTT_in
247    RLSTT=RLSTT_in
248    RLMLT=RLMLT_in
249    RTT=RTT_in
250    RG=RG_in
251    RVTMP2=RVTMP2_in
252    RPI=RPI_in
253
254
255
256    CALL getin_p('niter_lscp',niter_lscp)
257    CALL getin_p('iflag_evap_prec',iflag_evap_prec)
258    CALL getin_p('seuil_neb',seuil_neb)
259    CALL getin_p('iflag_mpc_bl',iflag_mpc_bl)
260    CALL getin_p('ok_radocond_snow',ok_radocond_snow)
261    CALL getin_p('t_glace_max',t_glace_max)
262    CALL getin_p('t_glace_min',t_glace_min)
263    CALL getin_p('exposant_glace',exposant_glace)
264    CALL getin_p('iflag_vice',iflag_vice)
265    CALL getin_p('iflag_t_glace',iflag_t_glace)
266    CALL getin_p('iflag_cloudth_vert',iflag_cloudth_vert)
267    CALL getin_p('iflag_gammasat',iflag_gammasat)
268    CALL getin_p('iflag_rain_incloud_vol',iflag_rain_incloud_vol)
269    CALL getin_p('iflag_bergeron',iflag_bergeron)
270    CALL getin_p('iflag_fisrtilp_qsat',iflag_fisrtilp_qsat)
271    CALL getin_p('iflag_pdf',iflag_pdf)
272    CALL getin_p('reevap_ice',reevap_ice)
273    CALL getin_p('cld_lc_lsc',cld_lc_lsc)
274    CALL getin_p('cld_lc_con',cld_lc_con)
275    cld_lc_lsc_snow=cld_lc_lsc
276    cld_lc_con_snow=cld_lc_con
277    CALL getin_p('cld_lc_lsc_snow',cld_lc_lsc_snow)
278    CALL getin_p('cld_lc_con_snow',cld_lc_con_snow)
279    CALL getin_p('cld_tau_lsc',cld_tau_lsc)
280    CALL getin_p('cld_tau_con',cld_tau_con)
281    CALL getin_p('cld_expo_lsc',cld_expo_lsc)
282    CALL getin_p('cld_expo_con',cld_expo_con)
283    CALL getin_p('ffallv_lsc',ffallv_lsc)
284    CALL getin_p('ffallv_lsc',ffallv_con)
285    CALL getin_p('coef_eva',coef_eva)
286    coef_sub=coef_eva
287    CALL getin_p('coef_eva_i',coef_sub)
288    CALL getin_p('coef_sub',coef_sub)
289    CALL getin_p('expo_eva',expo_eva)
290    expo_sub=expo_eva
291    CALL getin_p('expo_sub',expo_sub)
292    CALL getin_p('iflag_autoconversion',iflag_autoconversion)
293    CALL getin_p('dist_liq',dist_liq)
294    CALL getin_p('tresh_cl',tresh_cl)
295    CALL getin_p('iflag_oldbug_fisrtilp',iflag_oldbug_fisrtilp)
296    CALL getin_p('ok_poprecip',ok_poprecip)
297    CALL getin_p('rain_int_min',rain_int_min)
298    CALL getin_p('gamma_agg',gamma_agg)
299    CALL getin_p('gamma_col',gamma_col)
300    CALL getin_p('gamma_rim',gamma_rim)
301    CALL getin_p('gamma_freez',gamma_freez)
302    CALL getin_p('r_snow',r_snow)
303    CALL getin_p('rain_fallspeed',rain_fallspeed)
304    rain_fallspeed_clr=rain_fallspeed
305    rain_fallspeed_cld=rain_fallspeed
306    CALL getin_p('rain_fallspeed_clr',rain_fallspeed_clr)
307    CALL getin_p('rain_fallspeed_cld',rain_fallspeed_cld)
308    CALL getin_p('snow_fallspeed',snow_fallspeed)
309    snow_fallspeed_clr=snow_fallspeed
310    snow_fallspeed_cld=snow_fallspeed
311    CALL getin_p('snow_fallspeed_clr',snow_fallspeed_clr)
312    CALL getin_p('snow_fallspeed_cld',snow_fallspeed_cld)
313
314
315
316    WRITE(lunout,*) 'lscp_ini, niter_lscp:', niter_lscp
317    WRITE(lunout,*) 'lscp_ini, iflag_evap_prec:', iflag_evap_prec
318    WRITE(lunout,*) 'lscp_ini, seuil_neb:', seuil_neb
319    WRITE(lunout,*) 'lscp_ini, iflag_mpc_bl:', iflag_mpc_bl
320    WRITE(lunout,*) 'lscp_ini, ok_radocond_snow:', ok_radocond_snow
321    WRITE(lunout,*) 'lscp_ini, t_glace_max:', t_glace_max
322    WRITE(lunout,*) 'lscp_ini, t_glace_min:', t_glace_min
323    WRITE(lunout,*) 'lscp_ini, exposant_glace:', exposant_glace
324    WRITE(lunout,*) 'lscp_ini, iflag_vice:', iflag_vice
325    WRITE(lunout,*) 'lscp_ini, iflag_t_glace:', iflag_t_glace
326    WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert:', iflag_cloudth_vert
327    WRITE(lunout,*) 'lscp_ini, iflag_gammasat:', iflag_gammasat
328    WRITE(lunout,*) 'lscp_ini, iflag_rain_incloud_vol:', iflag_rain_incloud_vol
329    WRITE(lunout,*) 'lscp_ini, iflag_bergeron:', iflag_bergeron
330    WRITE(lunout,*) 'lscp_ini, iflag_fisrtilp_qsat:', iflag_fisrtilp_qsat
331    WRITE(lunout,*) 'lscp_ini, iflag_pdf', iflag_pdf
332    WRITE(lunout,*) 'lscp_ini, reevap_ice', reevap_ice
333    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc', cld_lc_lsc
334    WRITE(lunout,*) 'lscp_ini, cld_lc_con', cld_lc_con
335    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc_snow', cld_lc_lsc_snow
336    WRITE(lunout,*) 'lscp_ini, cld_lc_con_snow', cld_lc_con_snow
337    WRITE(lunout,*) 'lscp_ini, cld_tau_lsc', cld_tau_lsc
338    WRITE(lunout,*) 'lscp_ini, cld_tau_con', cld_tau_con
339    WRITE(lunout,*) 'lscp_ini, cld_expo_lsc', cld_expo_lsc
340    WRITE(lunout,*) 'lscp_ini, cld_expo_con', cld_expo_con
341    WRITE(lunout,*) 'lscp_ini, ffallv_lsc', ffallv_lsc
342    WRITE(lunout,*) 'lscp_ini, ffallv_con', ffallv_con
343    WRITE(lunout,*) 'lscp_ini, coef_eva', coef_eva
344    WRITE(lunout,*) 'lscp_ini, coef_sub', coef_sub
345    WRITE(lunout,*) 'lscp_ini, expo_eva', expo_eva
346    WRITE(lunout,*) 'lscp_ini, expo_sub', expo_sub
347    WRITE(lunout,*) 'lscp_ini, iflag_autoconversion', iflag_autoconversion
348    WRITE(lunout,*) 'lscp_ini, dist_liq', dist_liq
349    WRITE(lunout,*) 'lscp_ini, tresh_cl', tresh_cl
350    WRITE(lunout,*) 'lscp_ini, iflag_oldbug_fisrtilp', iflag_oldbug_fisrtilp
351    WRITE(lunout,*) 'lscp_ini, fl_cor_ebil', fl_cor_ebil
352    WRITE(lunout,*) 'lscp_ini, ok_poprecip', ok_poprecip
353    WRITE(lunout,*) 'lscp_ini, rain_int_min:', rain_int_min
354    WRITE(lunout,*) 'lscp_ini, gamma_agg:', gamma_agg
355    WRITE(lunout,*) 'lscp_ini, gamma_col:', gamma_col
356    WRITE(lunout,*) 'lscp_ini, gamma_rim:', gamma_rim
357    WRITE(lunout,*) 'lscp_ini, gamma_freez:', gamma_freez
358    WRITE(lunout,*) 'lscp_ini, r_snow:', r_snow
359    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_clr:', rain_fallspeed_clr
360    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_cld:', rain_fallspeed_cld
361    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_clr:', snow_fallspeed_clr
362    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_cld:', snow_fallspeed_cld
363
364
365
366
367
368    ! check for precipitation sub-time steps
369    IF (ABS(dtime/REAL(niter_lscp)-360.0).GT.0.001) THEN
370        WRITE(lunout,*) 'lscp: it is not expected, see Z.X.Li', dtime
371        WRITE(lunout,*) 'I would prefer a 6 min sub-timestep'
372    ENDIF
373
374    ! check consistency between numerical resolution of autoconversion
375    ! and other options
376   
377    IF (iflag_autoconversion .EQ. 2) THEN
378        IF ((iflag_vice .NE. 0) .OR. (niter_lscp .GT. 1)) THEN
379           abort_message = 'in lscp, iflag_autoconversion=2 requires iflag_vice=0 and niter_lscp=1'
380           CALL abort_physic (modname,abort_message,1)
381        ENDIF
382    ENDIF
383
384
385    ! check consistency between the use of the processes-oriented precipitation formulations
386    ! and other options
387   
388    IF (ok_poprecip) THEN
389        IF ((iflag_evap_prec .LT. 4) .OR. (niter_lscp .GT. 1)) THEN
390           abort_message = 'in lscp, ok_poprecip=y requires iflag_evap_prec >= 4 and niter_lscp=1'
391           CALL abort_physic (modname,abort_message,1)
392        ENDIF
393    ENDIF
394
395    !--Initialisations of constants depending on other constants
396    !--rho_snow formula from r_snow (Brandes et al. 2007 - JAMC)
397    rho_snow = 1.e3 * 0.178 * (r_snow * 2. * 1000.)**(-0.922)
398
399
400    !AA Temporary initialisation
401    a_tr_sca(1) = -0.5
402    a_tr_sca(2) = -0.5
403    a_tr_sca(3) = -0.5
404    a_tr_sca(4) = -0.5
405   
406    IF (ok_ice_sursat) CALL ice_sursat_init()
407
408    CALL cloudth_ini(iflag_cloudth_vert,iflag_ratqs)
409
410RETURN
411
412END SUBROUTINE lscp_ini
413
414END MODULE lmdz_lscp_ini
Note: See TracBrowser for help on using the repository browser.