Newer
Older

RODIER Quentin
committed
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
!MNH_LIC Copyright 1994-2021 CNRS, Meteo-France and Universite Paul Sabatier
!MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1.
!-----------------------------------------------------------------
! ##########################
MODULE MODI_RESOLVED_CLOUD
! ##########################
INTERFACE
SUBROUTINE RESOLVED_CLOUD ( HCLOUD, HACTCCN, HSCONV, HMF_CLOUD, &
KRR, KSPLITR, KSPLITG, KMI, KTCOUNT, &
HLBCX, HLBCY, TPFILE, HRAD, HTURBDIM, &
OSUBG_COND, OSIGMAS, HSUBG_AUCV, &
PTSTEP, PZZ, PRHODJ, PRHODREF, PEXNREF, &
PPABST, PTHT, PRT, PSIGS, PSIGQSAT, PMFCONV, &
PTHM, PRCM, PPABSM, &
PW_ACT,PDTHRAD, PTHS, PRS, PSVT, PSVS, PSRCS, PCLDFR,&
PCIT, OSEDIC, OACTIT, OSEDC, OSEDI, &
ORAIN, OWARM, OHHONI, OCONVHG, &
PCF_MF,PRC_MF, PRI_MF, &
PINPRC,PINPRC3D,PINPRR,PINPRR3D, PEVAP3D, &
PINPRS,PINPRS3D,PINPRG,PINPRG3D,PINPRH,PINPRH3D, &
PSOLORG,PMI, &
PSPEEDC, PSPEEDR, PSPEEDS, PSPEEDG, PSPEEDH, &
PINDEP, PSUPSAT, PNACT, PNPRO,PSSPRO, PRAINFR, &
PHLC_HRC, PHLC_HCF, PHLI_HRI, PHLI_HCF, &
PSEA,PTOWN )
!
USE MODD_IO, ONLY: TFILEDATA
!
CHARACTER(LEN=4), INTENT(IN) :: HCLOUD ! kind of cloud
CHARACTER(LEN=4), INTENT(IN) :: HACTCCN ! kind of CCN activation scheme
! paramerization
CHARACTER(LEN=4), INTENT(IN) :: HSCONV ! Shallow convection scheme
CHARACTER(LEN=4), INTENT(IN) :: HMF_CLOUD! Type of statistical cloud
INTEGER, INTENT(IN) :: KRR ! Number of moist variables
INTEGER, INTENT(IN) :: KSPLITR ! Number of small time step
! integrations for rain sedimendation
INTEGER, INTENT(IN) :: KSPLITG ! Number of small time step
! integrations for ice sedimendation
INTEGER, INTENT(IN) :: KMI ! Model index
INTEGER, INTENT(IN) :: KTCOUNT ! Temporal loop counter
CHARACTER(LEN=4), DIMENSION(2), INTENT(IN) :: HLBCX,HLBCY ! X and Y-direc. LBC type
TYPE(TFILEDATA), INTENT(IN) :: TPFILE ! Output file
CHARACTER(len=4), INTENT(IN) :: HRAD ! Radiation scheme name
CHARACTER(len=4), INTENT(IN) :: HTURBDIM ! Dimensionality of the
! turbulence scheme
LOGICAL, INTENT(IN) :: OSUBG_COND ! Switch for Subgrid Cond.
LOGICAL, INTENT(IN) :: OSIGMAS ! Switch for Sigma_s:
! use values computed in CONDENSATION
! or that from turbulence scheme
CHARACTER(LEN=4), INTENT(IN) :: HSUBG_AUCV
! Kind of Subgrid autoconversion method
REAL, INTENT(IN) :: PTSTEP ! Time step :XTSTEP in namelist
!
!
REAL, DIMENSION(:,:,:), INTENT(IN) :: PZZ ! Height (z)
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRHODJ !Dry density * Jacobian
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRHODREF! Reference dry air density
REAL, DIMENSION(:,:,:), INTENT(IN) :: PEXNREF ! Reference Exner function
!
!
REAL, DIMENSION(:,:,:), INTENT(IN) :: PPABST ! abs. pressure at time t
REAL, DIMENSION(:,:,:), INTENT(IN) :: PTHT ! Theta at time t
REAL, DIMENSION(:,:,:,:), INTENT(INOUT):: PRT ! Moist variables at time t
REAL, DIMENSION(:,:,:), INTENT(IN) :: PSIGS ! Sigma_s at time t
REAL, INTENT(IN) :: PSIGQSAT! coeff applied to qsat variance contribution
REAL, DIMENSION(:,:,:), INTENT(IN) :: PMFCONV ! convective mass flux
REAL, DIMENSION(:,:,:), INTENT(IN) :: PTHM ! Theta at time t-Dt
REAL, DIMENSION(:,:,:), INTENT(IN) :: PPABSM ! Pressure time t-Dt
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRCM ! Cloud water m.r. at time t-Dt
!
!
REAL, DIMENSION(:,:,:), INTENT(IN) :: PW_ACT ! W for CCN activation
REAL, DIMENSION(:,:,:), INTENT(IN) :: PDTHRAD! THeta RADiative Tendancy
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PTHS ! Theta source
REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS ! Moist variable sources
REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVT ! Scalar variable at time t
REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS ! Scalar variable sources
!
!
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSRCS ! Second-order flux
! s'rc'/2Sigma_s2 at time t+1
! multiplied by Lambda_3
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PCLDFR! Cloud fraction
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PCIT ! Pristine ice number
! concentration at time t
LOGICAL, INTENT(IN) :: OSEDIC! Switch to activate the
! cloud droplet sedimentation
! for ICE3
LOGICAL, INTENT(IN) :: OACTIT ! Switch to activate the
! activation through temp.
! evolution in C2R2 and KHKO
LOGICAL, INTENT(IN) :: OSEDC ! Switch to activate the
! cloud droplet sedimentation
! for C2R2 or KHKO
LOGICAL, INTENT(IN) :: OSEDI ! Switch to activate the
! cloud crystal sedimentation
LOGICAL, INTENT(IN) :: ORAIN ! Switch to activate the
! raindrop formation
LOGICAL, INTENT(IN) :: OWARM ! Control of the rain formation
! by slow warm microphysical
! processes
LOGICAL, INTENT(IN) :: OHHONI! enable haze freezing
LOGICAL, INTENT(IN) :: OCONVHG! Switch for conversion from
! hail to graupel
!
REAL, DIMENSION(:,:,:), INTENT(IN) :: PCF_MF! Convective Mass Flux Cloud fraction
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRC_MF! Convective Mass Flux liquid mixing ratio
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRI_MF! Convective Mass Flux solid mixing ratio
!
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINPRC ! Cloud instant precip
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINPRR ! Rain instant precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINPRR3D ! sed flux of precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PEVAP3D ! evap profile
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINPRS ! Snow instant precip
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINPRG ! Graupel instant precip
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINPRH ! Hail instant precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINPRC3D ! sed flux of precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINPRS3D ! sed flux of precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINPRG3D ! sed flux of precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINPRH3D ! sed flux of precip
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PSOLORG ![%] solubility fraction of soa
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PMI
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSPEEDC ! Cloud sedimentation speed
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSPEEDR ! Rain sedimentation speed
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSPEEDS ! Snow sedimentation speed
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSPEEDG ! Graupel sedimentation speed
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSPEEDH ! Hail sedimentation speed
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINDEP ! Cloud instant deposition
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PSUPSAT !sursat
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PNACT !concentrtaion d'aérosols activés au temps t
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PNPRO !concentrtaion d'aérosols activés au temps t
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PSSPRO !sursat
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PRAINFR ! Rain fraction
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PHLC_HRC !HighLow liquid content
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PHLC_HCF !HighLow liquid cloud fraction
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PHLI_HRI !HighLow ice content
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PHLI_HCF !HighLow ice clous fraction
REAL, DIMENSION(:,:), OPTIONAL, INTENT(IN) :: PSEA ! Land Sea mask
REAL, DIMENSION(:,:), OPTIONAL, INTENT(IN) :: PTOWN ! Town fraction
!
END SUBROUTINE RESOLVED_CLOUD
END INTERFACE
END MODULE MODI_RESOLVED_CLOUD
!
! ##########################################################################
SUBROUTINE RESOLVED_CLOUD ( HCLOUD, HACTCCN, HSCONV, HMF_CLOUD, &
KRR, KSPLITR, KSPLITG, KMI, KTCOUNT, &
HLBCX, HLBCY, TPFILE, HRAD, HTURBDIM, &
OSUBG_COND, OSIGMAS, HSUBG_AUCV, &
PTSTEP, PZZ, PRHODJ, PRHODREF, PEXNREF, &
PPABST, PTHT, PRT, PSIGS, PSIGQSAT, PMFCONV, &
PTHM, PRCM, PPABSM, &
PW_ACT,PDTHRAD, PTHS, PRS, PSVT, PSVS, PSRCS, PCLDFR,&
PCIT, OSEDIC, OACTIT, OSEDC, OSEDI, &
ORAIN, OWARM, OHHONI, OCONVHG, &
PCF_MF,PRC_MF, PRI_MF, &
PINPRC,PINPRC3D,PINPRR,PINPRR3D, PEVAP3D, &
PINPRS,PINPRS3D,PINPRG,PINPRG3D,PINPRH,PINPRH3D, &
PSOLORG,PMI, &
PSPEEDC, PSPEEDR, PSPEEDS, PSPEEDG, PSPEEDH, &
PINDEP, PSUPSAT, PNACT, PNPRO,PSSPRO, PRAINFR, &
PHLC_HRC, PHLC_HCF, PHLI_HRI, PHLI_HCF, &
PSEA,PTOWN )
! ##########################################################################
!
!!**** * - compute the resolved clouds and precipitation
!!
!! PURPOSE
!! -------
!! The purpose of this routine is to compute the microphysical sources
!! related to the resolved clouds and precipitation
!!
!!
!!** METHOD
!! ------
!! The main actions of this routine is to call the routines computing the
!! microphysical sources. Before that:
!! - it computes the real absolute pressure,
!! - negative values of the current guess of all mixing ratio are removed.
!! This is done by a global filling algorithm based on a multiplicative
!! method (Rood, 1987), in order to conserved the total mass in the
!! simulation domain.
!! - Sources are transformed in physical tendencies, by removing the
!! multiplicative term Rhod*J.
!! - External points values are filled owing to the use of cyclic
!! l.b.c., in order to performe computations on the full domain.
!! After calling to microphysical routines, the physical tendencies are
!! switched back to prognostic variables.
!!
!!
!! EXTERNAL
!! --------
!! Subroutine SLOW_TERMS: Computes the explicit microphysical sources
!! Subroutine FAST_TERMS: Performs the saturation adjustment for l
!! Subroutine RAIN_ICE : Computes the explicit microphysical sources for i
!! Subroutine ICE_ADJUST: Performs the saturation adjustment for i+l
!! MIN_ll,SUM3D_ll : distributed functions equivalent to MIN and SUM
!!

