source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/src/INCA_SRC/mknoprod.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: 10.5 KB
Line 
1!$Id: mknoprod.F90 157 2010-01-18 14:21:59Z 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!! Didier Hauglustaine, LSCE, hauglustaine@cea.fr
11!! Line Jourdain, SA
12!!
13!! Anne Cozic, LSCE, anne.cozic@cea.fr
14!! Yann Meurdesoif, LSCE, yann.meurdesoif@cea.fr
15!!
16!! This software is a computer program whose purpose is to simulate the
17!! atmospheric gas phase and aerosol composition. The model is designed to be
18!! used within a transport model or a general circulation model. This version
19!! of INCA was designed to be coupled to the LMDz GCM. LMDz-INCA accounts
20!! for emissions, transport (resolved and sub-grid scale), photochemical
21!! transformations, and scavenging (dry deposition and washout) of chemical
22!! species and aerosols interactively in the GCM. Several versions of the INCA
23!! model are currently used depending on the envisaged applications with the
24!! chemistry-climate model.
25!!
26!! This software is governed by the CeCILL  license under French law and
27!! abiding by the rules of distribution of free software.  You can  use,
28!! modify and/ or redistribute the software under the terms of the CeCILL
29!! license as circulated by CEA, CNRS and INRIA at the following URL
30!! "http://www.cecill.info".
31!!
32!! As a counterpart to the access to the source code and  rights to copy,
33!! modify and redistribute granted by the license, users are provided only
34!! with a limited warranty  and the software's author,  the holder of the
35!! economic rights,  and the successive licensors  have only  limited
36!! liability.
37!!
38!! In this respect, the user's attention is drawn to the risks associated
39!! with loading,  using,  modifying and/or developing or reproducing the
40!! software by the user in light of its specific status of free software,
41!! that may mean  that it is complicated to manipulate,  and  that  also
42!! therefore means  that it is reserved for developers  and  experienced
43!! professionals having in-depth computer knowledge. Users are therefore
44!! encouraged to load and test the software's suitability as regards their
45!! requirements in conditions enabling the security of their systems and/or
46!! data to be ensured and,  more generally, to use and operate it in the
47!! same conditions as regards security.
48!!
49!! The fact that you are presently reading this means that you have had
50!! knowledge of the CeCILL license and that you accept its terms.
51!! =========================================================================
52
53#include <inca_define.h>
54SUBROUTINE MKNOPROD(oro,  & 
55   lat,  &
56   lon,  &
57   area, &
58   pmid, &
59   zmid, &
60   temp, &
61   ctop, &
62   cbot, &
63   nx,   &
64   ny)
65  !----------------------------------------------------------------------
66  !     ... NOx from lightning
67  ! Line Jourdain, SA, 2001.
68  ! Modified, Didier Hauglustaine, IPSL,  08-2001.
69  !--------------------------------------------------------
70  USE LIGHTNING
71  USE CHEM_CONS
72  USE CHEM_MODS
73  USE SPECIES_NAMES
74  USE INCA_DIM
75
76  IMPLICIT NONE
77 
78  !--------------------------------------------------------
79  !       ... Dummy arguments
80  !--------------------------------------------------------
81  INTEGER, INTENT(in) :: ctop(PLON) !convective clouds top       
82  INTEGER, INTENT(in) :: cbot(PLON) !convective clouds bot
83  INTEGER, INTENT(in) :: nx, ny
84  REAL, INTENT(in)    :: oro(PLON)         !land-sea mask
85  REAL, INTENT(in)    :: area(PLON)        !Grid area (km2)
86  REAL, INTENT(in)    :: lat(PLON)         !Not used
87  REAL, INTENT(in)    :: pmid(PLON,PLEV)   !Pressure (Pa)
88  REAL, INTENT(in)    :: temp(PLON,PLEV)   !Temperature
89  REAL, INTENT(in)    :: lon(PLON)         !Not used
90  REAL, INTENT(in)    :: zmid(PLON,PLEV)   !Altitude (m)
91 
92  !--------------------------------------------------------
93  !       ... Local variables
94  !--------------------------------------------------------
95  INTEGER  :: i, k, l, lp
96  INTEGER  :: lmax, lmin
97 
98  REAL, PARAMETER :: secpyr = dayspy * 8.64e4
99  REAL, PARAMETER :: ap=0.021
100  REAL, PARAMETER :: bp=-0.648
101  REAL, PARAMETER :: cp=7.493
102  REAL, PARAMETER :: dp=-36.54
103  REAL, PARAMETER :: ep=63.09
104  REAL, PARAMETER :: zero = 1.e-20
105 
106  REAL     :: dx, dy
107  REAL     :: calibration
108  REAL     :: source
109  REAL     :: ziso0(PLON)
110  REAL     :: fic(PLON), fcg(PLON)
111  REAL     :: z(PLON)
112  REAL     :: a(PLON), b(PLON)
113  REAL     :: globoprod_no(PLON)
114  REAL     :: xprod_no(PLON,PLEV)
115  REAL     :: no_col(PLON)
116  REAL     :: factor(PLON)
117  REAL     :: scal(PLON)
118  REAL     :: altp(PLON,zdim)
119  REAL     :: atc(PLON,zdim-1), atm(PLON,zdim-1), amc(PLON,zdim-1)
120  REAL     :: btc(PLON,zdim-1), btm(PLON,zdim-1), bmc(PLON,zdim-1)
121  REAL     :: coeff_tcp(PLON,PLEV), coeff_mcp(PLON,PLEV), coeff_tmp(PLON,PLEV)
122  REAL     :: somcoeff1(PLON),somcoeff2(PLON),somcoeff3(PLON)
123  REAL     :: zinterf(PLON,PLEVP)
124  REAL     :: deltaz(PLON,PLEV)
125  REAL     :: zmidkm(PLON,PLEV)
126 
127  zmidkm = zmid*1.e-3
128
129  !     ... Zero all variables for this time-step
130  ztop=0.
131  flash=0.
132  ziso0=0.
133  dcold=0.
134  pcg=0. 
135  fcg=0.
136  fic=0.
137  globoprod_no=0.
138  xprod_no = 0.
139  factor=0. 
140  scal = 1.0
141
142  !     ... Ensure cloud presence
143  DO i=1,PLON
144    IF (pmid(i,ctop(i)) < pmid(i,cbot(i))) THEN
145        ztop(i)=zmidkm(i,ctop(i))
146    ENDIF
147  ENDDO
148
149  !     ... Flashes per sec (Price and Rind, 92)
150  DO i=1,PLON
151    IF (ztop(i) > 4.) THEN
152        flash(i)=3.44e-5*ztop(i)**4.90 *oro(i) + 6.40e-4*ztop(i)**1.73 *(1.-oro(i))
153    ENDIF
154  ENDDO
155 
156  !     ... Two calibrations applied:
157  !     1. To account for cloud height averaging (see Price and Rind, 1994)
158  !     2. To ensure 5 TgN in global and annual mean.
159 
160  dx = 2.*pi/FLOAT(nx)*r2d
161  dy = pi/FLOAT(ny)*r2d
162 
163  calibration = 9.7241e-1*EXP(4.8203e-2*dx*dy)
164  flash(:) = 2. * calibration * flash(:)   !KE
165
166  !     ... Find 0 celcius isotherm
167  DO i=1,PLON
168    DO l=1,PLEV-1
169      IF ( pmid(i,l) > 2.e4 ) THEN
170          IF ( (temp(i,l) > 273.15) .AND. (temp(i,l+1) < 273.15) ) THEN
171              a(i)=(temp(i,l+1)-temp(i,l))/(zmidkm(i,l+1)-zmidkm(i,l))
172              b(i)=temp(i,l)-a(i)*zmidkm(i,l)
173              ziso0(i)=(273.15-b(i))/a(i)
174          ENDIF
175      ENDIF
176    ENDDO
177  ENDDO
178 
179  !     ... Intracloud and cloud-to-ground lightning
180
181  DO i=1,PLON
182
183    IF (ziso0(i) < ztop(i)) THEN
184
185        dcold(i)=ztop(i)-ziso0(i)
186       
187        IF ( (dcold(i) > 5.5) .AND. (dcold(i) < 14.) ) THEN
188            z(i)=(ap*dcold(i)**4+bp*dcold(i)**3+cp*dcold(i)**2+dp*dcold(i)+ep)
189            pcg(i)=1./(z(i)+1.)
190        ELSE IF (dcold(i) <= 5.5) THEN
191            pcg(i)=0.
192        ELSE IF (dcold(i) >= 14.) THEN
193            pcg(i)=2.e-2
194        ENDIF
195       
196        fcg(i) = pcg(i)*flash(i)
197        fic(i) = (1.-pcg(i))*flash(i)
198
199    ENDIF
200   
201  ENDDO
202
203!     ... Change units to fl/s/m2 DH.
204
205      flash(:) = flash(:)/60./area(:)
206      flpcg(:) = fcg(:)/60./area(:)
207 
208  !     ... Column integrated NO production
209  globoprod_no(:) = 6.7e25 * (10.*fcg(:)+fic(:)) /60./area(:)
210 
211  !     ... Pickering et al. (1998) vertical distribution
212  DO i=1,PLON
213    xprod_no(i,1:ctop(i))=1.
214  ENDDO
215 
216  zinterf(:,1)=0.
217  zinterf(:,2)=2.*zmidkm(:,1)
218  DO l=2,PLEV
219    zinterf(:,l+1)=zinterf(:,l)+2.*(zmidkm(:,l)-zinterf(:,l))
220  ENDDO
221 
222  DO l=1,PLEV
223    deltaz(:,l)=(zinterf(:,l+1)-zinterf(:,l))*1.e3
224  ENDDO
225 
226     
227  DO i=1,PLON
228    IF (flash(i) > zero) THEN
229       
230        IF ( ABS(lat(i)) >= 30.) THEN
231            scal(i)=ztop(i)/14.5
232        ELSE
233            scal(i)=ztop(i)/16.
234        ENDIF
235       
236    ENDIF
237  ENDDO
238 
239  DO l=1,zdim
240    altp(:,l)=alt(l)*scal(:)
241  ENDDO
242 
243  DO i=1,PLON
244    DO l=1,zdim-1
245
246      IF (scal(i) > zero) THEN
247          atc(i,l)=(coeff_tc(l+1)-coeff_tc(l))/(altp(i,l+1)-altp(i,l))
248          btc(i,l)=coeff_tc(l)-atc(i,l)*altp(i,l)
249          atm(i,l)=(coeff_tm(l+1)-coeff_tm(l))/(altp(i,l+1)-altp(i,l))
250          btm(i,l)=coeff_tm(l)-atm(i,l)*altp(i,l)
251          amc(i,l)=(coeff_mc(l+1)-coeff_mc(l))/(altp(i,l+1)-altp(i,l))
252          bmc(i,l)=coeff_mc(l)-amc(i,l)*altp(i,l)
253      ENDIF
254     
255    ENDDO
256  ENDDO
257 
258  coeff_mcp=0.
259  coeff_tmp=0.
260  coeff_tcp=0.
261 
262  DO i=1,PLON
263    DO lp=1,zdim-1
264      DO l=1,ctop(i)
265       
266        IF (flash(i) > zero) THEN
267           
268            IF (zmidkm(i,l) <= altp(i,1)) THEN
269                coeff_tcp(i,l)=coeff_tc(1)
270                coeff_tmp(i,l)=coeff_tm(1)
271                coeff_mcp(i,l)=coeff_mc(1)
272            ENDIF
273           
274            IF ((zmidkm(i,l) <= altp(i,lp+1)) .AND. (zmidkm(i,l) >= altp(i,lp))) THEN
275                coeff_tcp(i,l)=atc(i,lp)*zmidkm(i,l)+btc(i,lp)
276                coeff_tmp(i,l)=atm(i,lp)*zmidkm(i,l)+btm(i,lp)
277                coeff_mcp(i,l)=amc(i,lp)*zmidkm(i,l)+bmc(i,lp)
278            ENDIF
279        ENDIF
280       
281      ENDDO
282    ENDDO
283  ENDDO
284 
285  somcoeff1=0.
286  somcoeff2=0.
287  somcoeff3=0.
288 
289  DO i=1,PLON
290    DO l=1,ctop(i)
291      somcoeff1(i)=somcoeff1(i)+coeff_tcp(i,l)*deltaz(i,l)
292      somcoeff2(i)=somcoeff2(i)+coeff_tmp(i,l)*deltaz(i,l)
293      somcoeff3(i)=somcoeff3(i)+coeff_mcp(i,l)*deltaz(i,l)
294    ENDDO
295  ENDDO
296 
297  DO i=1,PLON
298    DO l=1,ctop(i)
299     
300      IF (somcoeff1(i) > zero) THEN
301          coeff_tcp(i,l)=coeff_tcp(i,l)/somcoeff1(i)*1.e2
302      ENDIF
303     
304      IF (somcoeff2(i) > zero) THEN
305          coeff_tmp(i,l)=coeff_tmp(i,l)/somcoeff2(i)*1.e2
306      ENDIF
307     
308      IF (somcoeff3(i) > zero) THEN
309          coeff_mcp(i,l)=coeff_mcp(i,l)/somcoeff3(i)*1.e2
310      ENDIF
311     
312    ENDDO
313  ENDDO
314 
315  DO i=1,PLON
316    DO l=1,ctop(i)
317      IF (flash(i) > zero) THEN
318          IF ( ABS(lat(i)) <= 30. ) THEN
319             
320              xprod_no(i,l)=coeff_tcp(i,l)*0.01 * oro(i) + coeff_tmp(i,l)*0.01 * (1.-oro(i))
321          ELSE
322             
323              xprod_no(i,l)=coeff_mcp(i,l)*0.01
324          ENDIF
325      ENDIF
326    ENDDO
327  ENDDO
328 
329  no_col=0.
330  DO i=1,PLON
331    lmax=ctop(i)
332    DO l=1,lmax
333      no_col(i) = no_col(i) + xprod_no(i,l) * deltaz(i,l) * 1.e6
334    ENDDO
335  ENDDO
336 
337  prod_light=0.
338  factor=0.
339  DO i=1,PLON
340    lmax=ctop(i)
341    IF (no_col(i) /= 0.) THEN
342        factor(i) = globoprod_no(i) / no_col(i)
343    ENDIF
344    DO l=1,lmax
345      prod_light(i,l) = xprod_no(i,l) * factor(i)
346    ENDDO
347  ENDDO
348 
349  source = 0.
350  DO i=1,PLON
351    DO l=1,PLEV
352      source = source + prod_light(i,l)*area(i)*deltaz(i,l)*1.e6
353    ENDDO
354  ENDDO
355  source = source /6.02e23 *14. *secpyr *1.e-12
356
357!Integrated lightning NOx production (should be in kg/m2/s since prod_light is in molec/cm3/s)
358  DO i=1,PLON
359    DO l=1,PLEV
360      prod_light_col(i) = prod_light_col(i) + prod_light(i,l)*1.e6*deltaz(i,l)/6.02e23*14.*1.e-3
361    ENDDO
362  ENDDO
363 
364END SUBROUTINE MKNOPROD
365
Note: See TracBrowser for help on using the repository browser.