budget_global__detailed.F90 45 KB

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