RODIER Quentin
committed
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!! Module MODD_PARAMETERS : contains declarations of parameter variables
!! JPHEXT : Horizontal external points number
!! JPVEXT : Vertical external points number
!! Module MODD_CST

RODIER Quentin
committed
!! CST%XP00 ! Reference pressure
!! CST%XRD ! Gaz constant for dry air
!! CST%XCPD ! Cpd (dry air)

RODIER Quentin
committed
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
!!
!! REFERENCE
!! ---------
!!
!! Book1 and book2 of documentation ( routine RESOLVED_CLOUD )
!!
!! AUTHOR
!! ------
!! E. Richard * Laboratoire d'Aerologie*
!!
!! MODIFICATIONS
!! -------------
!! Original 21/12/94
!! Modifications: June 8, 1995 ( J.Stein )
!! Cleaning to improve efficienty and clarity
!! in agreement with the MESO-NH coding norm
!! March 1, 1996 ( J.Stein )
!! store the cloud fraction
!! March 18, 1996 ( J.Stein )
!! check that ZMASSPOS /= 0
!! Oct. 12, 1996 ( J.Stein )
!! remove the negative values correction
!! for the KES2 case
!! Modifications: Dec 14, 1995 (J.-P. Pinty)
!! Add the mixed-phase option
!! Modifications: Jul 01, 1996 (J.-P. Pinty)
!! Change arg. list in routine FAST_TERMS
!! Modifications: Jan 27, 1997 (J.-P. Pinty)
!! add W and SV in arg. list
!! Modifications: March 23, 98 (E.Richard)
!! correction of negative value based on
!! rv+rc+ri and thetal or thetail conservation
!! Modifications: April 08, 98 (J.-P. Lafore and V. Ducrocq )
!! modify the correction of negative values
!! Modifications: June 08, 00 (J.-P. Pinty and J.-M. Cohard)
!! add the C2R2 scheme
!! Modifications: April 08, 01 (J.-P. Pinty)
!! add the C3R5 scheme
!! Modifications: July 21, 01 (J.-P. Pinty)
!! Add OHHONI and PW_ACT (for haze freezing)
!! Modifications: Sept 21, 01 (J.-P. Pinty)
!! Add XCONC_CCN limitation
!! Modifications: Nov 21, 02 (J.-P. Pinty)
!! Add ICE4 and C3R5 options
!! June, 2005 (V. Masson)
!! Technical change in interface for scalar arguments
!! Modifications : March, 2006 (O.Geoffroy)
!! Add KHKO scheme
!! Modifications : March 2013 (O.Thouron)
!! Add prognostic supersaturation
!! July, 2015 (O.Nuissier/F.Duffourg) Add microphysics diagnostic for
!! aircraft, ballon and profiler
!! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1
!! M.Mazoyer : 04/2016 : Temperature radiative tendency used for
!! activation by cooling (OACTIT)
!! Modification 01/2016 (JP Pinty) Add LIMA
!! 10/2016 M.Mazoyer New KHKO output fields
!! 10/2016 (C.Lac) Add droplet deposition
!! S.Riette : 11/2016 : ice_adjust before and after rain_ice
!! ICE3/ICE4 modified, old version under LRED=F
! P. Wautelet 05/2016-04/2018: new data structures and calls for I/O
! P. Wautelet 01/02/2019: ZRSMIN is now allocatable (instead of size of XRTMIN which was sometimes not allocated)
! C. Lac 02/2019: add rain fraction as an output field
! P. Wautelet 02/2020: use the new data structures and subroutines for budgets
! B. Vie 03/2020: LIMA negativity checks after turbulence, advection and microphysics budgets
! B. Vie 03/03/2020: use DTHRAD instead of dT/dt in Smax diagnostic computation
! P. Wautelet 11/06/2020: bugfix: correct ZSVS array indices
! P. Wautelet 11/06/2020: bugfix: add "Non local correction for precipitating species" for ICE4
! P. Wautelet + Benoit Vié 06/2020: improve removal of negative scalar variables + adapt the corresponding budgets
! P. Wautelet 23/06/2020: remove ZSVS and ZSVT to improve code readability
! P. Wautelet 30/06/2020: move removal of negative scalar variables to Sources_neg_correct
! P. Wautelet 30/06/2020: remove non-local corrections
! B. Vie 06/2020: add prognostic supersaturation for LIMA
!-------------------------------------------------------------------------------
!
!* 0. DECLARATIONS
! ------------

