source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_SRC/sethet.f90 @ 6610

Last change on this file since 6610 was 6610, checked in by acosce, 10 months ago

INCA used for ICOLMDZORINCA_CO2_Transport_GMD_2023

File size: 8.7 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: sethet.F90 112 2009-01-28 16:40:56Z acosce $
13!! =========================================================================
14!! INCA - INteraction with Chemistry and Aerosols
15!!
16!! Copyright Laboratoire des Sciences du Climat et de l'Environnement (LSCE)
17!!           Unite mixte CEA-CNRS-UVSQ
18!!
19!! Contributors to this INCA subroutine:
20!!
21!! Didier Hauglustaine, LSCE, hauglustaine@cea.fr
22!! Xue-Xi Tie, NCAR
23!!
24!! Anne Cozic, LSCE, anne.cozic@cea.fr
25!! Yann Meurdesoif, LSCE, yann.meurdesoif@cea.fr
26!!
27!! This software is a computer program whose purpose is to simulate the
28!! atmospheric gas phase and aerosol composition. The model is designed to be
29!! used within a transport model or a general circulation model. This version
30!! of INCA was designed to be coupled to the LMDz GCM. LMDz-INCA accounts
31!! for emissions, transport (resolved and sub-grid scale), photochemical
32!! transformations, and scavenging (dry deposition and washout) of chemical
33!! species and aerosols interactively in the GCM. Several versions of the INCA
34!! model are currently used depending on the envisaged applications with the
35!! chemistry-climate model.
36!!
37!! This software is governed by the CeCILL  license under French law and
38!! abiding by the rules of distribution of free software.  You can  use,
39!! modify and/ or redistribute the software under the terms of the CeCILL
40!! license as circulated by CEA, CNRS and INRIA at the following URL
41!! "http://www.cecill.info".
42!!
43!! As a counterpart to the access to the source code and  rights to copy,
44!! modify and redistribute granted by the license, users are provided only
45!! with a limited warranty  and the software's author,  the holder of the
46!! economic rights,  and the successive licensors  have only  limited
47!! liability.
48!!
49!! In this respect, the user's attention is drawn to the risks associated
50!! with loading,  using,  modifying and/or developing or reproducing the
51!! software by the user in light of its specific status of free software,
52!! that may mean  that it is complicated to manipulate,  and  that  also
53!! therefore means  that it is reserved for developers  and  experienced
54!! professionals having in-depth computer knowledge. Users are therefore
55!! encouraged to load and test the software's suitability as regards their
56!! requirements in conditions enabling the security of their systems and/or
57!! data to be ensured and,  more generally, to use and operate it in the
58!! same conditions as regards security.
59!!
60!! The fact that you are presently reading this means that you have had
61!! knowledge of the CeCILL license and that you accept its terms.
62!! =========================================================================
63
64
65
66SUBROUTINE SETHET( &
67   het_rates   , &
68   press       , &
69   pdel        , &
70   lat         , &
71   zmid        , &
72   tfld        , &
73   delt        , &
74   xhnm        , &
75   flxr        , &
76   flxs        , &
77   flxupd      , &
78   cldtop      , &
79   cldbot      , &
80   cldfr       , &
81   index       , &
82   qin )
83  !-----------------------------------------------------------------------     
84  !   ... In-cloud and below-cloud scavenging of soluble species.
85  ! Xue-Xi Tie, NCAR, 1998.
86  ! Didier Hauglustaine, IPSL, 2001.
87  ! Didier Hauglustaine, IPSL, 05-2002.
88  !-----------------------------------------------------------------------     
89
90  USE CHEM_CONS,     ONLY : gravit, uma
91  USE SPECIES_NAMES
92
93
94
95  USE INCA_DIM
96  USE CHEM_MODS, ONLY : invariants
97  USE DRYDEP_PARAMETERS, ONLY : ndep
98  USE INPUT_DATA_TABLES, ONLY : spec_map
99  USE RATE_INDEX_MOD
100
101  IMPLICIT NONE
102
103  !-----------------------------------------------------------------------     
104  !       ... Dummy arguments
105  !-----------------------------------------------------------------------     
106  INTEGER, INTENT(in)  ::    lat  ! latitude index
107  INTEGER, INTENT(in)  ::    INDEX   ! index = 1 for stratiform clouds
108                                     ! index = 2 for convective clouds 
109  INTEGER, INTENT(in)  ::    cldtop(PLON)  ! cloud top level ( 1 ... 19 )
110  !gaf  cloud bottom is included: cldbot
111  INTEGER, INTENT(in)  ::    cldbot(PLON)  ! cloud bot level ( 1 ... 19 )
112  REAL, INTENT(in)     ::    delt          ! time step ( s )
113  REAL, INTENT(in)     ::    press(PLON,PLEV)     ! midpoint pressure Pa
114  REAL, INTENT(in)     ::    pdel(PLON,PLEV)      ! delta pressure (Pa)
115  REAL, INTENT(in)     ::    qin(PLON,PLEV,8) ! xported species (vmr)
116  REAL, INTENT(in)     ::    zmid(PLON,PLEV)      ! midpoint geopot
117  REAL, INTENT(in)     ::    tfld(PLON,PLEV)      ! temperature
118  REAL, INTENT(in)     ::    xhnm(PLON,PLEV)      ! total density (/cm**3)
119  REAL, INTENT(inout)  ::    het_rates(PLON,PLEV,1)  ! rainout loss rates
120  REAL, INTENT(inout)  ::    flxr(PLON,PLEVP)     !liquid water flx kgH2O/m2/s
121  REAL, INTENT(inout)  ::    flxs(PLON,PLEVP)     !solid  water flx kgH2O/m2/s
122  REAL, INTENT(in)     ::    flxupd(PLON,PLEV)    !entrainment  flx kgAIR/m2/s
123  REAL, INTENT(in)     ::    cldfr(PLON,PLEV)     !cloud fraction
124
125  !-----------------------------------------------------------------------     
126  !       ... Local variables
127  !-----------------------------------------------------------------------     
128  REAL, PARAMETER ::  RD = 287.04  ! ideal gas constant/molarmass of air J/molkg
129  REAL, PARAMETER ::  drym = 28.966
130  REAL, PARAMETER ::  Rg    = 8.205e-2           ! atm cm3/K/M/g
131  !     ... The following numbers are criticial and should be calculated
132  !     instead of fixed. A size distribution should be used for
133  !     rain drops based on the rain intensity (Seinfeld and Pandis, P. 831).
134  !     Then the terminal velocity could be calculated as well (Seinfeild
135  !     and Pandis, P. 468). See also Roelofs and Lelieveld (1995).
136  !     This will be done in a future version. For now we use typical numbers
137  !     provided in Brasseur et al. (1988). --DH, 2001
138
139!DH 11/2011 These variables updated based on Seinfeld and Pandis.
140  REAL, PARAMETER ::  xrm  = 0.100
141  REAL, PARAMETER ::  xum  = 300.
142
143  REAL, PARAMETER ::  xvv  = 0.146
144  REAL, PARAMETER ::  xdg  = 0.112
145
146  !     Here as well, we need something better for LWC.
147  REAL, DIMENSION(2) ::  lwc  = (/ .5   , 2.    /)
148  INTEGER    ::      i, k, ktrop, kk
149  REAL       ::      cst, alpha, dz
150  REAL, SAVE ::      xkgm
151  INTEGER, SAVE :: index_NH3
152  INTEGER, SAVE :: index_APp1g, index_APp2g, index_ARp1g, index_ARp2g
153!$OMP THREADPRIVATE(xkgm, index_NH3, index_APp1g, index_APp2g, index_ARp1g, index_ARp2g)
154  REAL       ::      all1, all2, stay
155  REAL       ::      xeqca1, xeqca2, xca1, xca2, xdtm
156  REAL       ::      xxx1, xxx2, yhno3, yh2o2
157  REAL, DIMENSION(PLON)  :: xk0, xk1, xk2, work1, work2
158  REAL, DIMENSION(PLON)  :: hplus_inv
159  REAL, DIMENSION(PLEV)  :: xgas1, xgas2
160  REAL, DIMENSION(PLON,PLEV) :: delz, xhno3, xh2o2, xliq, wh2o
161  REAL, DIMENSION(PLON,PLEV) :: xhenhno3   ! henry constants
162  REAL, DIMENSION(PLON,PLEV) :: xhenh2o2 
163
164  !-----------------------------------------------------------------------
165  !       ... effective Henry's Law Constants
166  !-----------------------------------------------------------------------
167  !     effective Henry's Law Constants are used for 19 species only
168  !     they are (in that order):
169  !     HNO3, H2O2, HNO2, HNO4, CH3OOH, CH3OH, CH2O, C2H5OH, CH3CHO,
170  !     CH3COOH, CH3COOOH, CH3COCHO, CH3COCH3, C2H5OOH, MVK, MEK,
171  !     PAN, ONITR, ONITU
172  !     the mapping garanties the correct hand over
173  INTEGER, PARAMETER :: n_effhetrxt = 19
174  INTEGER, PARAMETER :: n_hetrxt = 1-1
175  INTEGER, DIMENSION(n_effhetrxt), SAVE :: mapping1, mapping2
176! mapping1 permet de retrouver les variables avec constantes d'henry listees ci-dessus
177!          dans la liste ndep des variables pour lesquelles on a calcule heff_3D (mkdvel)
178! mapping2 permet de mettre les variables heterogene dans l'ordre que l'on veut
179!          dans le fichier inca***.def. Nous ne sommes plus contraint d'avoir hno3
180!          en premier et pb210 en dernier. Ni d'avoir en premier les especes de la liste ci-dessus
181
182  INTEGER, DIMENSION(n_effhetrxt), SAVE :: het_map
183!$OMP THREADPRIVATE(mapping1,mapping2, het_map)
184  !     field containing all effective Henry's Law constants
185  !     first entry always has to by HNO3
186  !     last slot reserved for Pb210
187  REAL, DIMENSION(PLON,PLEV,1) :: xhenconst
188
189
190  REAL, DIMENSION(PLON,PLEV) :: wrate
191  REAL, DIMENSION(PLON,PLEV) :: zrho
192  REAL, DIMENSION(PLON,PLEV) :: totmass
193  REAL, DIMENSION(PLON,PLEV) :: massupd
194  REAL, DIMENSION(PLON,PLEV) :: flxdwn
195  REAL, DIMENSION(PLON,PLEV) :: scaveff
196
197  LOGICAL, SAVE :: entered = .FALSE.
198!$OMP THREADPRIVATE(entered)
199
200  !--------------------------------------------------
201  ! VERSION AER calcul des constantes d'henry
202  ! et het_rate = 0
203  !--------------------------------------------------
204
205  ! changed for AERONLY MS July 07, AER needs to remove SO2, see aeronly section at end
206  het_rates(:,:,:) = 0.
207END SUBROUTINE SETHET
Note: See TracBrowser for help on using the repository browser.