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

Last change on this file since 4804 was 4803, checked in by evignon, 17 months ago

implementation sous flag des premiers changements
concernant le traitement des precipitations grande echelle
dans le cadre de l'atelier nuages
Audran, Lea, Niels, Gwendal et Etienne

File size: 14.8 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
9  !$OMP THREADPRIVATE(RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG)
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_eva_i                       ! tuning coefficient ice precip sublimation
115  !$OMP THREADPRIVATE(coef_eva_i)
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_eva_i                       ! tuning coefficient ice precip sublimation
121  !$OMP THREADPRIVATE(expo_eva_i)
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 :: rain_int_min=0.001               ! Minimum local rain intensity [mm/s] before the decrease in associated precipitation fraction
140  !$OMP THREADPRIVATE(rain_int_min)
141
142  REAL, SAVE, PROTECTED :: thresh_precip_frac=1.E-6         ! precipitation fraction threshold TODO [-]
143  !$OMP THREADPRIVATE(thresh_precip_frac)
144
145  REAL, SAVE, PROTECTED :: gamma_col=1.                     ! A COMMENTER TODO [-]
146  !$OMP THREADPRIVATE(gamma_col)
147
148  REAL, SAVE, PROTECTED :: gamma_agg=1.                     ! A COMMENTER TODO [-]
149  !$OMP THREADPRIVATE(gamma_agg)
150
151  REAL, SAVE, PROTECTED :: gamma_rim=1.                     ! A COMMENTER TODO [-]
152  !$OMP THREADPRIVATE(gamma_rim)
153
154  REAL, SAVE, PROTECTED :: rho_rain=1000.                    ! A COMMENTER TODO [kg/m3]
155  !$OMP THREADPRIVATE(rho_rain)
156
157  REAL, SAVE, PROTECTED :: rho_snow=500.                   ! A COMMENTER TODO [kg/m3]
158  !$OMP THREADPRIVATE(rho_snow)
159
160  REAL, SAVE, PROTECTED :: r_rain=100.E-6                   ! A COMMENTER TODO [m]
161  !$OMP THREADPRIVATE(r_rain)
162
163  REAL, SAVE, PROTECTED :: r_snow=100.E-6                    ! A COMMENTER TODO [m]
164  !$OMP THREADPRIVATE(r_snow)
165
166  REAL, SAVE, PROTECTED :: Eff_rain_liq=1.0                  ! A COMMENTER TODO [-]
167  !$OMP THREADPRIVATE(Eff_rain_liq)
168
169  REAL, SAVE, PROTECTED :: Eff_snow_ice=0.5                ! A COMMENTER TODO [-]
170  !$OMP THREADPRIVATE(Eff_snow_ice)
171
172  REAL, SAVE, PROTECTED :: Eff_snow_liq=1.0              ! A COMMENTER TODO [-]
173  !$OMP THREADPRIVATE(Eff_snow_liq)
174
175  REAL, SAVE, PROTECTED :: tau_auto_snow_min=1800.          ! A COMMENTER TODO [s]
176  !$OMP THREADPRIVATE(tau_auto_snow_min)
177
178  REAL, SAVE, PROTECTED :: tau_auto_snow_max=7200.          ! A COMMENTER TODO [s]
179  !$OMP THREADPRIVATE(tau_auto_snow_max)
180
181  REAL, SAVE, PROTECTED :: eps=1.E-10                       ! A COMMENTER TODO [-]
182  !$OMP THREADPRIVATE(eps)
183  !--End of the parameters for poprecip
184
185! Two parameters used for lmdz_lscp_old only
186  INTEGER, SAVE, PROTECTED :: iflag_oldbug_fisrtilp=0, fl_cor_ebil
187  !$OMP THREADPRIVATE(iflag_oldbug_fisrtilp,fl_cor_ebil)
188
189CONTAINS
190
191SUBROUTINE 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, &
192                    RVTMP2_in, RTT_in,RD_in,RG_in)
193
194
195   USE ioipsl_getin_p_mod, ONLY : getin_p
196   USE ice_sursat_mod, ONLY: ice_sursat_init
197   USE lmdz_cloudth_ini, ONLY : cloudth_ini
198
199   REAL, INTENT(IN)      :: dtime
200   INTEGER, INTENT(IN)   :: lunout_in,prt_level_in,iflag_ratqs,fl_cor_ebil_in
201   LOGICAL, INTENT(IN)   :: ok_ice_sursat
202
203   REAL, INTENT(IN)      :: RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in
204   REAL, INTENT(IN)      ::  RVTMP2_in, RTT_in, RD_in, RG_in
205   character (len=20) :: modname='lscp_ini_mod'
206   character (len=80) :: abort_message
207
208
209    lunout=lunout_in
210    prt_level=prt_level_in
211    fl_cor_ebil=fl_cor_ebil_in
212
213    RG=RG_in
214    RD=RD_in
215    RCPD=RCPD_in
216    RLVTT=RLVTT_in
217    RLSTT=RLSTT_in
218    RLMLT=RLMLT_in
219    RTT=RTT_in
220    RG=RG_in
221    RVTMP2=RVTMP2_in
222
223
224
225    CALL getin_p('niter_lscp',niter_lscp)
226    CALL getin_p('iflag_evap_prec',iflag_evap_prec)
227    CALL getin_p('seuil_neb',seuil_neb)
228    CALL getin_p('iflag_mpc_bl',iflag_mpc_bl)
229    CALL getin_p('ok_radocond_snow',ok_radocond_snow)
230    CALL getin_p('t_glace_max',t_glace_max)
231    CALL getin_p('t_glace_min',t_glace_min)
232    CALL getin_p('exposant_glace',exposant_glace)
233    CALL getin_p('iflag_vice',iflag_vice)
234    CALL getin_p('iflag_t_glace',iflag_t_glace)
235    CALL getin_p('iflag_cloudth_vert',iflag_cloudth_vert)
236    CALL getin_p('iflag_gammasat',iflag_gammasat)
237    CALL getin_p('iflag_rain_incloud_vol',iflag_rain_incloud_vol)
238    CALL getin_p('iflag_bergeron',iflag_bergeron)
239    CALL getin_p('iflag_fisrtilp_qsat',iflag_fisrtilp_qsat)
240    CALL getin_p('iflag_pdf',iflag_pdf)
241    CALL getin_p('reevap_ice',reevap_ice)
242    CALL getin_p('cld_lc_lsc',cld_lc_lsc)
243    CALL getin_p('cld_lc_con',cld_lc_con)
244    CALL getin_p('cld_tau_lsc',cld_tau_lsc)
245    CALL getin_p('cld_tau_con',cld_tau_con)
246    CALL getin_p('cld_expo_lsc',cld_expo_lsc)
247    CALL getin_p('cld_expo_con',cld_expo_con)
248    CALL getin_p('ffallv_lsc',ffallv_lsc)
249    CALL getin_p('ffallv_lsc',ffallv_con)
250    CALL getin_p('coef_eva',coef_eva)
251    coef_eva_i=coef_eva
252    CALL getin_p('coef_eva_i',coef_eva_i)
253    CALL getin_p('expo_eva',expo_eva)
254    expo_eva_i=expo_eva
255    CALL getin_p('expo_eva_i',expo_eva_i)
256    CALL getin_p('iflag_autoconversion',iflag_autoconversion)
257    CALL getin_p('dist_liq',dist_liq)
258    CALL getin_p('tresh_cl',tresh_cl)
259    CALL getin_p('iflag_oldbug_fisrtilp',iflag_oldbug_fisrtilp)
260    CALL getin_p('ok_poprecip',ok_poprecip)
261    CALL getin_p('rain_int_min',rain_int_min)
262    CALL getin_p('gamma_agg',gamma_agg)
263    CALL getin_p('gamma_col',gamma_col)
264
265
266
267    WRITE(lunout,*) 'lscp_ini, niter_lscp:', niter_lscp
268    WRITE(lunout,*) 'lscp_ini, iflag_evap_prec:', iflag_evap_prec
269    WRITE(lunout,*) 'lscp_ini, seuil_neb:', seuil_neb
270    WRITE(lunout,*) 'lscp_ini, iflag_mpc_bl:', iflag_mpc_bl
271    WRITE(lunout,*) 'lscp_ini, ok_radocond_snow:', ok_radocond_snow
272    WRITE(lunout,*) 'lscp_ini, t_glace_max:', t_glace_max
273    WRITE(lunout,*) 'lscp_ini, t_glace_min:', t_glace_min
274    WRITE(lunout,*) 'lscp_ini, exposant_glace:', exposant_glace
275    WRITE(lunout,*) 'lscp_ini, iflag_vice:', iflag_vice
276    WRITE(lunout,*) 'lscp_ini, iflag_t_glace:', iflag_t_glace
277    WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert:', iflag_cloudth_vert
278    WRITE(lunout,*) 'lscp_ini, iflag_gammasat:', iflag_gammasat
279    WRITE(lunout,*) 'lscp_ini, iflag_rain_incloud_vol:', iflag_rain_incloud_vol
280    WRITE(lunout,*) 'lscp_ini, iflag_bergeron:', iflag_bergeron
281    WRITE(lunout,*) 'lscp_ini, iflag_fisrtilp_qsat:', iflag_fisrtilp_qsat
282    WRITE(lunout,*) 'lscp_ini, iflag_pdf', iflag_pdf
283    WRITE(lunout,*) 'lscp_ini, reevap_ice', reevap_ice
284    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc', cld_lc_lsc
285    WRITE(lunout,*) 'lscp_ini, cld_lc_con', cld_lc_con
286    WRITE(lunout,*) 'lscp_ini, cld_tau_lsc', cld_tau_lsc
287    WRITE(lunout,*) 'lscp_ini, cld_tau_con', cld_tau_con
288    WRITE(lunout,*) 'lscp_ini, cld_expo_lsc', cld_expo_lsc
289    WRITE(lunout,*) 'lscp_ini, cld_expo_con', cld_expo_con
290    WRITE(lunout,*) 'lscp_ini, ffallv_lsc', ffallv_lsc
291    WRITE(lunout,*) 'lscp_ini, ffallv_con', ffallv_con
292    WRITE(lunout,*) 'lscp_ini, coef_eva', coef_eva
293    WRITE(lunout,*) 'lscp_ini, coef_eva_i', coef_eva_i
294    WRITE(lunout,*) 'lscp_ini, expo_eva', expo_eva
295    WRITE(lunout,*) 'lscp_ini, expo_eva_i', expo_eva_i
296    WRITE(lunout,*) 'lscp_ini, iflag_autoconversion', iflag_autoconversion
297    WRITE(lunout,*) 'lscp_ini, dist_liq', dist_liq
298    WRITE(lunout,*) 'lscp_ini, tresh_cl', tresh_cl
299    WRITE(lunout,*) 'lscp_ini, iflag_oldbug_fisrtilp', iflag_oldbug_fisrtilp
300    WRITE(lunout,*) 'lscp_ini, fl_cor_ebil', fl_cor_ebil
301    WRITE(lunout,*) 'lscp_ini, ok_poprecip', ok_poprecip
302    WRITE(lunout,*) 'lscp_ini, rain_int_min:', rain_int_min
303    WRITE(lunout,*) 'lscp_ini, gamma_agg:', gamma_agg
304    WRITE(lunout,*) 'lscp_ini, gamma_col:', gamma_col
305
306
307
308
309
310    ! check for precipitation sub-time steps
311    IF (ABS(dtime/REAL(niter_lscp)-360.0).GT.0.001) THEN
312        WRITE(lunout,*) 'lscp: it is not expected, see Z.X.Li', dtime
313        WRITE(lunout,*) 'I would prefer a 6 min sub-timestep'
314    ENDIF
315
316    ! check consistency between numerical resolution of autoconversion
317    ! and other options
318   
319    IF (iflag_autoconversion .EQ. 2) THEN
320        IF ((iflag_vice .NE. 0) .OR. (niter_lscp .GT. 1)) THEN
321           abort_message = 'in lscp, iflag_autoconversion=2 requires iflag_vice=0 and niter_lscp=1'
322           CALL abort_physic (modname,abort_message,1)
323        ENDIF
324    ENDIF
325
326
327    ! check consistency between the use of the processes-oriented precipitation formulations
328    ! and other options
329   
330    IF (ok_poprecip) THEN
331        IF ((iflag_evap_prec .LT. 4) .OR. (niter_lscp .GT. 1)) THEN
332           abort_message = 'in lscp, ok_poprecip=y requires iflag_evap_prec >= 4 and niter_lscp=1'
333           CALL abort_physic (modname,abort_message,1)
334        ENDIF
335    ENDIF
336
337
338    !AA Temporary initialisation
339    a_tr_sca(1) = -0.5
340    a_tr_sca(2) = -0.5
341    a_tr_sca(3) = -0.5
342    a_tr_sca(4) = -0.5
343   
344    IF (ok_ice_sursat) CALL ice_sursat_init()
345
346    CALL cloudth_ini(iflag_cloudth_vert,iflag_ratqs)
347
348RETURN
349
350END SUBROUTINE lscp_ini
351
352END MODULE lmdz_lscp_ini
Note: See TracBrowser for help on using the repository browser.