RODIER Quentin
committed
USE MODD_BUDGET, ONLY: TBUDGETS, TBUCONF

RODIER Quentin
committed
USE MODD_CH_AEROSOL, ONLY: LORILAM
USE MODD_DUST, ONLY: LDUST

RODIER Quentin
committed
USE MODD_CST, ONLY: CST
USE MODD_DIMPHYEX, ONLY: DIMPHYEX_t

RODIER Quentin
committed
USE MODD_DUST , ONLY: LDUST
USE MODD_IO, ONLY: TFILEDATA

RODIER Quentin
committed
USE MODD_NEB, ONLY: NEB

RODIER Quentin
committed
USE MODD_NSV, ONLY: NSV_C1R3END, NSV_C2R2BEG, NSV_C2R2END, &
NSV_LIMA_BEG, NSV_LIMA_END, NSV_LIMA_CCN_FREE, NSV_LIMA_IFN_FREE, &
NSV_LIMA_NC, NSV_LIMA_NI, NSV_LIMA_NR
USE MODD_PARAM_C2R2, ONLY: LSUPSAT
USE MODD_PARAMETERS, ONLY: JPHEXT, JPVEXT

RODIER Quentin
committed
USE MODD_PARAM_ICE, ONLY: CSEDIM, LADJ_BEFORE, LADJ_AFTER, CFRAC_ICE_ADJUST, LRED, &
PARAM_ICE

