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
!!
Loading
Loading full blame...