budget_global.F90 46 KB

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