emission_bc.F90 18 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550
  1. !
  2. #define TRACEBACK write (gol,'("in ",a," (",a,", line",i5,")")') rname, __FILE__, __LINE__; call goErr
  3. #define IF_NOTOK_RETURN(action) if (status/=0) then; TRACEBACK; action; return; end if
  4. #define IF_ERROR_RETURN(action) if (status> 0) then; TRACEBACK; action; return; end if
  5. !
  6. #include "tm5.inc"
  7. !
  8. !-----------------------------------------------------------------------------
  9. ! TM5 !
  10. !-----------------------------------------------------------------------------
  11. !BOP
  12. !
  13. ! !MODULE: EMISSION_BC
  14. !
  15. ! !DESCRIPTION: Data and methods fo Black Carbon (BC) emissions.
  16. !
  17. !>>> TvN
  18. ! The emission radii have been modified
  19. ! following the AeroCom recommendations of Dentener et al. (ACP, 2006),
  20. ! adapted for the M7 modes by Stier et al. (JGR, 2005).
  21. ! BC is emitted into the insoluble Aitken mode.
  22. ! The geometric mean radius for BC emissions from biomass burning
  23. ! is therefore assumed to be the same as for fossil-fuel emissions
  24. ! (as in Stier et al.)
  25. !
  26. !<<< TvN
  27. !
  28. !\\
  29. !\\
  30. ! !INTERFACE:
  31. !
  32. MODULE EMISSION_BC
  33. !
  34. ! !USES:
  35. !
  36. use GO, only : gol, goErr, goPr
  37. use tm5_distgrid, only : dgrid, get_distgrid, scatter, gather
  38. use dims, only : nregions, okdebug
  39. use global_data, only : emis_data, d3_data
  40. use emission_data, only : emis_input_year
  41. use emission_read, only : used_providers_aer, has_aer_emis
  42. IMPLICIT NONE
  43. PRIVATE
  44. !
  45. ! !PUBLIC MEMBER FUNCTIONS:
  46. !
  47. public :: emission_bc_init, emission_BC_done, emission_bc_declare
  48. !
  49. ! !PRIVATE DATA MEMBERS:
  50. !
  51. character(len=*), parameter :: mname = 'emission_bc'
  52. type(emis_data), dimension(:,:), allocatable :: bc_emis_2d
  53. type(d3_data), dimension(:,:), allocatable :: bc_emis_3d
  54. integer :: bc_2dsec, bc_3dsec
  55. !
  56. ! !REVISION HISTORY:
  57. ! ? ??? 2005 - Elisabetta Vignati - changed for coupling with M7
  58. ! 1 Sep 2010 - Achim Strunk - revised for AR5 emissions
  59. ! 22 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  60. !
  61. ! !REMARKS:
  62. !
  63. !EOP
  64. !------------------------------------------------------------------------
  65. CONTAINS
  66. !--------------------------------------------------------------------------
  67. ! TM5 !
  68. !--------------------------------------------------------------------------
  69. !BOP
  70. !
  71. ! !IROUTINE: EMISSION_BC_INIT
  72. !
  73. ! !DESCRIPTION: Allocate space needed to handle the emissions.
  74. !\\
  75. !\\
  76. ! !INTERFACE:
  77. !
  78. SUBROUTINE EMISSION_BC_INIT( status )
  79. !
  80. ! !USES:
  81. !
  82. use dims, only : lm
  83. use emission_read, only : providers_def, numb_providers
  84. use emission_data, only : LAR5BMB
  85. use emission_read, only : n_ar5_ant_sec, n_ar5_shp_sec, n_ar5_air_sec, n_ar5_bmb_sec
  86. use emission_read, only : ar5_cat_ant, ar5_cat_shp, ar5_cat_air, ar5_cat_bmb
  87. !
  88. ! !OUTPUT PARAMETERS:
  89. !
  90. integer, intent(out) :: status
  91. !
  92. ! !REVISION HISTORY:
  93. ! 1 Oct 2010 - Achim Strunk -
  94. ! 25 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  95. !
  96. !EOP
  97. !------------------------------------------------------------------------
  98. !BOC
  99. character(len=*), parameter :: rname = mname//'/Emission_BC_Init'
  100. integer :: region, lsec
  101. integer :: lmr, lprov, i1, i2, j1, j2
  102. ! --- begin --------------------------------------
  103. status = 0
  104. if(.not. has_aer_emis) return
  105. ! nb of sectors
  106. bc_2dsec = 0
  107. bc_3dsec = 0
  108. do lprov = 1, numb_providers
  109. if (count(used_providers_aer.eq.providers_def(lprov)%name)/=0) then
  110. if (trim(providers_def(lprov)%name) .eq. 'AR5') then
  111. ! nb of available sectors in AR5 depends on category
  112. bc_2dsec = bc_2dsec + n_ar5_ant_sec*count('BC'.eq.ar5_cat_ant) + &
  113. n_ar5_shp_sec*count('BC'.eq.ar5_cat_shp)
  114. if (LAR5BMB) bc_2dsec = bc_2dsec + n_ar5_bmb_sec*count('BC'.eq.ar5_cat_bmb)
  115. bc_3dsec = bc_3dsec + count('BC'.eq.ar5_cat_air)
  116. else
  117. bc_2dsec = bc_2dsec + providers_def(lprov)%nsect2d
  118. bc_3dsec = bc_3dsec + providers_def(lprov)%nsect3d
  119. endif
  120. endif
  121. enddo
  122. allocate( bc_emis_2d( nregions, bc_2dsec ) )
  123. allocate( bc_emis_3d( nregions, bc_3dsec ) )
  124. ! allocate information arrays (2d and 3d)
  125. do region=1,nregions
  126. CALL GET_DISTGRID( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  127. lmr = lm(region)
  128. do lsec=1,bc_2dsec
  129. allocate( bc_emis_2d(region,lsec)%surf(i1:i2,j1:j2) )
  130. end do
  131. do lsec=1,bc_3dsec
  132. allocate( bc_emis_3d(region,lsec)%d3(i1:i2,j1:j2,lmr) )
  133. end do
  134. enddo
  135. ! ok
  136. status = 0
  137. END SUBROUTINE EMISSION_BC_INIT
  138. !EOC
  139. !--------------------------------------------------------------------------
  140. ! TM5 !
  141. !--------------------------------------------------------------------------
  142. !BOP
  143. !
  144. ! !IROUTINE: EMISSION_BC_DONE
  145. !
  146. ! !DESCRIPTION: Free space after handling of BC emissions.
  147. !\\
  148. !\\
  149. ! !INTERFACE:
  150. !
  151. SUBROUTINE EMISSION_BC_DONE( status )
  152. !
  153. ! !OUTPUT PARAMETERS:
  154. !
  155. integer, intent(out) :: status
  156. !
  157. ! !REVISION HISTORY:
  158. ! 1 Oct 2010 - Achim Strunk -
  159. !
  160. !EOP
  161. !------------------------------------------------------------------------
  162. !BOC
  163. character(len=*), parameter :: rname = mname//'/Emission_BC_Done'
  164. integer :: region, lsec
  165. ! --- begin --------------------------------------
  166. status = 0
  167. if(.not. has_aer_emis) return
  168. do region = 1, nregions
  169. do lsec=1,bc_2dsec
  170. deallocate( bc_emis_2d(region,lsec)%surf )
  171. end do
  172. do lsec=1,bc_3dsec
  173. deallocate( bc_emis_3d(region,lsec)%d3 )
  174. end do
  175. end do
  176. deallocate( bc_emis_2d )
  177. deallocate( bc_emis_3d )
  178. ! ok
  179. status = 0
  180. END SUBROUTINE EMISSION_BC_DONE
  181. !EOC
  182. !--------------------------------------------------------------------------
  183. ! TM5 !
  184. !--------------------------------------------------------------------------
  185. !BOP
  186. !
  187. ! !IROUTINE: EMISSION_BC_DECLARE
  188. !
  189. ! !DESCRIPTION: Opens, reads and evaluates input files (per month).
  190. ! Provides emissions on 2d/3d-arrays which are then given
  191. ! to emis_number and emis_mass, which are used in
  192. ! sedimentation. (no *_apply!)
  193. !\\
  194. !\\
  195. ! !INTERFACE:
  196. !
  197. SUBROUTINE EMISSION_BC_DECLARE( status )
  198. !
  199. ! !USES:
  200. !
  201. use binas, only : pi
  202. use partools, only : isRoot, par_broadcast
  203. use toolbox, only : coarsen_emission
  204. use dims, only : im, jm, lm, idate, sec_month, nlon360, nlat180
  205. use chem_param, only : xmbc, mode_aii, sigma_lognormal, carbon_density
  206. use chem_param, only : rad_emi_ff, rad_emi_vg_insol
  207. use emission_data, only : emis_mass, emis_number, msg_emis, LAR5BMB
  208. use emission_data, only : emission_vdist_by_sector
  209. ! ---------------- AR5 - GFED - RETRO - MACC --------------------
  210. use emission_data, only : LAR5BMB
  211. use emission_data, only : emis_input_dir_mac
  212. use emission_data, only : emis_input_dir_retro
  213. use emission_data, only : emis_input_dir_gfed
  214. use emission_read, only : emission_ar5_regrid_aircraft
  215. use emission_read, only : emission_ar5_ReadSector
  216. use emission_read, only : emission_macc_ReadSector
  217. use emission_read, only : emission_gfed_ReadSector
  218. use emission_read, only : emission_retro_ReadSector
  219. use emission_read, only : sectors_def, numb_sectors
  220. use emission_read, only : ar5_dim_3ddata
  221. !
  222. ! !OUTPUT PARAMETERS:
  223. !
  224. integer, intent(out) :: status
  225. !
  226. ! !REVISION HISTORY:
  227. ! 1 Oct 2010 - Achim Strunk - adapted for AR5
  228. ! 22 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  229. !
  230. !EOP
  231. !------------------------------------------------------------------------
  232. !BOC
  233. character(len=*), parameter :: rname = mname//'/emission_bc_declare'
  234. integer :: region, hasData
  235. integer, parameter :: add_field=0
  236. integer, parameter :: amonth=2
  237. real :: rad_emi, numbscale
  238. integer :: imr, jmr, lmr, lsec, i1, i2, j1, j2
  239. ! ---------------------------------------------------------------
  240. ! AR5
  241. real,dimension(:,:,:), allocatable :: field3d
  242. real :: mass2numb
  243. type(d3_data) :: emis3d(nregions), work(nregions), work3d(nregions)
  244. type(emis_data) :: wrk2D(nregions)
  245. integer :: seccount2d, seccount3d
  246. ! --- begin -----------------------------------------
  247. status = 0
  248. if(.not. has_aer_emis) return
  249. write(gol,'(" EMISS-INFO ------------- read BC emissions -------------")'); call goPr
  250. ! Reset emissions
  251. do region = 1, nregions
  252. do lsec=1,bc_2dsec
  253. bc_emis_2d(region,lsec)%surf = 0.0
  254. end do
  255. do lsec=1,bc_3dsec
  256. bc_emis_3d(region,lsec)%d3 = 0.0
  257. end do
  258. end do
  259. ! Allocate work arrays
  260. do region = 1, nregions
  261. CALL GET_DISTGRID( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  262. lmr = lm(region)
  263. allocate( work3d(region)%d3 (i1:i2,j1:j2, ar5_dim_3ddata) ) ; work3d(region)%d3 = 0.0
  264. allocate( emis3d(region)%d3 (i1:i2,j1:j2, lmr ) ) ; emis3d(region)%d3 = 0.0
  265. end do
  266. ! Global arrays for coarsening
  267. do region = 1, nregions
  268. if (isRoot)then
  269. allocate(work(region)%d3(im(region),jm(region),ar5_dim_3ddata))
  270. else
  271. allocate(work(region)%d3(1,1,1))
  272. end if
  273. enddo
  274. do region = 1, nregions
  275. wrk2D(region)%surf => work(region)%d3(:,:,1)
  276. end do
  277. ! --------------------------------
  278. ! Loop over available sectors
  279. ! --------------------------------
  280. ! count 2d and 3d sectors
  281. seccount2d = 0
  282. seccount3d = 0
  283. ! always allocate here 3d data set (for 2d sectors it will be filled in first layer only)
  284. if (isRoot) then
  285. allocate( field3d( nlon360, nlat180, ar5_dim_3ddata ) ) ; field3d = 0.0
  286. else
  287. allocate( field3d( 1, 1, 1 ) )
  288. end if
  289. sec : do lsec = 1, numb_sectors
  290. if (count(used_providers_aer.eq.sectors_def(lsec)%prov).eq.0) cycle ! skip unused providers
  291. if (associated(sectors_def(lsec)%species)) then ! AR5 check
  292. if (count('BC'.eq.sectors_def(lsec)%species).eq.0) cycle
  293. if ((trim(sectors_def(lsec)%catname) .eq. 'biomassburning').and.(.not.LAR5BMB)) cycle
  294. endif
  295. field3d = 0.0
  296. if( sectors_def(lsec)%f3d ) then
  297. seccount3d = seccount3d + 1
  298. else
  299. seccount2d = seccount2d + 1
  300. end if
  301. if (isRoot) then ! READ
  302. select case( trim(sectors_def(lsec)%prov) )
  303. case( 'AR5' )
  304. ! Screen out agricultural and solvent sectors for BC,
  305. ! because they are zero in the RCPs
  306. ! and not present in the historical files.
  307. if (trim(sectors_def(lsec)%name) .ne. 'emiss_agr' .and. &
  308. trim(sectors_def(lsec)%name) .ne. 'emiss_slv') then
  309. call emission_ar5_ReadSector( 'BC', emis_input_year, idate(2), lsec, field3d, status )
  310. IF_NOTOK_RETURN(status=1;deallocate(field3d))
  311. endif
  312. case( 'MACC' )
  313. ! Screen out 'soil', 'nat', 'oc', bio', 'oc', and 'air' since they are not available for BC.
  314. if ( ( .not. (trim(sectors_def(lsec)%name) .eq. 'emiss_soil')) .and. &
  315. ( .not. (trim(sectors_def(lsec)%name) .eq. 'emiss_nat') ) .and. &
  316. ( .not. (trim(sectors_def(lsec)%name) .eq. 'emiss_oc') ) .and. &
  317. ( .not. (trim(sectors_def(lsec)%name) .eq. 'emiss_bio' ) ) .and. &
  318. ( .not. (trim(sectors_def(lsec)%name) .eq. 'emiss_air') ) ) then
  319. call emission_macc_ReadSector( emis_input_dir_mac, 'BC', emis_input_year, idate(2), &
  320. '0.5x0.5_kg.nc', sectors_def(lsec)%name, 'kg / s', field3d, status )
  321. IF_NOTOK_RETURN(status=1;deallocate(field3d))
  322. end if
  323. case('GFEDv3')
  324. call emission_gfed_ReadSector( emis_input_dir_gfed, 'bc', emis_input_year, idate(2), &
  325. 'GFED', 'kg / s', field3d(:,:,1), status )
  326. IF_NOTOK_RETURN(status=1)
  327. case('RETRO')
  328. call emission_retro_ReadSector( emis_input_dir_retro, 'BC', emis_input_year, idate(2), &
  329. sectors_def(lsec)%name, 'kg / s', field3d(:,:,1), status )
  330. IF_NOTOK_RETURN(status=1)
  331. case default
  332. write(gol,*) "Error in list of providers for BC"; call goErr
  333. status=1; TRACEBACK; return
  334. end select
  335. ! nothing found???
  336. if( sum(field3d) < 100.*TINY(1.0) ) then
  337. if (okdebug ) then
  338. write(gol,'("EMISS-INFO - no BC emissions found for ",a," ",a," for month ",i2 )') &
  339. trim(sectors_def(lsec)%prov), trim(sectors_def(lsec)%name), idate(2) ; call goPr
  340. endif
  341. hasData=0
  342. else
  343. if (okdebug) then
  344. write(gol,'("EMISS-INFO - found BC emissions for ",a," ",a," for month ",i2 )') &
  345. trim(sectors_def(lsec)%prov), trim(sectors_def(lsec)%name), idate(2) ; call goPr
  346. endif
  347. ! scale from kg/s to kg/month
  348. field3d = field3d * sec_month ! kg / month
  349. hasData=1
  350. end if
  351. end if
  352. call Par_broadcast(hasData, status)
  353. IF_NOTOK_RETURN(status=1)
  354. if (hasData == 0) cycle sec
  355. ! allow for different mean size for emissions from vegetation fires
  356. if( trim(sectors_def(lsec)%catname) == 'biomassburning' ) then
  357. rad_emi = rad_emi_vg_insol
  358. else
  359. rad_emi = rad_emi_ff
  360. endif
  361. ! mass to number factors
  362. numbscale = rad_emi*EXP(1.5*(LOG(sigma_lognormal(mode_aii)))**2)
  363. mass2numb = 3./(4.*pi*(numbscale**3)*carbon_density)
  364. ! distinguish 2d/3d sectors
  365. if( sectors_def(lsec)%f3d ) then
  366. ! ---------------------------
  367. ! 3d data (AIRCRAFT)
  368. ! ---------------------------
  369. if (isRoot) then
  370. ! write some numbers
  371. call msg_emis( amonth, trim(sectors_def(lsec)%prov), sectors_def(lsec)%name, 'BC', xmbc, sum(field3d) )
  372. ! distribute to work arrays in regions
  373. call Coarsen_Emission( 'BC '//trim(sectors_def(lsec)%name), nlon360, nlat180, ar5_dim_3ddata, &
  374. field3d, work, add_field, status )
  375. IF_NOTOK_RETURN(status=1)
  376. end if
  377. ! scatter, sum up on target array
  378. do region = 1, nregions
  379. call scatter(dgrid(region), work3d(region)%d3, work(region)%d3, 0, status)
  380. IF_NOTOK_RETURN( status=1 )
  381. CALL GET_DISTGRID( dgrid(region), I_STRT=i1, J_STRT=j1)
  382. ! aircraft data: regrid vertically to model layers
  383. call emission_ar5_regrid_aircraft( region, i1, j1, work3d(region)%d3, emis3d(region)%d3, status )
  384. IF_NOTOK_RETURN( status=1 )
  385. bc_emis_3d(region,seccount3d)%d3 = bc_emis_3d(region,seccount3d)%d3 + emis3d(region)%d3
  386. end do
  387. ! add to emis target arrays (scale mass to get number)
  388. do region = 1, nregions
  389. emis_mass (region,mode_aii)%d4(:,:,:,1) = &
  390. emis_mass (region,mode_aii)%d4(:,:,:,1) + bc_emis_3d(region,seccount3d)%d3
  391. emis_number(region,mode_aii)%d4(:,:,:,1) = &
  392. emis_number(region,mode_aii)%d4(:,:,:,1) + bc_emis_3d(region,seccount3d)%d3 * mass2numb
  393. end do
  394. else ! sector is 2d
  395. ! ---------------------------
  396. ! 2d data (Anthropogenic, Ships, Biomassburning)
  397. ! ---------------------------
  398. if (isRoot) then ! print total & regrid
  399. call msg_emis( amonth, trim(sectors_def(lsec)%prov), sectors_def(lsec)%name, 'BC', xmbc, sum(field3d(:,:,1)) )
  400. call coarsen_emission( 'BC '//sectors_def(lsec)%name, nlon360, nlat180, field3d(:,:,1), &
  401. wrk2D, add_field, status )
  402. IF_NOTOK_RETURN(status=1)
  403. end if
  404. ! get temporary array for vertical distribution
  405. do region = 1, nregions
  406. call scatter(dgrid(region), bc_emis_2d(region,seccount2d)%surf, work(region)%d3(:,:,1), 0, status)
  407. IF_NOTOK_RETURN(status=1)
  408. emis3d(region)%d3 = 0.0
  409. ! do vertical distribution
  410. call emission_vdist_by_sector( sectors_def(lsec)%vdisttype, 'BC', region, bc_emis_2d(region,seccount2d), &
  411. emis3d(region), status )
  412. IF_NOTOK_RETURN(status=1)
  413. ! add to emis target arrays (scale mass to get number)
  414. emis_mass (region,mode_aii)%d4(:,:,:,1) = &
  415. emis_mass (region,mode_aii)%d4(:,:,:,1) + emis3d(region)%d3
  416. emis_number(region,mode_aii)%d4(:,:,:,1) = &
  417. emis_number(region,mode_aii)%d4(:,:,:,1) + emis3d(region)%d3 * mass2numb
  418. end do
  419. end if
  420. end do sec
  421. deallocate( field3d )
  422. do region = 1, nregions
  423. if (associated(wrk2D(region)%surf)) nullify(wrk2D(region)%surf)
  424. deallocate( work(region)%d3 )
  425. deallocate( emis3d(region)%d3 )
  426. deallocate( work3d(region)%d3 )
  427. end do
  428. ! check sectors found
  429. if( seccount2d /= bc_2dsec ) then
  430. write(gol,'(80("-"))') ; call goPr
  431. write(gol,'("ERROR: 2d sectors do not equal total number:",i4," /= ",i4," !")') seccount2d, bc_2dsec ; call goErr
  432. write(gol,'(80("-"))') ; call goPr
  433. status=1; return
  434. end if
  435. if( seccount3d /= bc_3dsec ) then
  436. write(gol,'(80("-"))') ; call goPr
  437. write(gol,'("ERROR: 3d sectors do not equal total number:",i4," /= ",i4," !")') seccount3d, bc_3dsec ; call goErr
  438. write(gol,'(80("-"))') ; call goPr
  439. status=1; return
  440. end if
  441. ! ok
  442. status = 0
  443. END SUBROUTINE EMISSION_BC_DECLARE
  444. !EOC
  445. END MODULE EMISSION_BC