RODIER Quentin
committed
USE MODD_PARAM_LIMA, ONLY: LADJ, LCOLD, LPTSPLIT, LSPRO, NMOD_CCN, NMOD_IFN, NMOD_IMM

RODIER Quentin
committed
USE MODD_RAIN_ICE_DESCR, ONLY: XRTMIN, RAIN_ICE_DESCR

RODIER Quentin
committed
USE MODD_RAIN_ICE_PARAM, ONLY: RAIN_ICE_PARAM

RODIER Quentin
committed
USE MODD_SALT, ONLY: LSALT
USE MODD_TURB_n, ONLY: TURBN, CSUBG_AUCV_RI, CCONDENS, CLAMBDA3, CSUBG_MF_PDF

RODIER Quentin
committed
!
USE MODE_ll

RODIER Quentin
committed
USE MODE_FILL_DIMPHYEX, ONLY: FILL_DIMPHYEX

RODIER Quentin
committed
use mode_sources_neg_correct, only: Sources_neg_correct
!
USE MODI_C2R2_ADJUST
USE MODI_FAST_TERMS
USE MODI_GET_HALO
USE MODI_ICE_ADJUST
USE MODI_KHKO_NOTADJUST
USE MODI_LIMA
USE MODI_LIMA_ADJUST
USE MODI_LIMA_ADJUST_SPLIT
USE MODI_LIMA_COLD
USE MODI_LIMA_MIXED
USE MODI_LIMA_NOTADJUST
USE MODI_LIMA_WARM
USE MODI_RAIN_C2R2_KHKO

