1 !WRF:MODEL_LAYER:CHEMISTRY
3 ! Contains subroutine for converting flash rates into NO emissions
4 ! based on prescribed vertical distirbutions. Subroutines should behave
8 ! Output: tendency (ppmv/s)
10 ! The output will be muliplied by timestep and used to incremeent NO
11 ! concentration and the respective passive tracer in lightning_nox_driver.
13 ! See module_lightning_nox_driver for more info.
15 ! Contact: J. Wong <johnwong@ucar.edu>
17 !**********************************************************************
18 MODULE module_lightning_nox_ott
24 !**********************************************************************
26 ! Ott et al 2010 vertical disitrbution (page 12)
28 ! Ott, L. E. et al (2010), Production of lightning NOx and its vertical
29 ! distribution calculated from three-dimensional cloud-scale chemical
30 ! transport model simulations, J. Geophys. Res., 115, D04301, doi:10.1029/2009JD011880.
32 ! Usage note: This method consolidates IC and CG flash rates but scales
33 ! each category based on N_IC and N_CG. Thus by setting N_IC=N_CG, the
34 ! perturbation on NO emission would become agnostic to the IC:CG
35 ! partitioning method.
37 !**********************************************************************
38 SUBROUTINE lightning_nox_ott ( &
39 ! Frequently used prognostics
40 dx, dy, xlat, xland, ht, rho, z, &
41 ic_flashrate, cg_flashrate, & ! flashes (#/s)
44 ! Order dependent args for domain, mem, and tile dims
45 ids, ide, jds, jde, kds, kde, &
46 ims, ime, jms, jme, kms, kme, &
47 its, ite, jts, jte, kts, kte, &
49 lnox_total_tend & ! tendency (ppmv/s)
51 !-----------------------------------------------------------------
53 USE module_state_description
56 USE module_model_constants
60 !-----------------------------------------------------------------
62 ! Frequently used prognostics
63 REAL, INTENT(IN ) :: dx, dy
65 REAL, DIMENSION( ims:ime, jms:jme ), INTENT(IN ) :: xlat, xland, ht
66 REAL, DIMENSION( ims:ime, kms:kme, jms:jme ), INTENT(IN ) :: rho, z
67 REAL, DIMENSION( ims:ime, jms:jme ), INTENT(IN ) :: ic_flashrate , cg_flashrate ! #/sec
69 ! Namelist settings moles NO emission per flash
70 REAL, INTENT(IN ) :: N_IC, N_CG
72 ! Order dependent args for domain, mem, and tile dims
73 INTEGER, INTENT(IN ) :: ids,ide, jds,jde, kds,kde
74 INTEGER, INTENT(IN ) :: ims,ime, jms,jme, kms,kme
75 INTEGER, INTENT(IN ) :: its,ite, jts,jte, kts,kte
78 REAL, DIMENSION( ims:ime, kms:kme, jms:jme ), INTENT( OUT) :: lnox_total_tend
81 REAL, PARAMETER :: subtrop_midlat = 35.
82 REAL, PARAMETER :: trop_subtrop = 20.
84 ! Vertical distribution data
85 INTEGER, PARAMETER :: vds = 0
86 INTEGER, PARAMETER :: vde = 16
87 ! 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17
88 REAL, DIMENSION(vds:vde), PARAMETER :: &
89 ott_subtrop(vde+1) = (/ .010,.021,.039,.058,.077,.093,.105,.110,.110,.104,.092,.075,.055,.034,.015,.002,.000 /)
90 REAL, DIMENSION(vds:vde), PARAMETER :: &
91 ott_midlat(vde+1) = (/ .024,.050,.074,.093,.106,.114,.115,.110,.099,.083,.063,.042,.022,.005,.000,.000,.000 /)
92 REAL, DIMENSION(vds:vde), PARAMETER :: & ! tropical continental
93 ott_trpcon(vde+1) = (/ .002,.005,.006,.014,.027,.040,.050,.062,.086,.103,.116,.124,.127,.124,.076,.030,.008 /)
94 REAL, DIMENSION(vds:vde), PARAMETER :: & ! tropical marine
95 ott_trpmar(vde+1) = (/ .006,.015,.029,.043,.054,.067,.077,.085,.096,.102,.105,.102,.082,.065,.045,.022,.005 /)
99 INTEGER :: v ! vertical iterator in km
100 REAL :: total_NO, mass_of_air, dA
101 REAL, DIMENSION( kts:kte ):: zkm ! AGL height in km
102 REAL, DIMENSION( vds:vde ):: NOperkm ! moles/km, number of flashes of each grid / km in z
104 !-----------------------------------------------------------------
106 lnox_total_tend(its:ite,kts:kte,jts:jte) = 0.
112 ! Calculate column LNO (moles)
113 total_NO = ic_flashrate(I,J)*N_IC + cg_flashrate(I,J)*N_CG
114 IF ( total_NO .eq. 0. ) CONTINUE
116 ! Calculate vertical distribution in moles/km in z (/s)
117 IF ( xlat(I,J) .gt. subtrop_midlat ) THEN
118 NOperkm(:) = ott_midlat(:) * total_NO
119 ELSE IF ( xlat(I,J) .gt. trop_subtrop ) THEN
120 NOperkm(:) = ott_subtrop(:) * total_NO
121 ELSE IF ( xland(I,J) .gt. 1.5 ) THEN
122 NOperkm(:) = ott_trpcon(:) * total_NO
124 NOperkm(:) = ott_trpmar(:) * total_NO
127 ! Convert to ppmv in each grid
128 ! This method does not invert to the exact N_IC+N_CG mole # since grids
129 ! are assumed to be within discrete km levels according to the middle
130 ! AGL height. Improves with finer vertical discretization
132 zkm(kts:kte) = ( z(i,kts:kte,j) - ht(i,j) ) / 1000.
133 v = MAX( vds, int(zkm(k)) )
134 DO WHILE ( (v .le. vde) .and. (k .le. kte) )
135 mass_of_air = rho(i,k,j) * 1E3 * dA / .02897 ! # mol air /km in z
136 lnox_total_tend(i,k,j) = NOperkm(v)/mass_of_air * 1E6 ! ppmv (/s)
139 IF ( int(zkm(k)) .gt. v ) v = int( zkm(k) )
144 END SUBROUTINE lightning_nox_ott
147 END MODULE module_lightning_nox_ott