source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/src/INCA_SRC/humgrowth.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: 9.8 KB
Line 
1!$Id: humgrowth.F90 10 2007-08-09 12:43:01Z acosce $
2!! =========================================================================
3!! INCA - INteraction with Chemistry and Aerosols
4!!
5!! Copyright Laboratoire des Sciences du Climat et de l'Environnement (LSCE)
6!!           Unite mixte CEA-CNRS-UVSQ
7!!
8!! Contributors to this INCA subroutine:
9!!
10!! Sylvia Generoso, LSCE
11!! Michael Schulz, LSCE, Michael.Schulz@cea.fr
12!! Christiane Textor, LSCE
13!! K. Haustein, IFT, Leipzig, Germany, haustein@tropos.de
14!!
15!! Anne Cozic, LSCE, anne.cozic@cea.fr
16!! Yann Meurdesoif, LSCE, yann.meurdesoif@cea.fr
17!!
18!! This software is a computer program whose purpose is to simulate the
19!! atmospheric gas phase and aerosol composition. The model is designed to be
20!! used within a transport model or a general circulation model. This version
21!! of INCA was designed to be coupled to the LMDz GCM. LMDz-INCA accounts
22!! for emissions, transport (resolved and sub-grid scale), photochemical
23!! transformations, and scavenging (dry deposition and washout) of chemical
24!! species and aerosols interactively in the GCM. Several versions of the INCA
25!! model are currently used depending on the envisaged applications with the
26!! chemistry-climate model.
27!!
28!! This software is governed by the CeCILL  license under French law and
29!! abiding by the rules of distribution of free software.  You can  use,
30!! modify and/ or redistribute the software under the terms of the CeCILL
31!! license as circulated by CEA, CNRS and INRIA at the following URL
32!! "http://www.cecill.info".
33!!
34!! As a counterpart to the access to the source code and  rights to copy,
35!! modify and redistribute granted by the license, users are provided only
36!! with a limited warranty  and the software's author,  the holder of the
37!! economic rights,  and the successive licensors  have only  limited
38!! liability.
39!!
40!! In this respect, the user's attention is drawn to the risks associated
41!! with loading,  using,  modifying and/or developing or reproducing the
42!! software by the user in light of its specific status of free software,
43!! that may mean  that it is complicated to manipulate,  and  that  also
44!! therefore means  that it is reserved for developers  and  experienced
45!! professionals having in-depth computer knowledge. Users are therefore
46!! encouraged to load and test the software's suitability as regards their
47!! requirements in conditions enabling the security of their systems and/or
48!! data to be ensured and,  more generally, to use and operate it in the
49!! same conditions as regards security.
50!!
51!! The fact that you are presently reading this means that you have had
52!! knowledge of the CeCILL license and that you accept its terms.
53!! =========================================================================
54
55#include <inca_define.h>
56
57
58#ifdef AER
59SUBROUTINE humgrowth(tr_seri,rh)                  ! rel. humudity
60
61  !     -----------------------------------------------------------------------
62  !
63  !     Purpose: Calculation of humidity growth of aerosols
64  !
65  !     Method: 
66  !
67  !     Interpolation of the coefficients between those of seasalt and rural conditions
68  !     depending on the composition of the aerosol. This approach  seems justified, because
69  !     the effect of RH on particle growth is much larger than that of the composition.
70  !
71  !     Reference:  Gerber, Atm Aerosols and Nucleation, Lect. Notes Phys, vol 309, pp237-238   
72  !                 Springer Verlag  NY 1988
73  !
74  !     Authors: Christiane Textor and Michael Schulz
75  !
76  !     Modified Sylvia Generoso and Christiane Textor 05/14/04 : addition of water mass per species
77  !
78  !      relative humidity by S. Generoso - A. Cozic
79  !      28/07/2005
80  !
81  !     -----------------------------------------------------------------------
82
83  USE SPECIES_NAMES
84  USE AEROSOL_PROGNOS, ONLY : md,mdw                   ! median diameters of tracer [m]
85  USE AEROSOL_MOD, only  : mass1index,massnindex,numberindex,nmodes,&
86       trmx,trnx,srcsigmaln,asmode,csmode,ssmode
87  USE AEROSOL_DIAG, ONLY : aerh2o,totaerh2o,spaerh2o
88  USE INCA_DIM
89  IMPLICIT NONE
90
91  REAL, INTENT(in) ::  rh(PLON,PLEV)            ! relative humidity
92  REAL, INTENT(in) ::  tr_seri(PLON,PLEV,PCNST) ! mass mixing ratio  [kg/kg]
93
94
95  ! local variables
96  REAL    :: mr(PLON,PLEV,trmx:trnx)                               ! count median radius
97  REAL, DIMENSION(PLON,PLEV) :: con1,con2,con3,con4,gro_eff,zmsum  ! auxiliaries
98  real    :: ztm1(PLON,PLEV,trmx:trnx)
99
100  REAL :: cm2mm,cm2av,cm2mmean,third
101  INTEGER :: jt,mode,m1x,mnx,nnx                            ! indexes in mode
102
103  REAL    :: rh_inter(PLON,PLEV)
104  INTEGER :: i,j
105  ! initialisations
106  mdw=md
107  mr=0.
108  totaerh2o = 0.
109  aerh2o = 0.
110  spaerh2o = 0.
111  third=1./3. 
112  gro_eff = 0.
113
114
115  ! initialisation de rh_inter
116  DO i=1,PLON
117     DO j=1,PLEV
118        IF (rh (i,j) .gt. 1) then
119           rh_inter(i,j) = 1
120        ELSE
121           rh_inter(i,j) = rh(i,j)
122        endif
123     END DO
124  END DO
125
126
127#ifndef DUSS
128  DO mode = csmode,ssmode
129
130     m1x=mass1index(mode)     ! index of first mass in mode
131     mnx=massnindex(mode)     ! index of last mass in mode
132     nnx=numberindex(mode)    ! index of number of mode
133
134     ! computation of sum of mass for each soluble mode
135     zmsum = 0.
136     ztm1(:,:,m1x:mnx)=max(tr_seri(:,:,m1x:mnx),0.)
137
138     DO j=1,PLEV
139        DO i=1,PLON
140           zmsum(i,j)=sum(ztm1(i,j,m1x:mnx))
141        ENDDO
142     ENDDO
143
144     ! comversion: count median diameter [m] -> count median radius [cm] 
145     mr(:,:,nnx)=md(:,:,nnx)*50.
146
147     ! humidity growth only if mass > 1.e-20
148     ! interpolation of coefficients
149
150
151     IF (mode .eq. asmode) THEN
152        WHERE (zmsum .gt. 1.e-20) 
153#ifdef NMHC
154           gro_eff(:,:)=(tr_seri(:,:,id_ASSSM)       & 
155                +tr_seri(:,:,id_ASSO4M)*0.5          &
156                +tr_seri(:,:,id_ASPOMM)*0.3          &
157                +tr_seri(:,:,id_ASAPp1a)*0.3         &
158                +tr_seri(:,:,id_ASAPp2a)*0.3         &
159                +tr_seri(:,:,id_ASARp1a)*0.3         &
160                +tr_seri(:,:,id_ASARp2a)*0.3         &
161                +tr_seri(:,:,id_ASBCM) *0.3)/zmsum
162#else
163           gro_eff(:,:)=(tr_seri(:,:,id_ASSSM)       & 
164                +tr_seri(:,:,id_ASSO4M)*0.5          &
165                +tr_seri(:,:,id_ASPOMM)*0.3          &
166                +tr_seri(:,:,id_ASBCM) *0.3)/zmsum
167
168#endif
169        endwhere
170     ENDIF
171
172     IF (mode .eq. csmode) THEN
173        WHERE ((zmsum .gt. 1.e-20) .and. &
174             ((tr_seri(:,:,id_CSSSM) .gt.0) .or. (tr_seri(:,:,id_CSSO4M) .gt.0)))
175           gro_eff(:,:)=(tr_seri(:,:,id_CSSSM) &
176                +tr_seri(:,:,id_CSSO4M)*0.5)/zmsum
177        ENDWHERE
178     ENDIF
179
180     IF (mode .eq. ssmode) THEN
181        WHERE (zmsum .gt. 1.e-20) 
182           gro_eff(:,:)=1.
183        ENDWHERE
184     ENDIF
185
186     WHERE (zmsum .gt. 1.e-20) 
187        con1(:,:)=0.2789    +gro_eff(:,:)*(0.7674    -0.2789)   
188        con2(:,:)=3.1150    +gro_eff(:,:)*(3.0790    -3.1150) 
189        con3(:,:)=5.415e-11 +gro_eff(:,:)*(2.572e-11 -5.415e-11)
190        con4(:,:)=-1.399    +gro_eff(:,:)*(-1.424    +1.399)     
191
192         WHERE (mr(:,:,nnx) .NE. 0.) 
193        ! computation of wet count median diameter [m]       
194        mdw(:,:,nnx)=0.02*((con1(:,:)*mr(:,:,nnx)**con2(:,:) &
195             /(con3(:,:)*mr(:,:,nnx)**con4(:,:)-log(rh_inter(:,:))) &
196             +mr(:,:,nnx)**3)**third)
197         ELSEWHERE
198             mdw(:,:,nnx) = 0.0
199         ENDWHERE
200
201     ENDWHERE
202
203     ! conversion: wet count median diameter -> wet mass median diameter
204     cm2mm=exp(3.*srcsigmaln(mode)**2)
205     do jt=m1x,mnx
206        mdw(:,:,jt)=mdw(:,:,nnx)*cm2mm
207     enddo
208
209     ! conversion factor wet count median diameter -> wet diameter of average mass
210     cm2av=exp(1.5*srcsigmaln(mode)**2)
211
212     ! aerosol water mass = pi/6*rho_water*(dwav**3-dav**3)*number_mixing_ratio  -> [kg H20/ kg air]
213     aerh2o(:,:,mode)=523.598775 &
214          *((mdw(:,:,nnx)*cm2av)**3-(md(:,:,nnx)*cm2av)**3) &
215          *tr_seri(:,:,nnx) 
216
217     totaerh2o(:,:)=totaerh2o(:,:)+aerh2o(:,:,mode)
218
219
220     ! aerosol water mass per species. Distibution per species follows the same weights as for gro_eff
221     IF (mode .eq. asmode) THEN
222        WHERE ((zmsum .gt. 1.e-20)  .and. (gro_eff .gt. 1.e-20)) 
223           spaerh2o(:,:,id_ASSSM) = tr_seri(:,:,id_ASSSM)*1./(zmsum(:,:)*gro_eff(:,:)) &
224                *aerh2o(:,:,mode)
225           spaerh2o(:,:,id_ASSO4M)= tr_seri(:,:,id_ASSO4M)*0.5/(zmsum(:,:)*gro_eff(:,:)) &
226                *aerh2o(:,:,mode)
227           spaerh2o(:,:,id_ASPOMM)= tr_seri(:,:,id_ASPOMM)*0.3/(zmsum(:,:)*gro_eff(:,:)) &
228                *aerh2o(:,:,mode)
229#ifdef NMHC
230           spaerh2o(:,:,id_ASAPp1a)= tr_seri(:,:,id_ASAPp1a)*0.3/(zmsum(:,:)*gro_eff(:,:))&
231                *aerh2o(:,:,mode)
232           spaerh2o(:,:,id_ASAPp2a)= tr_seri(:,:,id_ASAPp2a)*0.3/(zmsum(:,:)*gro_eff(:,:))&
233                *aerh2o(:,:,mode)
234           spaerh2o(:,:,id_ASARp1a)= tr_seri(:,:,id_ASARp1a)*0.3/(zmsum(:,:)*gro_eff(:,:))&
235                *aerh2o(:,:,mode)
236           spaerh2o(:,:,id_ASARp2a)= tr_seri(:,:,id_ASARp2a)*0.3/(zmsum(:,:)*gro_eff(:,:))&
237                *aerh2o(:,:,mode)
238#endif
239           spaerh2o(:,:,id_ASBCM) = tr_seri(:,:,id_ASBCM)*0.3/(zmsum(:,:)*gro_eff(:,:)) &
240                *aerh2o(:,:,mode)         
241        endwhere
242     ENDIF
243
244     IF (mode .eq. csmode) THEN
245        WHERE ((zmsum .gt. 1.e-20) .and. (gro_eff .gt. 1.e-20))
246
247           spaerh2o(:,:,id_CSSSM) = tr_seri(:,:,id_cSSSM)*1./(zmsum(:,:)*gro_eff(:,:)) &
248                *aerh2o(:,:,mode)
249           spaerh2o(:,:,id_CSSO4M)= tr_seri(:,:,id_cSSO4M)*0.5/(zmsum(:,:)*gro_eff(:,:)) &
250                *aerh2o(:,:,mode)
251        ENDWHERE
252     ENDIF
253
254     IF (mode .eq. ssmode) THEN
255        WHERE ((zmsum .gt. 1.e-20) .and. (gro_eff .gt. 1.e-20))
256           spaerh2o(:,:,id_SSSSM) = tr_seri(:,:,id_SSSSM)*1./(zmsum(:,:)*gro_eff(:,:)) &
257                *aerh2o(:,:,mode)
258        ENDWHERE
259     ENDIF
260
261  ENDDO
262#endif
263END SUBROUTINE humgrowth
264#endif
Note: See TracBrowser for help on using the repository browser.