emission_co2.F90 18 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578
  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_CO2
  14. !
  15. ! !DESCRIPTION: Hold data and methods for CO2 emissions.
  16. !\\
  17. !\\
  18. ! !INTERFACE:
  19. !
  20. MODULE EMISSION_CO2
  21. !
  22. ! !USES:
  23. !
  24. use GO, only : gol, goErr, goPr
  25. use dims, only : nregions, idate, okdebug
  26. use global_types, only : emis_data, d3_data
  27. use emission_read, only : used_providers, has_emis
  28. use tm5_distgrid, only : dgrid, get_distgrid, scatter
  29. use partools, only : isRoot, par_broadcast
  30. implicit none
  31. private
  32. !
  33. ! !PUBLIC MEMBER FUNCTIONS:
  34. !
  35. public :: Emission_CO2_Init ! allocate dataset
  36. public :: Emission_CO2_Done ! deallocate dataset
  37. public :: Emission_CO2_Declare ! read monthly input
  38. public :: Emission_CO2_Apply ! distribute & add emissions to tracer array
  39. !
  40. ! !PRIVATE DATA MEMBERS:
  41. !
  42. character(len=*), parameter :: mname = 'emission_co2'
  43. type( emis_data ), dimension(:,:), allocatable :: co2_emis_2d
  44. type( d3_data ), dimension(:,:), allocatable :: co2_emis_3d
  45. logical, allocatable :: has_data_3d(:), has_data_2d(:)
  46. integer :: co2_2dsec, co2_3dsec
  47. !
  48. ! !REVISION HISTORY:
  49. ! 1 Oct 2010 - Achim Strunk - revamped for AR5
  50. ! 26 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  51. ! 14 May 2014 - T. van Noije - created CO2 version from CO version
  52. ! to be done: convert CMIP5 CO2 input files
  53. ! for emissions from fossil fuel use and land use
  54. ! into the same format as for the other trace species
  55. ! 23 March 2018 - T. van Noije - included CMIP6 anthropogenic emissions from CEDS
  56. !
  57. ! !REMARKS:
  58. !
  59. !EOP
  60. !------------------------------------------------------------------------
  61. CONTAINS
  62. !--------------------------------------------------------------------------
  63. ! TM5 !
  64. !--------------------------------------------------------------------------
  65. !BOP
  66. !
  67. ! !IROUTINE: EMISSION_CO2_INIT
  68. !
  69. ! !DESCRIPTION: Allocate memory to handle the emissions.
  70. !\\
  71. !\\
  72. ! !INTERFACE:
  73. !
  74. SUBROUTINE EMISSION_CO2_INIT( status )
  75. !
  76. ! !USES:
  77. !
  78. use dims, only : lm
  79. use emission_read, only : providers_def, numb_providers
  80. !
  81. ! !OUTPUT PARAMETERS:
  82. !
  83. integer, intent(out) :: status
  84. !
  85. ! !REVISION HISTORY:
  86. ! 1 Oct 2010 - Achim Strunk - v0
  87. ! 26 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  88. !
  89. !EOP
  90. !------------------------------------------------------------------------
  91. !BOC
  92. character(len=*), parameter :: rname = mname//'/Emission_CO2_Init'
  93. integer :: region
  94. integer :: imr, jmr, lmr, lsec, lprov, i1, i2, j1, j2
  95. ! --- begin --------------------------------------
  96. status = 0
  97. if(.not. has_emis) return
  98. ! nb of sectors
  99. co2_2dsec = 0
  100. co2_3dsec = 0
  101. do lprov = 1, numb_providers
  102. if (count(used_providers.eq.providers_def(lprov)%name)/=0) then
  103. co2_2dsec = co2_2dsec + providers_def(lprov)%nsect2d
  104. co2_3dsec = co2_3dsec + providers_def(lprov)%nsect3d
  105. endif
  106. enddo
  107. allocate( co2_emis_2d( nregions, co2_2dsec ) )
  108. allocate( co2_emis_3d( nregions, co2_3dsec ) )
  109. allocate( has_data_2d(co2_2dsec)) ; has_data_2d=.false.
  110. allocate( has_data_3d(co2_3dsec)) ; has_data_3d=.false.
  111. ! allocate information arrays (2d and 3d)
  112. do region=1,nregions
  113. CALL GET_DISTGRID( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  114. lmr = lm(region)
  115. do lsec=1,co2_2dsec
  116. allocate( co2_emis_2d(region,lsec)%surf(i1:i2,j1:j2) )
  117. end do
  118. do lsec=1,co2_3dsec
  119. allocate( co2_emis_3d(region,lsec)%d3(i1:i2,j1:j2,lmr) )
  120. end do
  121. enddo
  122. ! ok
  123. status = 0
  124. END SUBROUTINE EMISSION_CO2_INIT
  125. !EOC
  126. !--------------------------------------------------------------------------
  127. ! TM5 !
  128. !--------------------------------------------------------------------------
  129. !BOP
  130. !
  131. ! !IROUTINE: EMISSION_CO2_DONE
  132. !
  133. ! !DESCRIPTION: Free memory after handling of the emissions.
  134. !\\
  135. !\\
  136. ! !INTERFACE:
  137. !
  138. SUBROUTINE EMISSION_CO2_DONE( status )
  139. !
  140. ! !OUTPUT PARAMETERS:
  141. !
  142. integer, intent(out) :: status
  143. !
  144. ! !REVISION HISTORY:
  145. ! 1 Oct 2010 - Achim Strunk - v0
  146. !
  147. !EOP
  148. !------------------------------------------------------------------------
  149. !BOC
  150. character(len=*), parameter :: rname = mname//'/Emission_CO2_Done'
  151. integer :: region, lsec
  152. ! --- begin --------------------------------------
  153. status = 0
  154. if(.not. has_emis) return
  155. do region = 1, nregions
  156. do lsec=1,co2_2dsec
  157. deallocate( co2_emis_2d(region,lsec)%surf )
  158. end do
  159. do lsec=1,co2_3dsec
  160. deallocate( co2_emis_3d(region,lsec)%d3 )
  161. end do
  162. end do
  163. deallocate( co2_emis_2d )
  164. deallocate( co2_emis_3d )
  165. deallocate( has_data_2d, has_data_3d)
  166. ! ok
  167. status = 0
  168. END SUBROUTINE EMISSION_CO2_DONE
  169. !EOC
  170. !--------------------------------------------------------------------------
  171. ! TM5 !
  172. !--------------------------------------------------------------------------
  173. !BOP
  174. !
  175. ! !IROUTINE: EMISSION_CO2_DECLARE
  176. !
  177. ! !DESCRIPTION: Opens, reads and evaluates input files (per month).
  178. ! Provides emissions on 2d/3d-arrays which are then added
  179. ! to mixing ratios in routine *apply.
  180. !\\
  181. !\\
  182. ! !INTERFACE:
  183. !
  184. SUBROUTINE EMISSION_CO2_DECLARE( status )
  185. !
  186. ! !USES:
  187. !
  188. use toolbox, only : coarsen_emission
  189. use dims, only : im, jm, lm, idate, sec_month, nlon360, nlat180, iglbsfc
  190. use chem_param, only : xmco2
  191. use emission_data, only : msg_emis
  192. ! ---------------- AR5 - ETC. --------------------
  193. use emission_data, only : emis_input_year_co2
  194. use emission_read, only : emission_ar5_regrid_aircraft
  195. use emission_read, only : emission_cmip6_ReadSector
  196. use emission_read, only : emission_ar5_ReadCO2
  197. use emission_read, only : sectors_def, numb_sectors
  198. use emission_read, only : ar5_dim_3ddata
  199. !
  200. ! !OUTPUT PARAMETERS:
  201. !
  202. integer, intent(out) :: status
  203. !
  204. ! !REVISION HISTORY:
  205. ! 1 Oct 2010 - Achim Strunk - adapted for AR5
  206. ! 26 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  207. !
  208. ! !REMARKS:
  209. !
  210. !EOP
  211. !------------------------------------------------------------------------
  212. !BOC
  213. character(len=*), parameter :: rname = mname//'/emission_co2_declare'
  214. integer :: region, hasData
  215. integer, parameter :: add_field=0
  216. integer, parameter :: amonth=2
  217. integer :: imr, jmr, lmr, lsec, i1, i2, j1, j2
  218. ! AR5
  219. real,dimension(:,:,:), allocatable :: field3d, field3d2
  220. type(d3_data), dimension(nregions) :: emis3d, work, work3d
  221. type(emis_data) :: wrk2D(nregions)
  222. integer :: seccount2d, seccount3d
  223. ! --- begin -----------------------------------------
  224. status = 0
  225. if(.not. has_emis) return
  226. write(gol,'(" EMISS-INFO ------------- read CO2 emissions -------------")'); call goPr
  227. do region = 1, nregions
  228. do lsec=1,co2_2dsec
  229. co2_emis_2d(region,lsec)%surf = 0.0
  230. end do
  231. do lsec=1,co2_3dsec
  232. co2_emis_3d(region,lsec)%d3 = 0.0
  233. end do
  234. CALL GET_DISTGRID( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  235. lmr = lm(region)
  236. allocate( work3d(region)%d3 (i1:i2,j1:j2, ar5_dim_3ddata) ) ; work3d(region)%d3 = 0.0
  237. allocate( emis3d(region)%d3 (i1:i2,j1:j2, lmr ) ) ; emis3d(region)%d3 = 0.0
  238. end do
  239. ! global arrays for coarsening
  240. do region = 1, nregions
  241. if (isRoot)then
  242. allocate(work(region)%d3(im(region),jm(region),ar5_dim_3ddata))
  243. else
  244. allocate(work(region)%d3(1,1,1))
  245. end if
  246. enddo
  247. do region = 1, nregions
  248. wrk2D(region)%surf => work(region)%d3(:,:,1)
  249. end do
  250. ! --------------------------------
  251. ! do a loop over available sectors
  252. ! --------------------------------
  253. ! count 2d and 3d sectors
  254. seccount2d = 0
  255. seccount3d = 0
  256. ! always allocate here 3d data set (for 2d sectors it will be filled in first layer only)
  257. if (isRoot) then
  258. allocate( field3d( nlon360, nlat180, ar5_dim_3ddata ) ) ; field3d = 0.0
  259. else
  260. allocate( field3d( 1, 1, 1 ) )
  261. end if
  262. sec : do lsec = 1, numb_sectors
  263. if (count(used_providers.eq.sectors_def(lsec)%prov).eq.0) cycle
  264. field3d = 0.0
  265. if( sectors_def(lsec)%f3d ) then
  266. seccount3d = seccount3d + 1
  267. else
  268. seccount2d = seccount2d + 1
  269. end if
  270. if (isRoot) then ! READ
  271. select case( trim(sectors_def(lsec)%prov) )
  272. case( 'CMIP6' )
  273. call emission_cmip6_ReadSector( 'CO2', emis_input_year_co2, idate(2), lsec, field3d, status )
  274. IF_NOTOK_RETURN(status=1;deallocate(field3d))
  275. case( 'AR5' )
  276. call emission_ar5_ReadCO2( 'CO2', emis_input_year_co2, idate(2), lsec, field3d, status )
  277. IF_NOTOK_RETURN(status=1;deallocate(field3d))
  278. case('DUMMY')
  279. case default
  280. write(gol,*) "Error in buidling list of providers USED_PROVIDERS"; call goErr
  281. status=1; TRACEBACK; return
  282. end select
  283. ! nothing found???
  284. if( sum(field3d) < 100.*TINY(1.0) ) then
  285. if (okdebug) then
  286. write(gol,'("EMISS-INFO - no CO2 emissions found for ",a," ",a," for month ",i2 )') &
  287. trim(sectors_def(lsec)%prov), trim(sectors_def(lsec)%name), idate(2) ; call goPr
  288. endif
  289. hasData=0
  290. else
  291. if (okdebug) then
  292. write(gol,'("EMISS-INFO - found CO2 emissions for ",a," ",a," for month ",i2 )') &
  293. trim(sectors_def(lsec)%prov), trim(sectors_def(lsec)%name), idate(2) ; call goPr
  294. endif
  295. ! scale from kg/s to kg/month
  296. field3d = field3d * sec_month ! kg / month
  297. hasData=1
  298. end if
  299. end if
  300. call Par_broadcast(hasData, status)
  301. IF_NOTOK_RETURN(status=1)
  302. if (hasData == 0) then
  303. cycle sec
  304. else
  305. if ( sectors_def(lsec)%f3d ) then
  306. has_data_3d(seccount3d)=.true.
  307. else
  308. has_data_2d(seccount2d)=.true.
  309. end if
  310. end if
  311. ! Distinguish 2d/3d sectors
  312. if( sectors_def(lsec)%f3d ) then
  313. ! ---------------------------------------
  314. ! 3d data (AIRCRAFT), available for CMIP6
  315. ! ---------------------------------------
  316. if (isRoot) then
  317. ! write some numbers
  318. call msg_emis( amonth, trim(sectors_def(lsec)%prov), sectors_def(lsec)%name, 'CO2', xmco2, sum(field3d) )
  319. ! distribute to work arrays in regions
  320. call Coarsen_Emission( 'CO2 '//trim(sectors_def(lsec)%name), nlon360, nlat180, ar5_dim_3ddata, &
  321. field3d, work, add_field, status )
  322. IF_NOTOK_RETURN(status=1)
  323. end if
  324. ! scatter, sum up on target array
  325. do region = 1, nregions
  326. call scatter(dgrid(region), work3d(region)%d3, work(region)%d3, 0, status)
  327. IF_NOTOK_RETURN( status=1 )
  328. CALL GET_DISTGRID( dgrid(region), I_STRT=i1, J_STRT=j1)
  329. ! aircraft data: regrid vertically to model layers
  330. call emission_ar5_regrid_aircraft( region, i1, j1, work3d(region)%d3, emis3d(region)%d3, status )
  331. IF_NOTOK_RETURN( status=1 )
  332. co2_emis_3d(region,seccount3d)%d3 = co2_emis_3d(region,seccount3d)%d3 + emis3d(region)%d3
  333. end do
  334. else ! ar5_sector is 2d
  335. ! ---------------------------
  336. ! 2d data
  337. ! ---------------------------
  338. if (isRoot) then ! print total & regrid
  339. call msg_emis( amonth, trim(sectors_def(lsec)%prov), sectors_def(lsec)%name, 'CO2', xmco2, sum(field3d(:,:,1)) )
  340. call coarsen_emission( 'CO2 '//sectors_def(lsec)%name, &
  341. nlon360, nlat180, field3d(:,:,1), wrk2D, add_field, status )
  342. IF_NOTOK_RETURN(status=1;deallocate(field3d))
  343. end if
  344. do region = 1, nregions
  345. call scatter(dgrid(region), co2_emis_2d(region,seccount2d)%surf, work(region)%d3(:,:,1), 0, status)
  346. IF_NOTOK_RETURN(status=1)
  347. end do
  348. endif
  349. end do sec ! sectors
  350. deallocate( field3d )
  351. do region = 1, nregions
  352. if (associated(wrk2D(region)%surf)) nullify(wrk2D(region)%surf)
  353. deallocate( work(region)%d3 )
  354. deallocate( work3d(region)%d3 )
  355. deallocate( emis3d(region)%d3 )
  356. end do
  357. ! check sectors found
  358. if( seccount2d /= co2_2dsec ) then
  359. write(gol,'(80("-"))') ; call goPr
  360. write(gol,'("ERROR: 2d sectors do not equal total number:",i4," /= ",i4," !")') seccount2d, co2_2dsec ; call goErr
  361. write(gol,'(80("-"))') ; call goPr
  362. status=1; return
  363. end if
  364. if( seccount3d /= co2_3dsec ) then
  365. write(gol,'(80("-"))') ; call goPr
  366. write(gol,'("ERROR: 3d sectors do not equal total number:",i4," /= ",i4," !")') seccount3d, co2_3dsec ; call goErr
  367. write(gol,'(80("-"))') ; call goPr
  368. status=1; return
  369. end if
  370. ! ok
  371. status = 0
  372. END SUBROUTINE EMISSION_CO2_DECLARE
  373. !EOC
  374. !--------------------------------------------------------------------------
  375. ! TM5 !
  376. !--------------------------------------------------------------------------
  377. !BOP
  378. !
  379. ! !IROUTINE: EMISSION_CO2_APPLY
  380. !
  381. ! !DESCRIPTION: Take monthly emissions, and
  382. ! - split them vertically
  383. ! - apply time splitting factors
  384. ! - add them to tracers (add_3d)
  385. !\\
  386. !\\
  387. ! !INTERFACE:
  388. !
  389. SUBROUTINE EMISSION_CO2_APPLY( region, status )
  390. !
  391. ! !USES:
  392. !
  393. use dims, only : itaur, nsrce, tref
  394. use dims, only : im, jm, lm
  395. use datetime, only : tau2date
  396. use emission_data, only : emission_vdist_by_sector
  397. use emission_data, only : do_add_3d
  398. use chem_param, only : ico2, xmco2
  399. use emission_read, only : sectors_def, numb_sectors
  400. !
  401. ! !INPUT PARAMETERS:
  402. !
  403. integer, intent(in) :: region
  404. !
  405. ! !OUTPUT PARAMETERS:
  406. !
  407. integer, intent(out) :: status
  408. !
  409. ! !REVISION HISTORY:
  410. ! 1 Oct 2010 - Achim Strunk - AR5
  411. ! 26 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  412. !
  413. !EOP
  414. !------------------------------------------------------------------------
  415. !BOC
  416. character(len=*), parameter :: rname = mname//'/emission_co2_apply'
  417. integer, dimension(6) :: idater
  418. real :: dtime, fraction
  419. integer :: imr, jmr, lmr, lsec, i1, i2, j1, j2
  420. integer :: seccount2d, seccount3d
  421. type(d3_data) :: emis3d
  422. ! --- begin -----------------------------
  423. status = 0
  424. if(.not. has_emis) return
  425. if( okdebug ) then
  426. write(gol,*) 'start of emission_co2_apply'; call goPr
  427. end if
  428. call tau2date(itaur(region),idater)
  429. dtime=float(nsrce)/(2*tref(region)) !emissions are added in two steps...XYZECCEZYX.
  430. if(okdebug) then
  431. write(gol,*)'emission_co2_apply in region ',region,' at date: ',idater, ' with time step:', dtime
  432. call goPr
  433. end if
  434. ! get a working structure for 3d emissions
  435. call get_distgrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  436. allocate( emis3d%d3(i1:i2,j1:j2,lm(region)) ) ; emis3d%d3 = 0.0
  437. ! count 2d and 3d sectors
  438. seccount2d = 0
  439. seccount3d = 0
  440. ! cycle over sectors
  441. do lsec = 1, numb_sectors
  442. if (count(used_providers.eq.sectors_def(lsec)%prov).eq.0) cycle
  443. ! default: no additional splitting
  444. fraction = 1.0
  445. ! distinguish between 2d/3d sectors
  446. if( sectors_def(lsec)%f3d ) then
  447. seccount3d = seccount3d + 1
  448. if (.not.has_data_3d(seccount3d)) cycle
  449. emis3d%d3 = co2_emis_3d(region,seccount3d)%d3
  450. else
  451. seccount2d = seccount2d + 1
  452. if (.not.has_data_2d(seccount2d)) cycle
  453. emis3d%d3 = 0.0
  454. ! vertically distribute according to sector
  455. call emission_vdist_by_sector( sectors_def(lsec)%vdisttype, 'CO2', region, co2_emis_2d(region,seccount2d), emis3d, status )
  456. IF_NOTOK_RETURN(status=1;deallocate(emis3d%d3))
  457. end if
  458. ! add dataset according to sector and category
  459. call do_add_3d( region, ico2, i1, j1, emis3d%d3, xmco2, xmco2, status, fraction )
  460. IF_NOTOK_RETURN(status=1)
  461. end do
  462. deallocate( emis3d%d3 )
  463. if(okdebug) then
  464. write(gol,*) 'end of emission_co2_apply'; call goPr
  465. end if
  466. ! OK
  467. status = 0
  468. END SUBROUTINE EMISSION_CO2_APPLY
  469. !EOC
  470. END MODULE EMISSION_CO2