1 MODULE module_fire_emis
5 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
6 ! Simple smoke aerosol emissions scheme for Thompson-Eidhammer Aerosol-Aware microphysics scheme !
8 ! Implemented by T. W. Juliano (NCAR/RAL) on 4/13/2022 !
10 ! First implementation includes two options: !
11 ! 1. wif_fire_inj = 0 --> Emit smoke aerosols in the lowest model grid cell !
12 ! --> Recommended for LES configuration where dx is sufficiently small !
13 ! to resolve strong vertical velocities that can mix aerosols !
14 ! throughout the BL during convective conditions !
15 ! 2. wif_fire_inj = 1 --> Default option !
16 ! --> Emit smoke aerosols using simple plumerise scheme that evenly !
17 ! distributes throughout the BL column based on PBL height diagnosed !
18 ! by the PBL parameterization !
19 ! --> Recommended for mesoscale simulations where dx is not small enough !
20 ! to explicitly mix aerosols throughout the BL during convective !
21 ! conditions due to relatively weak updrafts !
23 ! Future implementation could include plumerise model by Freitas et al. (2007, ACP), which is !
24 ! currently part of the WRF-Chem codebase !
25 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
27 SUBROUTINE fire_emis_simple_plumerise(wif_fire_inj, aer_fire_emit_opt, z_at_mass, pblh, &
28 nwfa, nbca, nocbb2d, nbcbb2d, dt_in, ids, ide, jds, jde, kds, kde, &
29 ims, ime, jms, jme, kms, kme, its, ite, jts, jte, kts, kte)
33 INTEGER , INTENT(IN) :: wif_fire_inj, aer_fire_emit_opt
34 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), INTENT(IN) :: z_at_mass
35 REAL, DIMENSION(ims:ime, jms:jme) , INTENT(IN) :: pblh
36 REAL, DIMENSION(ims:ime, kms:kme, jms:jme), INTENT(INOUT) :: nwfa, nbca
37 REAL, DIMENSION(ims:ime, jms:jme) , INTENT(IN) :: nocbb2d, nbcbb2d
38 REAL , INTENT(IN) :: dt_in
39 INTEGER , INTENT(IN) :: ids, ide, jds, jde, kds, kde, &
40 ims, ime, jms, jme, kms, kme, &
41 its, ite, jts, jte, kts, kte
44 INTEGER :: i, j, k, i_start, i_end, j_start, j_end, k_inj
45 REAL :: noc_emit, nbc_emit
49 i_end = MIN(ite, ide-1)
50 j_end = MIN(jte, jde-1)
52 ! Emit fire aerosols at surface (recommended for LES configuration)
53 if (wif_fire_inj .eq. 0) then
56 nwfa(i,kts,j) = nwfa(i,kts,j) + nocbb2d(i,j)*dt_in
57 if (aer_fire_emit_opt .eq. 2) then
58 nbca(i,kts,j) = nbca(i,kts,j) + nbcbb2d(i,j)*dt_in
62 ! Distribute fire aerosols evenly through PBL (recommended for mesoscale simulations)
63 else if (wif_fire_inj .eq. 1) then
66 ! Find k index for PBL top
68 do while (z_at_mass(i,k_inj,j) .lt. pblh(i,j))
71 ! Compute num of OC aerosols to emit per grid cell
72 noc_emit = (nocbb2d(i,j)*dt_in)/k_inj
73 ! Compute num of BC aerosols to emit per grid cell
74 if (aer_fire_emit_opt .eq. 2) then
75 nbc_emit = (nbcbb2d(i,j)*dt_in)/k_inj
79 nwfa(i,k,j) = nwfa(i,k,j) + noc_emit
80 if (aer_fire_emit_opt .eq. 2) then
81 nbca(i,k,j) = nbca(i,k,j) + nbc_emit
86 ! Option does not exist
88 call wrf_error_fatal('option wif_fire_inj = ', wif_fire_inj, ' does not exist. Please set =0 or =1')
91 END SUBROUTINE fire_emis_simple_plumerise
93 END MODULE module_fire_emis