emission_isop.F90 29 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889
  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_ISOP
  14. !
  15. ! !DESCRIPTION: data and methods for Isoprene emissions.
  16. !\\
  17. !\\
  18. ! !INTERFACE:
  19. !
  20. MODULE EMISSION_ISOP
  21. !
  22. ! !USES:
  23. !
  24. use GO, only : gol, goPr, goErr, goBug
  25. use tm5_distgrid, only : dgrid, get_distgrid, scatter, gather
  26. use partools, only : isRoot, par_broadcast
  27. use dims, only : nregions, idate, okdebug
  28. use global_types, only : emis_data, d3_data
  29. use global_types, only : isop_data
  30. use emission_read, only : used_providers_isop, has_isop_emis
  31. IMPLICIT NONE
  32. PRIVATE
  33. !
  34. ! !PUBLIC MEMBER FUNCTIONS:
  35. !
  36. public :: Emission_isop_Init
  37. public :: Emission_isop_Done
  38. public :: emission_isop_Declare
  39. public :: Emission_isop_Apply
  40. !
  41. ! !PRIVATE DATA MEMBERS:
  42. !
  43. character(len=*), parameter :: mname = 'emission_isop'
  44. !isoprene emission distribution function
  45. type(isop_data),dimension(nregions),target :: isop_dat
  46. !flags the daily calculation of isoprene distribution func.
  47. integer,dimension(nregions) :: day_isop
  48. type( emis_data ), dimension(:,:), allocatable :: isop_emis_2d
  49. type( d3_data ), dimension(:,:), allocatable :: isop_emis_3d
  50. integer :: j_start, j_end ! indices for tropics
  51. integer :: isop_3dsec, isop_2dsec
  52. logical, allocatable :: has_data_3d(:), has_data_2d(:)
  53. !
  54. ! !REVISION HISTORY:
  55. ! 1 Oct 2010 - Achim Strunk - overhaul for AR5
  56. ! 28 Jun 2012 - Ph. Le Sager - adapted for lon-lat MPI domain decomposition
  57. !
  58. ! !REMARKS:
  59. !
  60. !EOP
  61. !------------------------------------------------------------------------
  62. contains
  63. !--------------------------------------------------------------------------
  64. ! TM5 !
  65. !--------------------------------------------------------------------------
  66. !BOP
  67. !
  68. ! !IROUTINE: EMISSION_ISOP_INIT
  69. !
  70. ! !DESCRIPTION: Allocate memory
  71. !\\
  72. !\\
  73. ! !INTERFACE:
  74. !
  75. SUBROUTINE EMISSION_ISOP_INIT( status )
  76. !
  77. ! !USES:
  78. !
  79. use dims, only : ndyn_max, tref, im, jm, lm, idate, nlon360, nlat180
  80. use dims, only : sec_month, dy, yref, ybeg
  81. use global_data, only : rcfile
  82. use emission_read, only : providers_def, numb_providers, sectors_def
  83. !
  84. ! !OUTPUT PARAMETERS:
  85. !
  86. integer, intent(out) :: status
  87. !
  88. ! !REVISION HISTORY:
  89. ! 1 Oct 2010 - Achim Strunk - adapted for AR5
  90. ! 28 Jun 2012 - Ph. Le Sager - adapted for lon-lat MPI domain decomposition
  91. !
  92. ! !REMARKS:
  93. !
  94. !EOP
  95. !------------------------------------------------------------------------
  96. !BOC
  97. character(len=*), parameter :: rname = mname//'/emission_isop_init'
  98. integer :: region, i1, i2, j1, j2
  99. integer :: lmr, lsec, ntim, lprov
  100. real :: dtime, dy1
  101. ! --- begin -----------------------------------------
  102. status = 0
  103. if(.not. has_isop_emis) return
  104. isop_2dsec = 0
  105. isop_3dsec = 0
  106. do lprov = 1, numb_providers
  107. if (count(used_providers_isop == providers_def(lprov)%name)/=0) then
  108. ! limit AR5 to the 2D biomass burning sector
  109. if ( trim(providers_def(lprov)%name) == 'AR5' ) then
  110. isop_2dsec = isop_2dsec + count( sectors_def%prov == 'AR5 ' &
  111. .and. sectors_def%catname == 'biomassburning')
  112. else
  113. ! use all sectors
  114. isop_2dsec = isop_2dsec + providers_def(lprov)%nsect2d
  115. isop_3dsec = isop_3dsec + providers_def(lprov)%nsect3d
  116. end if
  117. endif
  118. enddo
  119. allocate( isop_emis_2d( nregions, isop_2dsec ) )
  120. allocate( isop_emis_3d( nregions, isop_3dsec ) )
  121. allocate( has_data_2d(isop_2dsec)) ; has_data_2d=.false.
  122. allocate( has_data_3d(isop_3dsec)) ; has_data_3d=.false.
  123. ! allocate information arrays (2d and 3d)
  124. do region=1,nregions
  125. CALL GET_DISTGRID( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  126. lmr = lm(region)
  127. do lsec=1,isop_2dsec
  128. allocate( isop_emis_2d(region,lsec)%surf(i1:i2, j1:j2) )
  129. end do
  130. do lsec=1,isop_3dsec
  131. allocate( isop_emis_3d(region,lsec)%d3(i1:i2, j1:j2,lmr) )
  132. end do
  133. dtime=float(ndyn_max)/(2*tref(region)) ! timestep emissions
  134. ntim=86400/nint(dtime) ! number of timesteps in 24 hours for this region
  135. allocate(isop_dat(region)%scalef_isop(ntim,j1:j2)) ! allocate enough memory!
  136. enddo
  137. ! find indices of tropics for splitting emissions
  138. dy1=dy/yref(1)
  139. j_start = floor((-20. - ybeg(1))/dy1) + 1
  140. j_end = floor(( 20. - ybeg(1))/dy1) + 1
  141. ! ok
  142. status = 0
  143. end subroutine Emission_isop_Init
  144. !EOC
  145. !--------------------------------------------------------------------------
  146. ! TM5 !
  147. !--------------------------------------------------------------------------
  148. !BOP
  149. !
  150. ! !IROUTINE: EMISSION_ISOP_DONE
  151. !
  152. ! !DESCRIPTION: Free memory
  153. !\\
  154. !\\
  155. ! !INTERFACE:
  156. !
  157. subroutine Emission_isop_Done( status )
  158. !
  159. ! !OUTPUT PARAMETERS:
  160. !
  161. integer, intent(out) :: status
  162. !
  163. ! !REVISION HISTORY:
  164. ! 1 Oct 2010 - Achim Strunk - adapted to new structures
  165. ! 28 Jun 2012 - Ph. Le Sager - adapted for lon-lat MPI domain decomposition
  166. !
  167. !EOP
  168. !------------------------------------------------------------------------
  169. !BOC
  170. character(len=*), parameter :: rname = mname//'/Emission_isop_Done'
  171. integer :: region, lsec
  172. ! --- begin --------------------------------------
  173. status = 0
  174. if(.not. has_isop_emis) return
  175. do region = 1, nregions
  176. do lsec=1,isop_2dsec
  177. deallocate( isop_emis_2d(region,lsec)%surf )
  178. end do
  179. do lsec=1,isop_3dsec
  180. deallocate( isop_emis_3d(region,lsec)%d3 )
  181. end do
  182. deallocate(isop_dat(region)%scalef_isop )
  183. end do
  184. deallocate( isop_emis_2d, isop_emis_3d )
  185. deallocate( has_data_2d, has_data_3d )
  186. status = 0
  187. end subroutine Emission_isop_Done
  188. !EOC
  189. !--------------------------------------------------------------------------
  190. ! TM5 !
  191. !--------------------------------------------------------------------------
  192. !BOP
  193. !
  194. ! !IROUTINE: EMISSION_ISOP_DECLARE
  195. !
  196. ! !DESCRIPTION: Opens, reads and evaluates input files (per month).
  197. ! Provides emissions on 2d/3d-arrays which are then added
  198. ! to mixing ratios in routine *apply.
  199. !\\
  200. !\\
  201. ! !INTERFACE:
  202. !
  203. SUBROUTINE EMISSION_ISOP_DECLARE( status )
  204. !
  205. ! !USES:
  206. !
  207. use toolbox, only : coarsen_emission
  208. use dims, only : im, jm, lm, idate, sec_month, nlon360, nlat180, iglbsfc
  209. use chem_param, only : xmisop
  210. use emission_data, only : msg_emis, LAR5BMB, LMEGAN
  211. ! ---------------- AR5 - MACC --------------------
  212. use emission_data, only : emis_input_year
  213. use emission_data, only : emis_input_dir_mac
  214. use emission_data, only : emis_input_dir_megan
  215. use emission_data, only : emis_input_dir_retro
  216. use emission_data, only : emis_input_dir_gfed
  217. use emission_read, only : emission_ar5_regrid_aircraft
  218. use emission_read, only : emission_ar5_ReadSector
  219. use emission_read, only : emission_macc_ReadSector
  220. use emission_read, only : emission_megan_ReadSector
  221. use emission_read, only : emission_gfed_ReadSector
  222. use emission_read, only : emission_retro_ReadSector
  223. use emission_read, only : sectors_def, numb_sectors
  224. use emission_read, only : ar5_dim_3ddata
  225. !
  226. ! !OUTPUT PARAMETERS:
  227. !
  228. integer, intent(out) :: status
  229. !
  230. ! !REVISION HISTORY:
  231. ! 1 Oct 2010 - Achim Strunk - adapted for AR5
  232. !
  233. !EOP
  234. !------------------------------------------------------------------------
  235. !BOC
  236. character(len=*), parameter :: rname = mname//'/emission_isop_declare'
  237. integer :: region, hasData
  238. integer, parameter :: add_field=0
  239. integer, parameter :: amonth=2
  240. integer :: imr, jmr, lmr, lsec
  241. ! AR5
  242. real,dimension(:,:,:),allocatable :: field3d, field3d2
  243. type(d3_data) :: emis3d, work(nregions)
  244. type(emis_data) :: wrk2D(nregions)
  245. integer :: seccount2d, seccount3d
  246. ! --- begin -----------------------------------------
  247. status = 0
  248. if(.not. has_isop_emis) return
  249. write(gol,'(" EMISS-INFO ------------- read ISOPRENE emissions -------------")'); call goPr
  250. ! flag calculation of daily isoprene emission distribution
  251. day_isop(1:nregions) = -1
  252. do region = 1, nregions
  253. do lsec=1,isop_2dsec
  254. isop_emis_2d(region,lsec)%surf = 0.0
  255. end do
  256. do lsec=1,isop_3dsec
  257. isop_emis_3d(region,lsec)%d3 = 0.0
  258. end do
  259. end do
  260. ! global arrays for coarsening
  261. do region = 1, nregions
  262. if (isRoot)then
  263. allocate(work(region)%d3(im(region),jm(region),lm(region)))
  264. else
  265. allocate(work(region)%d3(1,1,1))
  266. end if
  267. enddo
  268. do region = 1, nregions
  269. wrk2D(region)%surf => work(region)%d3(:,:,1)
  270. end do
  271. ! --------------------------------
  272. ! do a loop over available sectors
  273. ! --------------------------------
  274. ! count 2d and 3d sectors
  275. seccount2d = 0
  276. seccount3d = 0
  277. ! always allocate here 3d data set (for 2d sectors it will be filled in first layer only)
  278. if (isRoot) then
  279. allocate( field3d( nlon360, nlat180, ar5_dim_3ddata ) ) ; field3d = 0.0
  280. else
  281. allocate( field3d( 1, 1, 1 ) )
  282. end if
  283. sec : do lsec = 1, numb_sectors
  284. ! screen out unused providers
  285. if (count(used_providers_isop.eq.sectors_def(lsec)%prov).eq.0) cycle
  286. ! screen out AR5 non-fires
  287. if ( sectors_def(lsec)%prov == 'AR5 ' .and. sectors_def(lsec)%catname /= 'biomassburning') cycle
  288. field3d = 0.0
  289. if( sectors_def(lsec)%f3d ) then
  290. seccount3d = seccount3d + 1
  291. else
  292. seccount2d = seccount2d + 1
  293. end if
  294. if (isRoot) then ! READ
  295. select case( trim(sectors_def(lsec)%prov) )
  296. case( 'AR5' )
  297. ! here only if we select AR5, and if sector is BMB
  298. if (LAR5BMB) then
  299. call emission_ar5_ReadSector( 'isoprene', emis_input_year, idate(2), lsec, field3d, status )
  300. IF_NOTOK_RETURN(status=1)
  301. endif
  302. case( 'MACC' )
  303. ! skip if MEGAN is used, screen out sectors w/o isop else
  304. if( (trim(sectors_def(lsec)%name) .eq. 'emiss_bio') .and. (.not. LMEGAN) ) then
  305. call emission_macc_ReadSector( emis_input_dir_mac, 'ISOPRENE', emis_input_year, idate(2), &
  306. '0.5x0.5_kg.nc', sectors_def(lsec)%name, 'kg / s', field3d, status )
  307. IF_NOTOK_RETURN(status=1)
  308. endif
  309. case('GFEDv3')
  310. call emission_gfed_ReadSector( emis_input_dir_gfed, 'isoprene', emis_input_year, idate(2), &
  311. sectors_def(lsec)%name, 'kg / s', field3d(:,:,1), status )
  312. IF_NOTOK_RETURN(status=1)
  313. case('RETRO')
  314. call emission_retro_ReadSector( emis_input_dir_retro, 'ISOPRENE', emis_input_year, idate(2), &
  315. sectors_def(lsec)%name, 'kg / s', field3d(:,:,1), status )
  316. IF_NOTOK_RETURN(status=1)
  317. case('MEGAN')
  318. call emission_megan_ReadSector( emis_input_dir_megan, 'isoprene', emis_input_year, idate(2), &
  319. sectors_def(lsec)%name, 'kg / s', field3d(:,:,1), status )
  320. IF_NOTOK_RETURN(status=1)
  321. case('DUMMY')
  322. case default
  323. write(gol,*) "Error in buidling list of providers USED_PROVIDERS_ISOP" ; call goErr
  324. status=1; TRACEBACK; return
  325. end select
  326. ! nothing found???
  327. if( sum(field3d) < 100.*TINY(1.0) ) then
  328. if (okdebug) then
  329. write(gol,'("EMISS-INFO - no ISOP emissions found for ",a," ",a," for month ",i2 )') &
  330. trim(sectors_def(lsec)%prov), trim(sectors_def(lsec)%name), idate(2) ; call goPr
  331. endif
  332. hasData=0
  333. else
  334. if (okdebug) then
  335. write(gol,'("EMISS-INFO - found ISOP emissions for ",a," ",a," for month ",i2 )') &
  336. trim(sectors_def(lsec)%prov), trim(sectors_def(lsec)%name), idate(2) ; call goPr
  337. endif
  338. ! scale from kg/s to kg/month
  339. field3d = field3d * sec_month ! kg / month
  340. hasData=1
  341. end if
  342. end if
  343. call Par_broadcast(hasData, status)
  344. IF_NOTOK_RETURN(status=1)
  345. if (hasData == 0) then
  346. cycle sec
  347. else
  348. if ( sectors_def(lsec)%f3d ) then
  349. has_data_3d(seccount3d)=.true.
  350. else
  351. has_data_2d(seccount2d)=.true.
  352. end if
  353. end if
  354. ! Distinguish 2d/3d sectors
  355. if( sectors_def(lsec)%f3d ) then
  356. write(gol,'("EMISS-ERROR - Unexpected 3D data: Uncomment code below ")'); call goErr
  357. status=1; TRACEBACK; return
  358. ! ---------------------------
  359. ! 3d data (AIRCRAFT)
  360. ! ---------------------------
  361. ! if (isRoot) then ! regrid
  362. ! ! helper array for regridding
  363. ! allocate( field3d2( nlon360,nlat180,lm(1) ) ) ; field3d2 = 0.0
  364. ! ! aircraft data: regrid vertically to model layers
  365. ! call emission_ar5_regrid_aircraft( iglbsfc, field3d, nlon360, nlat180, ar5_dim_3ddata, lm(1), field3d2, status )
  366. ! IF_NOTOK_RETURN(status=1;deallocate(field3d,field3d2))
  367. ! ! write some numbers
  368. ! call msg_emis( amonth, 'aircraft. mass month', 'ISOP', xmisop, sum(field3d2) )
  369. ! ! distribute to isop_emis in regions
  370. ! call Coarsen_Emission( 'ISOP '//trim(sectors_def(lsec)%name), nlon360, nlat180, lm(1), &
  371. ! field3d2, work, add_field, status )
  372. ! IF_NOTOK_RETURN(status=1;deallocate(field3d,field3d2))
  373. ! deallocate( field3d2 )
  374. ! end if
  375. ! do region = 1, nregions
  376. ! call scatter(dgrid(region), isop_emis_3d(region,seccount3d)%d3, work(region)%d3, 0, status)
  377. ! IF_NOTOK_RETURN(status=1)
  378. ! end do
  379. else
  380. ! ---------------------------
  381. ! 2d data (Anthropogenic, Ships, Biomassburning)
  382. ! ---------------------------
  383. if (isRoot) then ! print total & regrid
  384. call msg_emis( amonth, trim(sectors_def(lsec)%prov), sectors_def(lsec)%name, 'ISOP', xmisop, sum(field3d(:,:,1)) )
  385. call coarsen_emission( 'ISOP '//sectors_def(lsec)%name, nlon360, nlat180, field3d(:,:,1), wrk2D, add_field, status )
  386. IF_NOTOK_RETURN(status=1)
  387. end if
  388. do region = 1, nregions
  389. call scatter(dgrid(region), isop_emis_2d(region,seccount2d)%surf, work(region)%d3(:,:,1), 0, status)
  390. IF_NOTOK_RETURN(status=1)
  391. end do
  392. end if
  393. end do sec ! sectors
  394. deallocate( field3d )
  395. do region = 1, nregions
  396. if (associated(wrk2D(region)%surf)) nullify(wrk2D(region)%surf)
  397. deallocate( work(region)%d3 )
  398. end do
  399. status = 0
  400. END SUBROUTINE EMISSION_ISOP_DECLARE
  401. !EOC
  402. !--------------------------------------------------------------------------
  403. ! TM5 !
  404. !--------------------------------------------------------------------------
  405. !BOP
  406. !
  407. ! !IROUTINE: EMISSION_ISOP_APPLY
  408. !
  409. ! !DESCRIPTION: Take monthly emissions, and
  410. ! - split them vertically
  411. ! - apply time splitting factors
  412. ! - add them up (add_isop)
  413. !\\
  414. !\\
  415. ! !INTERFACE:
  416. !
  417. SUBROUTINE EMISSION_ISOP_APPLY( region, status )
  418. !
  419. ! !USES:
  420. !
  421. use dims, only : itaur, nsrce, tref
  422. use dims, only : im, jm, lm, mlen, ndyn_max
  423. use dims, only : yref, dy, ybeg
  424. use datetime, only : tau2date, get_day
  425. use emission_data, only : emission_vdist_by_sector
  426. use chem_param, only : iisop, xmisop
  427. use emission_data, only : do_add_3d
  428. use emission_read, only : sectors_def, numb_sectors
  429. use tracer_data, only : tracer_print
  430. !
  431. ! !INPUT PARAMETERS:
  432. !
  433. integer, intent(in) :: region
  434. !
  435. ! !OUTPUT PARAMETERS:
  436. !
  437. integer, intent(out) :: status
  438. !
  439. ! !REVISION HISTORY:
  440. ! 1 Oct 2010 - Achim Strunk - adapted for AR5
  441. ! 27 Apr 2012 - Ph. Le Sager - adapted for lon-lat MPI domain decomposition
  442. !
  443. ! !REMARKS:
  444. !
  445. !EOP
  446. !------------------------------------------------------------------------
  447. !BOC
  448. character(len=*), parameter :: rname = mname//'/emission_isop_apply'
  449. integer, dimension(6) :: idater
  450. real :: dtime, fraction
  451. integer :: imr, jmr, lmr, lsec
  452. integer :: seccount2d, seccount3d
  453. type(d3_data) :: emis3d
  454. real :: dlatr
  455. integer :: day, ntim, i1, i2, j1, j2, j01, j02
  456. ! --- begin -----------------------------------------
  457. status = 0
  458. if(.not. has_isop_emis) return
  459. if( okdebug ) then
  460. write(gol,*) 'start of emission_apply_isop'; call goPr
  461. end if
  462. ! --- WHERE, WHEN
  463. CALL TAU2DATE( itaur(region), idater)
  464. CALL GET_DISTGRID( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  465. day = GET_DAY(idater(2),idater(3),mlen)
  466. dtime = float(nsrce)/(2*tref(region)) !emissions are added in two steps...XYZECCEZYX.
  467. if(okdebug) then
  468. write(gol,*)'emission_isop_apply in region ',region,' at date: ',idater, ' with time step:', dtime
  469. call goPr
  470. end if
  471. ! --- DIURNAL CYCLE
  472. if ( day /= day_isop(region) ) then
  473. dlatr = dy/yref(region) ! should be the same as lli%dlat_deg
  474. dtime=float(ndyn_max)/(2*tref(region)) ! timestep emissions
  475. ntim=86400/nint(dtime) ! number of timesteps in 24 hours.
  476. if ( okdebug ) then
  477. write (gol,*) 'day',day,'ntim',ntim,'jm',jm(region),'ybeg',&
  478. ybeg(region),'dlatr',dlatr,'sum(mlen)',sum(mlen),nsrce,dtime
  479. call goPr
  480. end if
  481. ! NOTE : latitude_start must be an integer. This is ok as long as
  482. ! the regions ybeg are integer.
  483. call scale_isop(day, ntim, j1, isop_dat(region)%scalef_isop, ybeg(region), dlatr, sum(mlen))
  484. day_isop(region) = day !avoid recalculation during this day!
  485. endif
  486. ! --- ADD EMISSIONS
  487. ! get a working structure for 3d emissions
  488. allocate( emis3d%d3(i1:i2,j1:j2,lm(region)) ) ; emis3d%d3 = 0.0
  489. ! count 2d and 3d sectors
  490. seccount2d = 0
  491. seccount3d = 0
  492. ! cycle over sectors
  493. do lsec = 1, numb_sectors
  494. ! screen out unused providers
  495. if (count(used_providers_isop.eq.sectors_def(lsec)%prov).eq.0) cycle
  496. ! screen out AR5 non-fires
  497. if ( sectors_def(lsec)%prov == 'AR5 ' .and. sectors_def(lsec)%catname /= 'biomassburning') cycle
  498. ! default: no additional splitting
  499. fraction = 1.0
  500. ! ----------------------------------------------------------------------------------------
  501. ! distinguish here between sectors and whether they should have additional splitting
  502. ! if( sectors_def(lsec)%catname == 'biomassburning' ) fraction = fraction * bb_frac etc...
  503. ! ----------------------------------------------------------------------------------------
  504. ! distinguish between 2d/3d sectors
  505. if( sectors_def(lsec)%f3d ) then
  506. seccount3d = seccount3d + 1
  507. if (.not.has_data_3d(seccount3d)) cycle
  508. emis3d%d3 = isop_emis_3d(region,seccount3d)%d3
  509. else
  510. seccount2d = seccount2d + 1
  511. if (.not.has_data_2d(seccount2d)) cycle
  512. emis3d%d3 = 0.0
  513. ! vertically distribute according to sector
  514. call emission_vdist_by_sector( sectors_def(lsec)%vdisttype, 'ISOP', region, isop_emis_2d(region,seccount2d), &
  515. emis3d, status)
  516. IF_NOTOK_RETURN(status=1)
  517. ! is tile in tropics
  518. if ((j_end .lt. j1 ).or.(j_start .gt. j2) ) then
  519. continue
  520. else
  521. ! limit range
  522. j02=j_end
  523. j01=j_start
  524. if (j_end .gt. j2 ) j02 = j2
  525. if (j_start .lt. j1 ) j01 = j1
  526. emis3d%d3(:,j01:j02,1)=0.5*emis3d%d3(:,j01:j02,1)
  527. emis3d%d3(:,j01:j02,2)=emis3d%d3(:,j01:j02,1)
  528. end if
  529. end if
  530. ! add dataset according to sector and category
  531. if( trim(sectors_def(lsec)%catname) == "natural" ) then
  532. call do_add_isop( region, i1, j1, emis3d%d3, status, fraction ) ! special routine with additional emission scaling...
  533. IF_NOTOK_RETURN(status=1)
  534. else
  535. call do_add_3d( region, iisop, i1, j1, emis3d%d3, xmisop, xmisop, status, fraction )
  536. IF_NOTOK_RETURN(status=1)
  537. end if
  538. end do
  539. deallocate( emis3d%d3 )
  540. if(okdebug) then
  541. write(gol,*) 'end of emission_isop_apply' ; call goPr
  542. end if
  543. ! OK
  544. status = 0
  545. END SUBROUTINE EMISSION_ISOP_APPLY
  546. !EOC
  547. !--------------------------------------------------------------------------
  548. ! TM5 !
  549. !--------------------------------------------------------------------------
  550. !BOP
  551. !
  552. ! !IROUTINE: SCALE_ISOP
  553. !
  554. ! !DESCRIPTION: calculates factors to be multiplied with an emission field
  555. ! (e.g. isop) in order to simulate a diurnal cycle in
  556. ! emissions (caused by solar dependency), e.g. :
  557. !
  558. ! rm(i,j,1,isop) = rm(i,j,1,isop) + e_isop(i,j)*scalef(ipos,j)*dt
  559. !
  560. ! with ipos depending on time and longitude.
  561. !
  562. ! The scalefactor is calculated for -180 longitude and the
  563. ! mean value for ntim timesteps during a day is scaled to 1.
  564. ! The routine should be called every day, since the position
  565. ! relative to the sun changes. The scaling is based on the
  566. ! cos(zenith) which is 1 for overhead sun and 0 at sunset.
  567. ! For the polar night, the values are set to 1.0 (even distribution)
  568. ! One thing is sure afterwards: we know that e_isop kg/s is added.
  569. !\\
  570. !\\
  571. ! !INTERFACE:
  572. !
  573. SUBROUTINE SCALE_ISOP(day, ntim, j1, scalef, lat_start, dlat, idayy)
  574. !
  575. ! !INPUT PARAMETERS:
  576. !
  577. integer, intent(in) :: day ! day number based on 365 days a year
  578. integer, intent(in) :: ntim ! number of timesteps during one day
  579. integer, intent(in) :: j1 ! start index for latitudes
  580. integer, intent(in) :: lat_start ! southern edge of the domain (integer!)
  581. real, intent(in) :: dlat ! increment (real!)
  582. integer, intent(in) :: idayy ! # days this year
  583. !
  584. ! !OUTPUT PARAMETERS:
  585. !
  586. real, dimension(:,j1:), intent(out) :: scalef
  587. !
  588. ! !REVISION HISTORY:
  589. ! 10 May 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  590. !
  591. ! !REMARKS:
  592. !
  593. !EOP
  594. !------------------------------------------------------------------------
  595. !BOC
  596. real :: pi, piby, obliq, deday, delta, dt, lon, hr, lat, houra, smm
  597. integer :: i, j
  598. pi = acos(-1.0)
  599. piby = pi/180.0
  600. obliq = 23.45 * piby
  601. deday = 4.88 + 2*pi/idayy * day
  602. delta = asin(sin(obliq)*sin(deday))
  603. dt = 24./ntim ! timestep in hours
  604. lon = -180.0*piby ! calculate for dateline
  605. do j=j1,ubound(scalef,2) ! over latitudes
  606. hr = - 0.5*dt ! shift half a interval back
  607. lat = (lat_start + (j-0.5)*dlat)*piby
  608. smm = 0.0
  609. do i=1,ntim
  610. hr = hr + dt
  611. houra = lon - pi + hr * (2.*pi/24.)
  612. scalef(i,j) = &
  613. max((sin(delta)*sin(lat) + cos(delta)*cos(lat)*cos(houra)),0.0)
  614. smm = smm+scalef(i,j)/ntim
  615. end do
  616. if ( smm > 1e-5 ) then
  617. scalef(1:ntim,j) = scalef(1:ntim,j)/smm
  618. else
  619. scalef(1:ntim,j) = 1.0
  620. end if
  621. end do
  622. END SUBROUTINE SCALE_ISOP
  623. !EOC
  624. !--------------------------------------------------------------------------
  625. ! TM5 !
  626. !--------------------------------------------------------------------------
  627. !BOP
  628. !
  629. ! !IROUTINE: DO_ADD_ISOP
  630. !
  631. ! !DESCRIPTION: Add local time splitted emissions to chemical array
  632. !\\
  633. !\\
  634. ! !INTERFACE:
  635. !
  636. SUBROUTINE DO_ADD_ISOP(region, i1, j1, em_isop, status, fraction)
  637. !
  638. ! !USES:
  639. !
  640. use dims, only : tref, nsrce, itaur, ndyn_max
  641. use dims, only : sec_month, lm, dx, xref, xbeg
  642. use global_data, only : mass_dat
  643. use chem_param, only : iisop, xmisop
  644. #ifdef with_budgets
  645. use budget_global, only : budg_dat, nzon_vg
  646. use emission_data, only : sum_emission, budemi_dat
  647. #endif
  648. use datetime, only : tau2date
  649. !
  650. ! !INPUT PARAMETERS:
  651. !
  652. integer, intent(in) :: region, i1, j1
  653. real, intent(in) :: em_isop(i1:,j1:,:)
  654. real, optional, intent(in) :: fraction
  655. !
  656. ! !OUTPUT PARAMETERS:
  657. !
  658. integer, intent(out) :: status
  659. !
  660. ! !REVISION HISTORY:
  661. ! 1 Oct 2010 - Achim Strunk - added fraction input
  662. ! - switch from 2D to 3D input => remove tropics case
  663. ! 10 May 2012 - Ph. Le Sager - adapted for lon-lat MPI domain decomposition
  664. !
  665. ! !REMARKS:
  666. ! (1) scalef_isop has been calculated w/ ndyn_max.
  667. !EOP
  668. !------------------------------------------------------------------------
  669. !BOC
  670. character(len=*), parameter :: rname = mname//'/do_add_isop'
  671. real :: x, xlon, dtime, month2dt, dtime2
  672. integer :: i, j, l, ipos, nzone, nzone_v
  673. integer :: sec_in_day, ntim, itim, i2, j2
  674. integer, dimension(6) :: idater
  675. real, dimension(:,:,:,:), pointer :: rm
  676. ! --- begin -----------------------------------------
  677. rm => mass_dat(region)%rm
  678. CALL GET_DISTGRID( dgrid(region), I_STOP=i2, J_STOP=j2 )
  679. dtime = float(nsrce) / (2*tref(region)) ! timestep emissions
  680. dtime2 = float(ndyn_max) / (2*tref(region)) ! timestep emissions based on non-CFL interference (CMK 05/2006)
  681. month2dt = dtime/sec_month ! conversion to emission per timestep (CFl induced timestep CMK 05/2006)
  682. ntim = 86400/nint(dtime2) ! number of timesteps in 24 hours based on non-CFL interference (CMK 05/2006)
  683. call tau2date(itaur(region),idater)
  684. sec_in_day = idater(4)*3600 + idater(5)*60 + idater(6) ! elapsd seconds this day
  685. itim = sec_in_day/nint(dtime2)+1 ! # time interval CMK 05/2006
  686. do l= 1,lm(region)
  687. do j=j1,j2
  688. do i=i1,i2
  689. xlon = xbeg(region) + (i-0.5)*dx/xref(region)
  690. ! itim = 1 and lon = -180 --->position 1
  691. ! itim = ntim ant lon = -180 --->position ntim, etc.
  692. ! itim = 1 and lon = 0 ---->position ntim/2
  693. ipos = 1 + mod(int((xlon+180.)*ntim/360.) + (itim-1),ntim) !position in array depending on time and lon.
  694. x=em_isop(i,j,l)*isop_dat(region)%scalef_isop(ipos,j)*month2dt
  695. rm(i,j,l,iisop)=rm(i,j,l,iisop)+x
  696. #ifdef with_budgets
  697. nzone=budg_dat(region)%nzong(i,j) !global budget
  698. nzone_v=nzon_vg(l)
  699. budemi_dat(region)%emi(i,j,nzone_v,iisop) = &
  700. budemi_dat(region)%emi(i,j,nzone_v,iisop) + x/xmisop*1e3
  701. if(iisop ==1) sum_emission(region) = sum_emission(region) + x !in kg
  702. #endif
  703. !--
  704. !AJS: strange statement: injection of emission decreases vertical slope ?
  705. !AJS: this gives negative slopes in case of large emissions ...
  706. !if(adv_scheme.eq.'slope') rzm(i,j,L,iisop)=rzm(i,j,L,iisop)-x
  707. !--
  708. enddo !i
  709. enddo !j
  710. enddo !l
  711. nullify(rm)
  712. status=0
  713. END SUBROUTINE DO_ADD_ISOP
  714. !EOC
  715. END MODULE EMISSION_ISOP