RODIER Quentin
committed
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
USE MODI_SHUMAN
USE MODI_SLOW_TERMS
!
IMPLICIT NONE
!
!* 0.1 Declarations of dummy arguments :
!
!
!
CHARACTER(LEN=4), INTENT(IN) :: HCLOUD ! kind of cloud paramerization
CHARACTER(LEN=4), INTENT(IN) :: HACTCCN ! kind of CCN activation scheme
CHARACTER(LEN=4), INTENT(IN) :: HSCONV ! Shallow convection scheme
CHARACTER(LEN=4), INTENT(IN) :: HMF_CLOUD! Type of statistical cloud
INTEGER, INTENT(IN) :: KRR ! Number of moist variables
INTEGER, INTENT(IN) :: KSPLITR ! Number of small time step
! integrations for rain sedimendation
INTEGER, INTENT(IN) :: KSPLITG ! Number of small time step
! integrations for ice sedimendation
INTEGER, INTENT(IN) :: KMI ! Model index
INTEGER, INTENT(IN) :: KTCOUNT ! Temporal loop counter
CHARACTER(LEN=4), DIMENSION(2), INTENT(IN) :: HLBCX,HLBCY ! X and Y-direc. LBC type
TYPE(TFILEDATA), INTENT(IN) :: TPFILE ! Output file
CHARACTER(len=4), INTENT(IN) :: HRAD ! Radiation scheme name
CHARACTER(len=4), INTENT(IN) :: HTURBDIM ! Dimensionality of the
! turbulence scheme
LOGICAL, INTENT(IN) :: OSUBG_COND ! Switch for Subgrid Cond.
LOGICAL, INTENT(IN) :: OSIGMAS ! Switch for Sigma_s:
! use values computed in CONDENSATION
! or that from turbulence scheme
CHARACTER(LEN=4), INTENT(IN) :: HSUBG_AUCV
! Kind of Subgrid autoconversion method
REAL, INTENT(IN) :: PTSTEP ! Time step :XTSTEP in namelist
!
!
REAL, DIMENSION(:,:,:), INTENT(IN) :: PZZ ! Height (z)
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRHODJ !Dry density * Jacobian
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRHODREF! Reference dry air density
REAL, DIMENSION(:,:,:), INTENT(IN) :: PEXNREF ! Reference Exner function
!
!
REAL, DIMENSION(:,:,:), INTENT(IN) :: PPABST ! abs. pressure at time t
REAL, DIMENSION(:,:,:), INTENT(IN) :: PTHT ! Theta at time t
REAL, DIMENSION(:,:,:,:), INTENT(INOUT):: PRT ! Moist variables at time t
REAL, DIMENSION(:,:,:), INTENT(IN) :: PSIGS ! Sigma_s at time t
REAL, INTENT(IN) :: PSIGQSAT! coeff applied to qsat variance contribution
REAL, DIMENSION(:,:,:), INTENT(IN) :: PMFCONV ! convective mass flux
REAL, DIMENSION(:,:,:), INTENT(IN) :: PTHM ! Theta at time t-Dt
REAL, DIMENSION(:,:,:), INTENT(IN) :: PPABSM ! Pressure time t-Dt
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRCM ! Cloud water m.r. at time t-Dt
!
!
REAL, DIMENSION(:,:,:), INTENT(IN) :: PW_ACT ! W for CCN activation
REAL, DIMENSION(:,:,:), INTENT(IN) :: PDTHRAD! THeta RADiative Tendancy
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PTHS ! Theta source
REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS ! Moist variable sources
REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVT ! Scalar variable at time t
REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS ! Scalar variable sources
!
!
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSRCS ! Second-order flux
! s'rc'/2Sigma_s2 at time t+1
! multiplied by Lambda_3
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PCLDFR! Cloud fraction
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PCIT ! Pristine ice number
! concentration at time t
LOGICAL, INTENT(IN) :: OSEDIC! Switch to activate the
! cloud droplet sedimentation
! for ICE3
LOGICAL, INTENT(IN) :: OACTIT ! Switch to activate the
! activation through temp.
! evolution in C2R2 and KHKO
LOGICAL, INTENT(IN) :: OSEDC ! Switch to activate the
! cloud droplet sedimentation
LOGICAL, INTENT(IN) :: OSEDI ! Switch to activate the
! cloud crystal sedimentation
LOGICAL, INTENT(IN) :: ORAIN ! Switch to activate the
! raindrop formation
LOGICAL, INTENT(IN) :: OWARM ! Control of the rain formation
! by slow warm microphysical
! processes
LOGICAL, INTENT(IN) :: OHHONI! enable haze freezing
LOGICAL, INTENT(IN) :: OCONVHG! Switch for conversion from
! hail to graupel
!
REAL, DIMENSION(:,:,:), INTENT(IN) :: PCF_MF! Convective Mass Flux Cloud fraction
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRC_MF! Convective Mass Flux liquid mixing ratio
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRI_MF! Convective Mass Flux solid mixing ratio
!
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINPRC ! Cloud instant precip
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINPRR ! Rain instant precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINPRR3D ! sed flux of precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PEVAP3D ! evap profile
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINPRS ! Snow instant precip
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINPRG ! Graupel instant precip
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINPRH ! Hail instant precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINPRC3D ! sed flux of precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINPRS3D ! sed flux of precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINPRG3D ! sed flux of precip
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PINPRH3D ! sed flux of precip
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PSOLORG ![%] solubility fraction of soa
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PMI
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSPEEDC ! Cloud sedimentation speed
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSPEEDR ! Rain sedimentation speed
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSPEEDS ! Snow sedimentation speed
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSPEEDG ! Graupel sedimentation speed
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PSPEEDH ! Hail sedimentation speed
REAL, DIMENSION(:,:), INTENT(INOUT) :: PINDEP ! Cloud instant deposition
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PSUPSAT !sursat
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PNACT !concentrtaion d'aérosols activés au temps t
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PNPRO !concentrtaion d'aérosols activés au temps t
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PSSPRO !sursat
REAL, DIMENSION(:,:,:), INTENT(OUT) :: PRAINFR ! Rain fraction
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PHLC_HRC !HighLow liquid content
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PHLC_HCF !HighLow liquid cloud fraction
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PHLI_HRI !HighLow ice content
REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PHLI_HCF !HighLow ice clous fraction
REAL, DIMENSION(:,:), OPTIONAL, INTENT(IN) :: PSEA ! Land Sea mask
REAL, DIMENSION(:,:), OPTIONAL, INTENT(IN) :: PTOWN ! Town fraction
!
!
!* 0.2 Declarations of local variables :
!
INTEGER :: JRR,JSV ! Loop index for the moist and scalar variables
INTEGER :: IIB ! Define the physical domain
INTEGER :: IIE !
INTEGER :: IJB !
INTEGER :: IJE !
INTEGER :: IKB
Loading
Loading full blame...