budget_global__detailed.F90 43 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173
  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: BUDGET_GLOBAL
  14. !
  15. ! !DESCRIPTION: This module holds most of the budget variables (see
  16. ! wet_deposition for exceptions).
  17. !
  18. ! ******************************************************************
  19. ! ***** THIS VERSION DIFFERS FROM THE ONE IN BASE IN THE ****
  20. ! ***** DEFINITION OF THE HORIZONTAL AND VERTICAL BUDGET-REGION ****
  21. ! ******************************************************************
  22. !
  23. ! Budgets are defined for a set of horizontal regions, split vertically, and
  24. ! available for each transported tracers. In the module:
  25. !
  26. ! o defines the budget output filename
  27. ! o defines the horizontal 'regions' for which a budgets are calculated
  28. ! HERE: 10degree wide latitudinal bands
  29. ! o defines the vertical split of the budgets
  30. ! HERE: each levels (instead of vertical 4 regions)
  31. ! o routines to compute the transport budgets (advx, advy, advz, conv)
  32. ! o sets up the possibility to calculate transport fluxes in/out a
  33. ! predefined XY, XZ, and YZ planes (2 of each => define a box)
  34. ! o other budget terms (emission, deposition, etc.) can be added to the budget file
  35. !
  36. !\\
  37. !\\
  38. ! !INTERFACE:
  39. !
  40. MODULE BUDGET_GLOBAL
  41. !
  42. ! !USES:
  43. !
  44. use GO, only : gol, goErr, goPr
  45. use dims, only : im, jm, lm, idatei, idatee, nregions, region_name
  46. use dims, only : itau, idate, dx, dy, xref, yref, xbeg, ybeg
  47. use chem_param, only : ntracet, ntrace, names, ra
  48. use tm5_distgrid, only : dgrid, Get_DistGrid, reduce, gather
  49. IMPLICIT NONE
  50. PRIVATE
  51. !
  52. ! !PUBLIC MEMBER FUNCTIONS:
  53. !
  54. public :: init_budget_global ! initialize and allocate variables
  55. public :: done_budget_global ! final computation, write budgets to file
  56. public :: budget_transportg ! evaluate advection/convection budgets
  57. public :: budget_displayg ! print out budget of tracer #1
  58. !
  59. ! !PUBLIC DATA MEMBERS:
  60. !
  61. character(len=256), public :: budget_file_global ! name of budget output file
  62. integer, public, parameter :: nbudg = 18 ! # horizontal budget regions (h-budgets)
  63. integer, public, parameter :: nbud_vg = lm(1) ! # vertical budget regions (v-budgets)
  64. logical, public :: apply_budget_global = .false. ! compute budgets
  65. logical, public :: apply_budget_global_flux = .false. ! compute extra fluxes
  66. logical, public :: NHAB ! Non-Horizontally-Aggregated-Budgets (if true (default), writes [im,jm,nbud_vg] budgets)
  67. real, public, dimension(nbudg, nbud_vg, ntracet) :: budconvg ! convection budget
  68. real, public, dimension(nregions) :: init_mass = 0.0 ! tracer #1 : initial mass (meaningful on root only)
  69. real, public, dimension(nregions) :: sum_update = 0.0 ! tracer #1 :
  70. real, public, dimension(nregions) :: sum_advection = 0.0 ! tracer #1 : mass change thru advection (meaningful on root only)
  71. integer, public, dimension(lm(1)) :: nzon_vg ! vertical budget code of each level
  72. integer, public, dimension(nregions) :: iflux1, iflux2 ! I index of YZ plane where flux flowing in from west
  73. integer, public, dimension(nregions) :: jflux1, jflux2 ! J index of XZ plane where flux flowing in from south
  74. integer, public, dimension(nregions) :: lflux1, lflux2 ! L index of XY plane where flux flowing in from below
  75. !
  76. ! !PUBLIC TYPES:
  77. !
  78. type, public :: budg_data
  79. ! holds horizontal budget code of each cell (1:SH 90-30, 2:S30-N30, 3:NH 30-90, 4: Europe...)
  80. integer, dimension(:,:), pointer :: nzong
  81. end type budg_data
  82. type(budg_data), public, dimension(nregions), target :: budg_dat ! horizontal budget codes
  83. type, public :: budflux_data
  84. ! fluxes of all species through some predefined slices:
  85. real, dimension(:,:,:), pointer :: flux_x1 ! (jm,lm,ntracet)
  86. real, dimension(:,:,:), pointer :: flux_x2 ! (jm,lm,ntracet)
  87. real, dimension(:,:,:), pointer :: flux_y1 ! (im,lm,ntracet)
  88. real, dimension(:,:,:), pointer :: flux_y2 ! (im,lm,ntracet)
  89. real, dimension(:,:,:), pointer :: flux_z1 ! (im,jm,ntracet)
  90. real, dimension(:,:,:), pointer :: flux_z2 ! (im,jm,ntracet)
  91. end type budflux_data
  92. type(budflux_data), public, dimension(nregions), target :: budget_flux
  93. type(budflux_data), dimension(nregions), target :: budget_flux_all
  94. !
  95. ! !PRIVATE DATA MEMBERS:
  96. !
  97. real, dimension(nbudg, nbud_vg, ntracet) :: rmoldg, rmnewg ! work arrays (old/new rm)
  98. real, dimension(nbudg, nbud_vg, ntracet) :: budconcg ! final concentrations (end run)
  99. real, dimension(nbudg, nbud_vg, ntracet) :: budinig ! initial concentrations (begin run)
  100. real, dimension(nbudg, nbud_vg, ntracet) :: budchngg = 0.0 ! change of concentration b/w end-begin
  101. real, dimension(nbudg, nbud_vg, ntracet) :: budadvxg ! advection-x budget
  102. real, dimension(nbudg, nbud_vg, ntracet) :: budadvyg ! advection-y budget
  103. real, dimension(nbudg, nbud_vg, ntracet) :: budadvzg ! advection-z budget
  104. character(len=20), dimension(nbudg) :: zone_nameg ! name of horizontal budget regions
  105. character(len=20), dimension(nbud_vg) :: zone_namvg ! name of vertical budget regions
  106. integer :: lon_in, lon_out, lat_in, lat_out ! read box boundaries for extra fluxes
  107. character(len=*), parameter :: mname = 'budget_global' ! module name
  108. !
  109. ! !REVISION HISTORY:
  110. ! 28 Feb 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  111. ! 16 Jul 2013 - P. Le Sager - version for "budget_detailed"
  112. !
  113. ! !REMARKS:
  114. ! (1) All processors compute the same aggregated budgets in case of MPI, but
  115. ! account only for the contribution of their own tile, if any. MPI
  116. ! reduction is used to sum up contributions.
  117. !
  118. !EOP
  119. !------------------------------------------------------------------------
  120. CONTAINS
  121. !--------------------------------------------------------------------------
  122. ! TM5 !
  123. !--------------------------------------------------------------------------
  124. !BOP
  125. !
  126. ! !IROUTINE: INI_ZONEG
  127. !
  128. ! !DESCRIPTION: set structure of user-defined "budget regions"
  129. !\\
  130. !\\
  131. ! !INTERFACE:
  132. !
  133. SUBROUTINE INI_ZONEG ( status )
  134. !
  135. ! !USES:
  136. !
  137. use GO , only : TrcFile, Init, Done, ReadRc
  138. use global_data, only : outdir, rcfile
  139. use toolbox , only : lvlpress
  140. use partools , only : isRoot
  141. use file_hdf, only : THdfFile, TSds
  142. use file_hdf, only : Init, Done, WriteAttribute, WriteData
  143. !
  144. ! !OUTPUT PARAMETERS:
  145. !
  146. integer, intent(out) :: status
  147. !
  148. ! !REVISION HISTORY:
  149. ! 28 Feb 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  150. !
  151. ! !REMARKS:
  152. !
  153. !EOP
  154. !------------------------------------------------------------------------
  155. !BOC
  156. type(THdfFile) :: io
  157. type(TSds) :: sds
  158. integer :: i1, i2, j1, j2, i, j, n, nix, niy, region
  159. integer :: ilvl1, ilvl2, ilvl3
  160. real :: psurf, plev, rlat, rlon
  161. real :: dyr, dxr, lats ! made real instead of integer to handle hi-res regions
  162. integer, allocatable :: gbl_data(:,:)
  163. type(TrcFile) :: rcF
  164. character(len=256) :: fname
  165. character(len=*), parameter :: rname = mname//'/ini_zong'
  166. ! ------- Compute budgets and extra fluxes ?
  167. #ifdef with_budgets
  168. apply_budget_global = .true.
  169. #endif
  170. if (.not.apply_budget_global) return
  171. call Init( rcF, rcfile, status )
  172. IF_NOTOK_RETURN(status=1)
  173. call ReadRc(rcF, 'apply.budget.global.flux', apply_budget_global_flux, status, default=.false.)
  174. IF_ERROR_RETURN(status=1)
  175. if (apply_budget_global_flux) then
  176. ! Example Europe: lat_in = 34, lat_out = 62, lon_in = -12, lon_out = 36
  177. call ReadRc(rcF, 'budget.global.flux.lon_in', lon_in, status )
  178. IF_NOTOK_RETURN(status=1)
  179. call ReadRc(rcF, 'budget.global.flux.lon_out', lon_out, status )
  180. IF_NOTOK_RETURN(status=1)
  181. call ReadRc(rcF, 'budget.global.flux.lat_in', lat_in, status )
  182. IF_NOTOK_RETURN(status=1)
  183. call ReadRc(rcF, 'budget.global.flux.lat_out', lat_out, status )
  184. IF_NOTOK_RETURN(status=1)
  185. endif
  186. call ReadRc(rcF, 'write.column.budgets', NHAB, status, default=.true.)
  187. IF_ERROR_RETURN(status=1)
  188. call Done( rcF, status )
  189. IF_NOTOK_RETURN(status=1)
  190. ! -------- Fill budgets name, code and vertical indices
  191. region = 1
  192. do i = 1, nbud_vg
  193. write( zone_namvg(i),'("Level_",i2.2)')i
  194. enddo
  195. do i=1,nbudg
  196. write( zone_nameg(i),'("i_Latitude_",i2.2)')i
  197. enddo
  198. if ( isRoot ) then
  199. write(gol,'(A)') '-----------------------------------------------'; call goPr
  200. write(gol,'(A)') 'Horizontal definition of budget regions '; call goPr
  201. write(gol,'(A)') '-----------------------------------------------'; call goPr
  202. do i=1,nbudg
  203. write(gol,'(A,i4,4x,A)') 'Budget region:',i,zone_nameg(i); call goPr
  204. enddo
  205. write(gol,'(A)') '-----------------------------------------------'; call goPr
  206. endif
  207. ! Associate a v-budget code to each level
  208. psurf = 98400.0
  209. plev = 85000.0 ; ilvl1 = lvlpress(region,plev, psurf)
  210. plev = 50000.0 ; ilvl2 = lvlpress(region,plev, psurf)
  211. plev = 10000.0 ; ilvl3 = lvlpress(region,plev, psurf)
  212. do i=1,lm(1)
  213. nzon_vg(i) = i
  214. enddo
  215. if (apply_budget_global_flux) then ! Limited to free troposphere
  216. lflux1(:) = ilvl1+1 ! where to calculate the vertical flux (1 = BL->FT)
  217. lflux2(:) = ilvl2+1 ! where to calculate the vertical flux (2 = FT->UFT)
  218. endif
  219. !---------- Allocate/fill arrays w/r/t horizontal definitions
  220. REG: do n=1,nregions
  221. call Get_DistGrid( dgrid(n), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  222. ! allocate horizontal budget code :
  223. allocate( budg_dat(n)%nzong(i1:i2,j1:j2))
  224. ! allocate flux data:
  225. if (apply_budget_global_flux) then
  226. allocate( budget_flux(n)%flux_x1(j1:j2,lm(n),ntracet))
  227. allocate( budget_flux(n)%flux_y1(i1:i2,lm(n),ntracet))
  228. allocate( budget_flux(n)%flux_z1(i1:i2,j1:j2,ntracet))
  229. allocate( budget_flux(n)%flux_x2(j1:j2,lm(n),ntracet))
  230. allocate( budget_flux(n)%flux_y2(i1:i2,lm(n),ntracet))
  231. allocate( budget_flux(n)%flux_z2(i1:i2,j1:j2,ntracet))
  232. if (isRoot) then
  233. allocate( budget_flux_all(n)%flux_x1(jm(n),lm(n),ntracet))
  234. allocate( budget_flux_all(n)%flux_y1(im(n),lm(n),ntracet))
  235. allocate( budget_flux_all(n)%flux_z1(im(n),jm(n),ntracet))
  236. else
  237. allocate( budget_flux_all(n)%flux_x1(1,1,1))
  238. allocate( budget_flux_all(n)%flux_y1(1,1,1))
  239. allocate( budget_flux_all(n)%flux_z1(1,1,1))
  240. end if
  241. budget_flux(n)%flux_x1(:,:,:) = 0.0
  242. budget_flux(n)%flux_y1(:,:,:) = 0.0
  243. budget_flux(n)%flux_z1(:,:,:) = 0.0
  244. budget_flux(n)%flux_x2(:,:,:) = 0.0
  245. budget_flux(n)%flux_y2(:,:,:) = 0.0
  246. budget_flux(n)%flux_z2(:,:,:) = 0.0
  247. endif
  248. dyr = dy/yref(n)
  249. dxr = dx/xref(n)
  250. ! Fill horizontal budget codes for zonal bands
  251. do j=j1,j2
  252. lats = ybeg(n) + (j-1)*dyr
  253. budg_dat(n)%nzong(:,j) = ( nint(lats)+90+10 ) / 10
  254. end do
  255. ! --- Calculate in each region where to calculate the flux:
  256. !
  257. ! Get the index of the flux planes. The plane is always exactly between cells.
  258. ! The cell i-index east of the YZ-plane will be put in iflux(n) (for each region).
  259. ! iflux1 is the western plan (lon_in) and iflux2 is the eastern plane (lon_out).
  260. ! The same way jflux1 and jflux2 will become the j-index of the cells just north
  261. ! of the XZ-planes, etc.
  262. !
  263. if (apply_budget_global_flux) then
  264. jflux1(n)=0 ; jflux2(n)=0
  265. iflux1(n)=0 ; iflux2(n)=0
  266. do j=1,jm(n)
  267. ! rlat = ybeg(n) + (float(j)-0.5)*dyr
  268. ! Example Europe: lat_in = 34, lat_out = 62, lon_in = -12, lon_out = 36
  269. if( nint(ybeg(n) + float(j-1)*dyr) == lat_in) jflux1(n) = j
  270. if( nint(ybeg(n) + float(j-1)*dyr) == lat_out) jflux2(n) = j
  271. !if( nint(ybeg(n) + float(j)*dyr) == 62) jflux2(n) = j !CMK corrected
  272. enddo
  273. do i=1,im(n)
  274. ! rlon = xbeg(n) + (float(i)-0.5)*dxr
  275. if( nint(xbeg(n) + float(i-1)*dxr) == lon_in) iflux1(n) = i
  276. if( nint(xbeg(n) + float(i-1)*dxr) == lon_out) iflux2(n) = i ! corrected CMK
  277. !cmk if( nint(xbeg(n) + float(i)*dxr) == 36) iflux2(n) = i ! corrected CMK
  278. enddo
  279. endif
  280. ! --- Write the budgets regional definition to HDF file:
  281. if ( isRoot ) then
  282. allocate( gbl_data(im(n),jm(n)))
  283. else
  284. allocate( gbl_data(1,1))
  285. end if
  286. call gather( dgrid(n), budg_dat(n)%nzong, gbl_data, 0, status)
  287. if ( isRoot ) then
  288. write (fname,'(a,"/regionsg_",a,".hdf")') trim(outdir), trim(region_name(n))
  289. call Init(io,fname,'create',status)
  290. IF_NOTOK_RETURN(status=1)
  291. call WriteAttribute(io, 'im', im(n), status)
  292. call WriteAttribute(io, 'jm', jm(n), status)
  293. call WriteAttribute(io, 'lm', lm(n), status)
  294. call Init(Sds, io, 'region_global', (/im(n),jm(n)/), 'integer(4)', status)
  295. IF_NOTOK_RETURN(status=1)
  296. call WriteData(Sds, gbl_data, status)
  297. IF_NOTOK_RETURN(status=1)
  298. call Done(Sds,status)
  299. IF_NOTOK_RETURN(status=1)
  300. call Done(io,status)
  301. IF_NOTOK_RETURN(status=1)
  302. end if
  303. deallocate(gbl_data)
  304. end do REG
  305. ! Filename for budget data (include time range: budget_2001010100_2001020100_global.hdf)
  306. write (budget_file_global,'(a,"/budget_",i4.4,3i2.2,"_",i4.4,3i2.2,"_",a,".hdf")') &
  307. trim(outdir), idatei(1:4), idatee(1:4), 'global'
  308. if ( isRoot ) then
  309. !write(gol,'(A )') '----------------------------------------------------'; call goPr
  310. write(gol,'(A,A)') 'Budget will be written to:', trim(budget_file_global); call goPr
  311. write(gol,'(A )') '----------------------------------------------------'; call goPr
  312. endif
  313. ! OK
  314. status = 0
  315. END SUBROUTINE INI_ZONEG
  316. !EOC
  317. !--------------------------------------------------------------------------
  318. ! TM5 !
  319. !--------------------------------------------------------------------------
  320. !BOP
  321. !
  322. ! !IROUTINE: INIT_BUDGET_GLOBAL
  323. !
  324. ! !DESCRIPTION: initialize budgets
  325. !\\
  326. !\\
  327. ! !INTERFACE:
  328. !
  329. SUBROUTINE INIT_BUDGET_GLOBAL ( status )
  330. !
  331. ! !USES:
  332. !
  333. use ParTools, only : isRoot
  334. use global_data, only : region_dat, mass_dat
  335. !
  336. ! !OUTPUT PARAMETERS:
  337. !
  338. integer, intent(out) :: status
  339. !
  340. ! !REVISION HISTORY:
  341. ! 28 Feb 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  342. !
  343. !EOP
  344. !------------------------------------------------------------------------
  345. !BOC
  346. real,dimension(:,:,:,:),pointer :: rm
  347. ! integer,dimension(:,:) ,pointer :: zoomed, edge
  348. integer :: nzone, nzone_v, region
  349. integer :: i,j,l,n, i1,i2,j1,j2
  350. character(len=*), parameter :: rname = mname//'/init_budget_global'
  351. ! --- begin --------------------------------
  352. ! first set up the budget regions, and extra info from rcfile
  353. call ini_zoneg( status )
  354. IF_NOTOK_RETURN(status=1)
  355. ! reset budget variables
  356. budconcg = 0.
  357. budinig = 0.
  358. budconvg = 0.0
  359. budadvxg = 0.0
  360. budadvyg = 0.0
  361. budadvzg = 0.0
  362. REG: do region = 1, nregions
  363. rm => mass_dat(region)%rm
  364. !zoomed => region_dat(region)%zoomed
  365. !edge => region_dat(region)%edge
  366. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  367. ! Tracer #1 init budgets
  368. call REDUCE( dgrid(region), rm(:,:,:,1), mass_dat(region)%halo, 'SUM', init_mass(region), status)
  369. IF_NOTOK_RETURN(status=1)
  370. sum_update(region) = 0.0
  371. sum_advection(region) = 0.0
  372. !
  373. ! initialise budinig
  374. !
  375. do n=1,ntracet
  376. do l=1,lm(region)
  377. nzone_v=nzon_vg(l) ! vertical bud code
  378. do j=j1,j2
  379. do i=i1,i2
  380. !skip zoomed part of the region
  381. !if ( zoomed(i,j) /= region .or. edge(i,j) >= 1 ) cycle
  382. ! include the edges....parent takes care!
  383. nzone = budg_dat(region)%nzong(i,j)
  384. budinig(nzone, nzone_v, n) = budinig(nzone, nzone_v, n) + &
  385. rm(i,j,l,n)/ra(n)*1000.
  386. end do !i
  387. end do !j
  388. end do !l
  389. end do !n
  390. nullify(rm)
  391. ! nullify(zoomed)
  392. ! nullify(edge)
  393. enddo REG
  394. ! ok
  395. status = 0
  396. END SUBROUTINE INIT_BUDGET_GLOBAL
  397. !EOC
  398. !--------------------------------------------------------------------------
  399. ! TM5 !
  400. !--------------------------------------------------------------------------
  401. !BOP
  402. !
  403. ! !IROUTINE: DONE_BUDGET_GLOBAL
  404. !
  405. ! !DESCRIPTION: compute concentration change b/w beginning and end of the
  406. ! run; write budgets to output file.
  407. !\\
  408. !\\
  409. ! !INTERFACE:
  410. !
  411. SUBROUTINE DONE_BUDGET_GLOBAL ( status )
  412. !
  413. ! !USES:
  414. !
  415. use ParTools, only : isRoot, par_reduce_element, par_barrier
  416. use global_data, only : region_dat, mass_dat
  417. use file_hdf, only : THdfFile, TSds
  418. use file_hdf, only : Done, WriteAttribute, Init, WriteData, SetDim
  419. use tm5_distgrid, only : gather_i_band, gather_j_band
  420. !
  421. ! !OUTPUT PARAMETERS:
  422. !
  423. integer, intent(out) :: status
  424. !
  425. ! !REVISION HISTORY:
  426. ! 28 Feb 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  427. !
  428. !EOP
  429. !------------------------------------------------------------------------
  430. !BOC
  431. real, dimension(:,:,:,:), pointer :: rm
  432. integer, dimension(:,:) , pointer :: zoomed, edge
  433. integer :: nzone, nzone_v, region
  434. integer :: i,j,l,n, i1,i2,j1,j2
  435. type(THdfFile) :: io
  436. type(TSds) :: sds
  437. ! Need these arrays to deal with buggy MPI implementations: if send and receive buffers
  438. ! are the same, you can get this error on some system:
  439. ! Fatal error in PMPI_Reduce: Invalid buffer pointer, error stack:
  440. ! PMPI_Reduce(1701): MPI_Reduce(sbuf=0x1bae7a0 rbuf=0x1bae7a0, count=3060, MPI_DOUBLE_PRECISION, MPI_SUM, root=0, MPI_COMM_WORLD) failed
  441. ! PMPI_Reduce(1511): Buffers must not be aliased
  442. ! For MPICH2, this is a bug that was fixed in 2009 (http://lists.mcs.anl.gov/pipermail/mpich-discuss/2009-October/005804.html)
  443. ! but this is not the case for Intel MPI (the version used at KNMI)
  444. real, dimension(nbudg,nbud_vg,ntracet) :: budconcg_all
  445. real, dimension(nbudg,nbud_vg,ntracet) :: budchngg_all
  446. real, dimension(nbudg,nbud_vg,ntracet) :: budinig_all
  447. real, dimension(nbudg,nbud_vg,ntracet) :: budadvxg_all
  448. real, dimension(nbudg,nbud_vg,ntracet) :: budadvyg_all
  449. real, dimension(nbudg,nbud_vg,ntracet) :: budadvzg_all
  450. real, dimension(nbudg,nbud_vg,ntracet) :: budconvg_all
  451. ! --- const -------------------------------
  452. character(len=*), parameter :: rname = mname//'/done_budget_global'
  453. integer, parameter :: nproces=4 ! x,y,z, conv
  454. character(len=10), dimension(nproces),parameter :: proces_name=(/'names ','names ','names ','names '/)
  455. integer, dimension(nproces),parameter :: proces_nr = (/ ntracet, ntracet, ntracet, ntracet /)
  456. ! --- begin --------------------------------
  457. if (.not.apply_budget_global) return
  458. ! final concentrations
  459. budconcg = 0.0
  460. do region = 1, nregions
  461. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  462. ! zoomed => region_dat(region)%zoomed
  463. ! edge => region_dat(region)%edge
  464. rm => mass_dat(region)%rm
  465. do n=1,ntracet
  466. do l=1,lm(region)
  467. nzone_v = nzon_vg(l)
  468. do j=j1,j2
  469. do i=i1,i2
  470. !if (zoomed(i,j)/=region .or. edge(i,j) >= 1) cycle
  471. nzone = budg_dat(region)%nzong(i,j)
  472. budconcg(nzone, nzone_v, n) = budconcg(nzone, nzone_v, n) + &
  473. rm(i,j,l,n)/ra(n)*1000.
  474. end do !i
  475. end do !j
  476. end do !l
  477. end do !n
  478. nullify(rm)
  479. ! nullify(zoomed)
  480. ! nullify(edge)
  481. enddo
  482. ! Calculate concentrations change
  483. budchngg = budconcg - budinig
  484. ! Sum up contribution from each proc into root array
  485. call PAR_REDUCE_ELEMENT( budconcg, 'SUM', budconcg_all, status )
  486. IF_NOTOK_RETURN(status=1)
  487. call PAR_REDUCE_ELEMENT( budchngg, 'SUM', budchngg_all, status )
  488. IF_NOTOK_RETURN(status=1)
  489. call PAR_REDUCE_ELEMENT( budinig, 'SUM', budinig_all, status )
  490. IF_NOTOK_RETURN(status=1)
  491. call PAR_REDUCE_ELEMENT( budadvxg, 'SUM', budadvxg_all, status )
  492. IF_NOTOK_RETURN(status=1)
  493. call PAR_REDUCE_ELEMENT( budadvyg, 'SUM', budadvyg_all, status )
  494. IF_NOTOK_RETURN(status=1)
  495. call PAR_REDUCE_ELEMENT( budadvzg, 'SUM', budadvzg_all, status )
  496. IF_NOTOK_RETURN(status=1)
  497. call PAR_REDUCE_ELEMENT( budconvg, 'SUM', budconvg_all, status )
  498. IF_NOTOK_RETURN(status=1)
  499. ! Write out budget file
  500. if ( isRoot ) then
  501. call Init(io, budget_file_global, 'create', status)
  502. IF_NOTOK_RETURN(status=1)
  503. call WriteAttribute(io, 'nregions', nregions, status)
  504. call WriteAttribute(io, 'itau', itau, status)
  505. call WriteAttribute(io, 'nbud', nbudg, status)
  506. call WriteAttribute(io, 'nbud_v', nbud_vg, status)
  507. call WriteAttribute(io, 'ntrace', ntrace, status)
  508. call WriteAttribute(io, 'ntracet', ntracet, status)
  509. call WriteAttribute(io, 'idate', idate, status)
  510. call WriteAttribute(io, 'idatei', idatei, status)
  511. call WriteAttribute(io, 'idatee', idatee, status)
  512. call WriteAttribute(io, 'proces_nr', proces_nr, status)
  513. call WriteAttribute(io, 'proces_name', proces_name, status)
  514. call WriteAttribute(io, 'zone_name', zone_nameg, status)
  515. call WriteAttribute(io, 'zone_namv', zone_namvg, status)
  516. call WriteAttribute(io, 'names', names, status)
  517. if (apply_budget_global_flux) then
  518. call WriteAttribute(io, 'iflux1' , iflux1, status)
  519. call WriteAttribute(io, 'iflux2' , iflux2, status)
  520. call WriteAttribute(io, 'jflux1' , jflux1, status)
  521. call WriteAttribute(io, 'jflux2' , jflux2, status)
  522. call WriteAttribute(io, 'lflux1' , lflux1, status)
  523. call WriteAttribute(io, 'lflux2' , lflux2, status)
  524. endif
  525. IF_NOTOK_RETURN(status=1)
  526. call Init(Sds, io, 'budconc', (/nbudg, nbud_vg, ntracet/), 'real(8)', status)
  527. call SetDim(Sds, 0, 'nbudg', 'horizontal budget', (/(j, j=1,nbudg)/), status)
  528. call SetDim(Sds, 1, 'nbud_vg', 'vertical budget', (/(j, j=1,nbud_vg)/), status)
  529. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1, ntracet)/), status)
  530. IF_NOTOK_RETURN(status=1)
  531. call WriteData(Sds, budconcg_all, status)
  532. IF_NOTOK_RETURN(status=1)
  533. call Done(Sds, status)
  534. IF_NOTOK_RETURN(status=1)
  535. call Init(Sds, io, 'budchng', (/nbudg, nbud_vg, ntracet/), 'real(8)', status)
  536. call SetDim(Sds, 0, 'nbudg', 'horizontal budget', (/(j, j=1,nbudg)/), status)
  537. call SetDim(Sds, 1, 'nbud_vg', 'vertical budget', (/(j, j=1,nbud_vg)/), status)
  538. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1, ntracet)/), status)
  539. IF_NOTOK_RETURN(status=1)
  540. call WriteData(Sds, budchngg_all, status)
  541. IF_NOTOK_RETURN(status=1)
  542. call Done(Sds, status)
  543. IF_NOTOK_RETURN(status=1)
  544. call Init(Sds, io, 'budini', (/nbudg, nbud_vg, ntracet/), 'real(8)', status)
  545. call SetDim(Sds, 0, 'nbudg', 'horizontal budget', (/(j, j=1,nbudg)/), status)
  546. call SetDim(Sds, 1, 'nbud_vg', 'vertical budget', (/(j, j=1,nbud_vg)/), status)
  547. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1, ntracet)/), status)
  548. IF_NOTOK_RETURN(status=1)
  549. call WriteData(Sds, budinig_all, status)
  550. IF_NOTOK_RETURN(status=1)
  551. call Done(Sds, status)
  552. IF_NOTOK_RETURN(status=1)
  553. call Init(Sds, io, 'budadvx', (/nbudg, nbud_vg, ntracet/), 'real(8)', status)
  554. call SetDim(Sds, 0, 'nbudg', 'horizontal budget', (/(j, j=1,nbudg)/), status)
  555. call SetDim(Sds, 1, 'nbud_vg', 'vertical budget', (/(j, j=1,nbud_vg)/), status)
  556. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1, ntracet)/), status)
  557. IF_NOTOK_RETURN(status=1)
  558. call WriteData(Sds, budadvxg_all, status)
  559. IF_NOTOK_RETURN(status=1)
  560. call Done(Sds, status)
  561. IF_NOTOK_RETURN(status=1)
  562. call Init(Sds, io, 'budadvy', (/nbudg, nbud_vg, ntracet/), 'real(8)', status)
  563. call SetDim(Sds, 0, 'nbudg', 'horizontal budget', (/(j, j=1,nbudg)/), status)
  564. call SetDim(Sds, 1, 'nbud_vg', 'vertical budget', (/(j, j=1,nbud_vg)/), status)
  565. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1,ntracet)/), status)
  566. IF_NOTOK_RETURN(status=1)
  567. call WriteData(Sds, budadvyg_all, status)
  568. IF_NOTOK_RETURN(status=1)
  569. call Done(Sds, status)
  570. IF_NOTOK_RETURN(status=1)
  571. call Init(Sds, io, 'budadvz', (/nbudg, nbud_vg, ntracet/), 'real(8)', status)
  572. call SetDim(Sds, 0, 'nbudg', 'horizontal budget', (/(j, j=1,nbudg)/), status)
  573. call SetDim(Sds, 1, 'nbud_vg', 'vertical budget', (/(j, j=1,nbud_vg)/), status)
  574. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1,ntracet)/), status)
  575. IF_NOTOK_RETURN(status=1)
  576. call WriteData(Sds, budadvzg_all, status)
  577. IF_NOTOK_RETURN(status=1)
  578. call Done(Sds, status)
  579. IF_NOTOK_RETURN(status=1)
  580. call Init(Sds, io, 'budconv_nocp', (/nbudg, nbud_vg, ntracet/), 'real(8)', status)
  581. call SetDim(Sds, 0, 'nbudg', 'horizontal budget', (/(j, j=1,nbudg)/), status)
  582. call SetDim(Sds, 1, 'nbud_vg', 'vertical budget', (/(j, j=1,nbud_vg)/), status)
  583. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1,ntracet)/), status)
  584. IF_NOTOK_RETURN(status=1)
  585. call WriteAttribute(Sds, 'comment', 'Convection budget not corrected for cp removal', status)
  586. IF_NOTOK_RETURN(status=1)
  587. call WriteData(Sds, budconvg_all, status)
  588. IF_NOTOK_RETURN(status=1)
  589. call Done(Sds, status)
  590. IF_NOTOK_RETURN(status=1)
  591. end if ! root
  592. ! PLS: old unclear comment:
  593. ! Jottum. We have the chemistry. We have it before dry deposition.
  594. ! Let us not write it down. That is an idea
  595. ! Chemistry is done by budget_global
  596. ! Dry deposition is done by chemistry
  597. ! That is logical. We do not write chemistry here, because 'chemistry', the one
  598. ! about dry deposition can access it. And we need dry deposition (that is not accessible).
  599. ! because chemistry has been infested by dry deposition.
  600. ! Gather and write the extra flux through 2D slices
  601. if (apply_budget_global_flux) then
  602. do region=1,nregions
  603. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  604. call GATHER_I_BAND( dgrid(region), budget_flux(region)%flux_x1, budget_flux_all(region)%flux_x1, status, iflux1(region) )
  605. IF_NOTOK_RETURN(status=1)
  606. if (isRoot) then
  607. call Init(Sds, io, 'budget_flux_x1_'//region_name(region), (/jm(region),lm(region),ntracet/), 'real(4)', status)
  608. call SetDim(Sds, 0, 'jm_'//region_name(region), 'latitude index', (/(j, j=1,jm(region))/), status)
  609. call SetDim(Sds, 1, 'lm_'//region_name(region), 'layer index ', (/(j, j=1,lm(region))/), status)
  610. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1,ntracet)/), status)
  611. IF_NOTOK_RETURN(status=1)
  612. call WriteData(Sds, budget_flux_all(region)%flux_x1, status)
  613. IF_NOTOK_RETURN(status=1)
  614. call Done(Sds, status)
  615. IF_NOTOK_RETURN(status=1)
  616. end if
  617. call GATHER_I_BAND( dgrid(region), budget_flux(region)%flux_x2, budget_flux_all(region)%flux_x1, status, iflux2(region) )
  618. IF_NOTOK_RETURN(status=1)
  619. if (isRoot) then
  620. call Init(Sds, io, 'budget_flux_x2_'//region_name(region), (/jm(region),lm(region),ntracet/), 'real(4)', status)
  621. call SetDim(Sds, 0, 'jm_'//region_name(region), 'latitude index', (/(j, j=1,jm(region))/), status)
  622. call SetDim(Sds, 1, 'lm_'//region_name(region), 'layer index ', (/(j, j=1,lm(region))/), status)
  623. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1,ntracet)/), status)
  624. IF_NOTOK_RETURN(status=1)
  625. call WriteData(Sds, budget_flux_all(region)%flux_x1, status)
  626. IF_NOTOK_RETURN(status=1)
  627. call Done(Sds, status)
  628. IF_NOTOK_RETURN(status=1)
  629. end if
  630. call GATHER_J_BAND( dgrid(region), budget_flux(region)%flux_y1, budget_flux_all(region)%flux_y1, status, jflux1(region) )
  631. IF_NOTOK_RETURN(status=1)
  632. if (isRoot) then
  633. call Init(Sds, io, 'budget_flux_y1_'//region_name(region), (/im(region),lm(region),ntracet/), 'real(4)', status)
  634. call SetDim(Sds, 0, 'im_'//region_name(region), 'longitude index', (/(j, j=1,im(region))/), status)
  635. call SetDim(Sds, 1, 'lm_'//region_name(region), 'layer index ', (/(j, j=1,lm(region))/), status)
  636. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1,ntracet)/), status)
  637. IF_NOTOK_RETURN(status=1)
  638. call WriteData(Sds, budget_flux_all(region)%flux_y1, status)
  639. IF_NOTOK_RETURN(status=1)
  640. call Done(Sds, status)
  641. IF_NOTOK_RETURN(status=1)
  642. end if
  643. call GATHER_J_BAND( dgrid(region), budget_flux(region)%flux_y2, budget_flux_all(region)%flux_y1, status, jflux2(region) )
  644. IF_NOTOK_RETURN(status=1)
  645. if (isRoot) then
  646. call Init(Sds, io, 'budget_flux_y2_'//region_name(region), (/im(region),lm(region),ntracet/), 'real(4)', status)
  647. call SetDim(Sds, 0, 'im_'//region_name(region), 'longitude index', (/(j, j=1,im(region))/), status)
  648. call SetDim(Sds, 1, 'lm_'//region_name(region), 'layer index ', (/(j, j=1,lm(region))/), status)
  649. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1,ntracet)/), status)
  650. IF_NOTOK_RETURN(status=1)
  651. call WriteData(Sds, budget_flux_all(region)%flux_y1, status)
  652. IF_NOTOK_RETURN(status=1)
  653. call Done(Sds, status)
  654. IF_NOTOK_RETURN(status=1)
  655. end if
  656. call GATHER( dgrid(region), budget_flux(region)%flux_z1, budget_flux_all(region)%flux_z1, 0, status )
  657. IF_NOTOK_RETURN(status=1)
  658. if (isRoot) then
  659. call Init(Sds, io, 'budget_flux_z1_'//region_name(region), (/im(region),jm(region),ntracet/), 'real(4)', status)
  660. call SetDim(Sds, 0, 'im_'//region_name(region), 'longitude index', (/(j, j=1,im(region))/), status)
  661. call SetDim(Sds, 1, 'jm_'//region_name(region), 'latitude index ', (/(j, j=1,jm(region))/), status)
  662. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1,ntracet)/), status)
  663. IF_NOTOK_RETURN(status=1)
  664. call WriteData(Sds, budget_flux_all(region)%flux_z1, status)
  665. IF_NOTOK_RETURN(status=1)
  666. call Done(Sds, status)
  667. IF_NOTOK_RETURN(status=1)
  668. end if
  669. call GATHER( dgrid(region), budget_flux(region)%flux_z2, budget_flux_all(region)%flux_z1, 0, status )
  670. IF_NOTOK_RETURN(status=1)
  671. if (isRoot) then
  672. call Init(Sds, io, 'budget_flux_z2_'//region_name(region), (/im(region),jm(region),ntracet/), 'real(4)', status)
  673. call SetDim(Sds, 0, 'im_'//region_name(region), 'longitude index', (/(j, j=1,im(region))/), status)
  674. call SetDim(Sds, 1, 'jm_'//region_name(region), 'latitude index ', (/(j, j=1,jm(region))/), status)
  675. call SetDim(Sds, 2, 'ntracet', 'tracer number', (/(j, j=1,ntracet)/), status)
  676. IF_NOTOK_RETURN(status=1)
  677. call WriteData(Sds, budget_flux_all(region)%flux_z1, status)
  678. IF_NOTOK_RETURN(status=1)
  679. call Done(Sds, status)
  680. IF_NOTOK_RETURN(status=1)
  681. end if
  682. deallocate( budget_flux(region)%flux_x1)
  683. deallocate( budget_flux(region)%flux_y1)
  684. deallocate( budget_flux(region)%flux_z1)
  685. deallocate( budget_flux(region)%flux_x2)
  686. deallocate( budget_flux(region)%flux_y2)
  687. deallocate( budget_flux(region)%flux_z2)
  688. deallocate( budget_flux_all(region)%flux_x1)
  689. deallocate( budget_flux_all(region)%flux_y1)
  690. deallocate( budget_flux_all(region)%flux_z1)
  691. deallocate( budg_dat(region)%nzong)
  692. end do
  693. endif ! apply_budget_flux
  694. if (isRoot) then
  695. call Done(io, status)
  696. IF_NOTOK_RETURN(status=1)
  697. end if
  698. call budget_displayg ( status )
  699. IF_NOTOK_RETURN(status=1)
  700. ! OK
  701. status = 0
  702. END SUBROUTINE DONE_BUDGET_GLOBAL
  703. !EOC
  704. !--------------------------------------------------------------------------
  705. ! TM5 !
  706. !--------------------------------------------------------------------------
  707. !BOP
  708. !
  709. ! !IROUTINE: BUDGET_TRANSPORTG
  710. !
  711. ! !DESCRIPTION: evaluate advection/convection budgets
  712. !
  713. ! Routine is called before and after a transport step. The difference is used to
  714. ! calculate the budget.
  715. !\\
  716. !\\
  717. ! !INTERFACE:
  718. !
  719. SUBROUTINE BUDGET_TRANSPORTG(region, stat, proces, prev_step)
  720. !
  721. ! !USES:
  722. !
  723. use dims, only : okdebug
  724. use global_data, only : region_dat, mass_dat
  725. !
  726. ! !INPUT PARAMETERS:
  727. !
  728. integer, intent(in) :: stat ! 0 before process, 1 after
  729. integer, intent(in) :: region
  730. character(len=*) :: proces ! current process (xyzvcs)
  731. character(len=*) :: prev_step ! previous process.
  732. !
  733. ! !REVISION HISTORY:
  734. ! 28 Feb 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  735. !
  736. !EOP
  737. !------------------------------------------------------------------------
  738. !BOC
  739. real, dimension(:,:,:,:), pointer :: rm
  740. ! integer, dimension(:,:), pointer :: zoomed, edge
  741. ! logical, dimension(:,:), allocatable :: skip_flag
  742. integer :: i,j,l,n, nzone, nzone_v, lmr, i1,j1,i2,j2
  743. ! ------ start
  744. if (.not.apply_budget_global) return
  745. rm => mass_dat(region)%rm
  746. ! zoomed => region_dat(region)%zoomed
  747. ! edge => region_dat(region)%edge
  748. lmr = lm(region)
  749. ! if ( okdebug ) then
  750. ! write(gol,*) 'budget_transportg: region, stat, proces, prev_step = ',&
  751. ! region, stat, proces,' ', prev_step; call goPr
  752. ! end if
  753. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  754. !---------- flag
  755. ! allocate(skip_flag(i1:i2,j1:j2))
  756. ! skip_flag = .false.
  757. ! where ( zoomed /= region .or. edge >= 1 )
  758. ! skip_flag = .true.
  759. ! end where
  760. ! if ( proces(1:4) == 'advx' .and. prev_step /= 'y' ) then
  761. ! ! include y-edges if XYZ sequence
  762. ! where(edge >= 2)
  763. ! skip_flag = .false. !only remaining problem: reduced grid!
  764. ! end where
  765. ! else if ( proces(1:4) == 'advy' .and. prev_step /= 'x' ) then
  766. ! where ( edge == 1 .or. edge == 3 )
  767. ! skip_flag = .false.
  768. ! end where
  769. ! else if ( proces(1:4) == 'advz' .and. prev_step /= 'y' ) then
  770. ! ! zyx sequence: include interface
  771. ! where ( edge >= 1 )
  772. ! skip_flag = .false.
  773. ! end where
  774. ! else if ( proces(1:4) == 'conv' ) then ! always interface
  775. ! where ( edge >= 1 )
  776. ! skip_flag = .false.
  777. ! end where
  778. ! end if
  779. !----------- Calculate budget
  780. if ( stat == 0 ) then ! save current tracer concentrations
  781. rmoldg = 0.0
  782. do n=1, ntracet
  783. do l=1,lmr
  784. nzone_v = nzon_vg(l)
  785. do j=j1, j2
  786. do i=i1, i2
  787. !if (skip_flag(i,j)) cycle
  788. nzone = budg_dat(region)%nzong(i,j)
  789. rmoldg(nzone,nzone_v,n) = &
  790. rmoldg(nzone,nzone_v,n) + rm(i,j,l,n)
  791. end do
  792. end do
  793. end do
  794. end do
  795. else ! new concentration and fill budget
  796. rmnewg = 0.0
  797. do n=1, ntracet
  798. do l=1,lmr
  799. nzone_v = nzon_vg(l)
  800. do j=j1,j2
  801. do i=i1,i2
  802. !if (skip_flag(i,j)) cycle
  803. nzone=budg_dat(region)%nzong(i,j)
  804. rmnewg(nzone,nzone_v,n) = rmnewg(nzone,nzone_v,n) + rm(i,j,l,n)
  805. end do
  806. end do
  807. end do
  808. end do
  809. select CASE(proces(1:4))
  810. case('advx')
  811. do n=1, ntracet
  812. budadvxg(:,:,n) = budadvxg(:,:,n) + &
  813. (rmnewg(:,:,n)-rmoldg(:,:,n))/ra(n)*1e3
  814. end do
  815. case('advy')
  816. do n=1, ntracet
  817. budadvyg(:,:,n) = budadvyg(:,:,n) + &
  818. (rmnewg(:,:,n)-rmoldg(:,:,n))/ra(n)*1e3
  819. end do
  820. case('advz')
  821. do n=1, ntracet
  822. budadvzg(:,:,n) = budadvzg(:,:,n) + &
  823. (rmnewg(:,:,n)-rmoldg(:,:,n))/ra(n)*1e3
  824. end do
  825. case('conv')
  826. do n=1, ntracet
  827. budconvg(:,:,n) = budconvg(:,:,n) + &
  828. (rmnewg(:,:,n)-rmoldg(:,:,n))/ra(n)*1e3
  829. end do
  830. case default
  831. write(gol,*)'budget_transportg: no valid value for transport budget,', &
  832. ' budget not updated!'
  833. call goPr
  834. end select
  835. end if
  836. ! deallocate(skip_flag)
  837. nullify(rm)
  838. ! nullify(zoomed)
  839. ! nullify(edge)
  840. END SUBROUTINE BUDGET_TRANSPORTG
  841. !EOC
  842. !--------------------------------------------------------------------------
  843. ! TM5 !
  844. !--------------------------------------------------------------------------
  845. !BOP
  846. !
  847. ! !IROUTINE: BUDGET_DISPLAYG
  848. !
  849. ! !DESCRIPTION: print out budget for tracer #1
  850. !\\
  851. !\\
  852. ! !INTERFACE:
  853. !
  854. SUBROUTINE BUDGET_DISPLAYG( status )
  855. !
  856. ! !USES:
  857. !
  858. use dims, only : nregions
  859. use chem_param, only : names
  860. use global_data, only : mass_dat
  861. use partools , only : isRoot
  862. use file_hdf, only : THdfFile
  863. use file_hdf, only : Init, Done, WriteAttribute, WriteData
  864. !
  865. ! !OUTPUT PARAMETERS:
  866. !
  867. integer, intent(out) :: status
  868. !
  869. ! !REVISION HISTORY:
  870. ! 28 Feb 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  871. !
  872. !EOP
  873. !------------------------------------------------------------------------
  874. !BOC
  875. type(THdfFile) :: io
  876. character(len=40) :: frmt
  877. integer :: region, imr, jmr, lmr
  878. real :: mass(nregions)
  879. character(len=*), parameter :: rname = mname//'/budget_displayg'
  880. ! --- begin --------------------------------
  881. if (.not.apply_budget_global) return
  882. if ( isRoot ) then
  883. write (gol,'("--------------------------------------------------------")'); call goPr
  884. write (gol,'(" Budget of tracer ",a," (kg) : ")') trim(names(1)) ; call goPr
  885. write (gol,'("--------------------------------------------------------")'); call goPr
  886. end if
  887. do region = 1, nregions
  888. call REDUCE( dgrid(region), mass_dat(region)%rm(:,:,:,1), mass_dat(region)%halo, 'SUM', mass(region), status)
  889. IF_NOTOK_RETURN(status=1)
  890. call get_format(mass(region),frmt)
  891. if ( isRoot ) then
  892. !write (gol,'("Region ",i3)') region; call goPr
  893. write (gol,frmt) 'Initial mass : ',init_mass(region); call goPr
  894. ! write (gol,frmt) 'mass emitted : ',sum_emission(region); call goPr
  895. ! write (gol,frmt) 'chemistry : ',sum_chemistry_all; call goPr
  896. ! write (gol,frmt) 'wet chemistry : ',-sum_wetchem_all; call goPr
  897. write (gol,frmt) 'update_p : ',sum_update(region); call goPr
  898. write (gol,frmt) 'advection : ',sum_advection(region); call goPr
  899. ! write (gol,frmt) 'deposition : ',sum_deposition(region); call goPr
  900. ! write (gol,frmt) 'stratosphere : ',sum_stratosphere(region); call goPr
  901. write (gol,frmt) 'Final mass : ',mass(region); call goPr
  902. write (gol,frmt) 'Budget (error) : ', &
  903. init_mass(region) +sum_advection(region) +sum_update(region)-mass(region) ; call goPr
  904. ! write (gol,frmt) 'Budget (error) : ', &
  905. ! init_mass(region) + sum_emission(region) &
  906. ! +sum_advection(region) + sum_chemistry_all &
  907. ! +sum_update(region) &
  908. ! +sum_deposition(region) + sum_stratosphere(region) - sum_wetchem_all - mass; call goPr
  909. write (gol,'("--------------------------------------------------------")'); call goPr
  910. end if
  911. end do
  912. if ( isRoot ) then
  913. call Init(io, budget_file_global, 'write', status)
  914. IF_NOTOK_RETURN(status=1)
  915. call WriteAttribute(io, 'initial mass', init_mass, status)
  916. IF_NOTOK_RETURN(status=1)
  917. call WriteAttribute(io, 'final mass', mass, status)
  918. IF_NOTOK_RETURN(status=1)
  919. call WriteAttribute(io, 'sum_advection', sum_advection, status)
  920. IF_NOTOK_RETURN(status=1)
  921. call WriteAttribute(io, 'sum_update', sum_update, status)
  922. IF_NOTOK_RETURN(status=1)
  923. call Done(io,status)
  924. IF_NOTOK_RETURN(status=1)
  925. endif
  926. ! ok
  927. status = 0
  928. END SUBROUTINE BUDGET_DISPLAYG
  929. !EOC
  930. !--------------------------------------------------------------------------
  931. ! TM5 !
  932. !--------------------------------------------------------------------------
  933. !BOP
  934. !
  935. ! !IROUTINE: GET_FORMAT
  936. !
  937. ! !DESCRIPTION: returns convenient format to write a real
  938. !\\
  939. !\\
  940. ! !INTERFACE:
  941. !
  942. SUBROUTINE GET_FORMAT( mm, frmt)
  943. !
  944. ! !INPUT PARAMETERS:
  945. !
  946. real, intent(in) :: mm
  947. !
  948. ! !OUTPUT PARAMETERS:
  949. !
  950. character(len=*), intent(out) :: frmt
  951. !
  952. !EOP
  953. !------------------------------------------------------------------------
  954. !BOC
  955. integer :: is
  956. if ( mm > 0.0 ) then
  957. is = int(alog10(mm))
  958. else
  959. is = 0
  960. end if
  961. select case(is)
  962. case(1:10)
  963. write (frmt,'(a9,i1,a1)') '(a30,f14.', 10-is, ')'
  964. case default
  965. frmt = '(a30,1pe12.5)'
  966. end select
  967. END SUBROUTINE GET_FORMAT
  968. !EOC
  969. END MODULE BUDGET_GLOBAL