calc_pm.F90 8.4 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243
  1. #define TRACEBACK write (gol,'("in ",a," (",a,i6,")")') rname, __FILE__, __LINE__ ; call goErr
  2. #define IF_NOTOK_RETURN(action) if (status/=0) then; TRACEBACK; action; return; end if
  3. #define IF_ERROR_RETURN(action) if (status> 0) then; TRACEBACK; action; return; end if
  4. !
  5. #include "tm5.inc"
  6. !-----------------------------------------------------------------------------
  7. ! TM5 !
  8. !-----------------------------------------------------------------------------
  9. !BOP
  10. !
  11. ! !MODULE: CALC_PM
  12. !
  13. ! !DESCRIPTION: PM module to calculate particulate matter concentrations for
  14. ! user defined aerodynamic diameters
  15. !\\
  16. !\\
  17. ! !INTERFACE:
  18. !
  19. MODULE CALC_PM
  20. !
  21. ! !USES:
  22. !
  23. USE GO, only : gol, goErr, goPr
  24. IMPLICIT NONE
  25. PRIVATE
  26. !
  27. ! !PUBLIC MEMBER FUNCTIONS:
  28. !
  29. Public :: PMX_Integrate_3d
  30. !
  31. ! !PRIVATE DATA MEMBERS:
  32. !
  33. character(len=*), parameter :: mname = 'calc_pm'
  34. Real, Parameter :: hr2 = 0.5*sqrt(2.0)
  35. !
  36. ! !REVISION HISTORY:
  37. ! 1 Oct 2010 - Achim Strunk - Revised and made suitable for 3D and stations
  38. ! 19 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  39. !
  40. ! !REMARKS:
  41. ! (1) module used only if with_m7 is used
  42. !
  43. !EOP
  44. !------------------------------------------------------------------------
  45. CONTAINS
  46. !--------------------------------------------------------------------------
  47. ! TM5 !
  48. !--------------------------------------------------------------------------
  49. !BOP
  50. !
  51. ! !IROUTINE: PMX_Integrate_0d
  52. !
  53. ! !DESCRIPTION: This routine generates a pmx value for a given grid cell
  54. ! Arbitrary radii may be specified.
  55. ! NO3 and NH4 come from EQSAM and are considered to be in
  56. ! the accumulation mode.
  57. !\\
  58. !\\
  59. ! !INTERFACE:
  60. !
  61. Subroutine PMX_Integrate_0d(region, is, js, ls, isizelimit, pmx, status)
  62. !
  63. ! !USES:
  64. !
  65. Use tracer_data, only : mass_dat
  66. ! I need to convert (/kg air) to (/m3 air)
  67. use chem_param, only : iso4nus
  68. use chem_param, only : iso4ais, ibcais, ipomais
  69. use chem_param, only : iso4acs, ibcacs, ipomacs, issacs, iduacs
  70. use chem_param, only : iso4cos, ibccos, ipomcos, isscos, iducos
  71. use chem_param, only : ibcaii, ipomaii, iduaci
  72. use chem_param, only : iducoi, ino3_a, inh4
  73. Use mo_aero_m7, only : nmod, cmedr2mmedr, sigma
  74. Use m7_data, only : h2o_mode, rw_mode
  75. ! To rewrite ug / cell to ug/m3
  76. Use global_data, only : region_dat
  77. Use Meteodata, only : gph_dat
  78. !
  79. ! !INPUT PARAMETERS:
  80. !
  81. Integer, Intent(In) :: region
  82. real, intent(in) :: isizelimit
  83. integer, Intent(in) :: is, js, ls
  84. !
  85. ! !OUTPUT PARAMETERS:
  86. !
  87. Integer, Intent(out) :: status
  88. real, Intent(out) :: pmx ! units = 'kg/m3'
  89. !
  90. ! !REVISION HISTORY:
  91. ! 7 Oct 2010 - Achim Strunk - v0
  92. ! 19 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  93. !
  94. !EOP
  95. !------------------------------------------------------------------------
  96. !BOC
  97. character(len=*), parameter :: rname = mname//'/PMX_Integrate_0d'
  98. Integer :: imod
  99. Real :: z, rad, sizelimit
  100. Real :: volume ! For converting mass to mass/volume
  101. Real, Dimension(nmod) :: modfrac ! Length: Number of M7 modes (7)
  102. Real, Dimension(nmod) :: lnsigma
  103. ! --- begin -------------------------------------
  104. lnsigma = log(sigma)
  105. ! We can convert micrometers diameter to meters radius. One micrometer diameter is 5.e-7 meter radius.
  106. sizelimit = isizelimit * 5.e-7
  107. ! initialise target value
  108. pmx = 0.0
  109. Do imod = 1, nmod
  110. ! Calculate the median radius of the volume weighted distribution.
  111. rad = rw_mode(region,imod)%d3(is,js,ls) * cmedr2mmedr(imod)
  112. !! if( rad == 0.0 ) then ! changed to a precision depending value
  113. if( rad < 100*TINY(1.0) ) then
  114. modfrac(imod) = 1.0 ! Should not matter, because if the radius is zero,
  115. ! there are no aerosols. But in principle, it would
  116. ! mean that all aerosols are infinitely small, so
  117. ! they would fit in any PM-class.
  118. else
  119. z = ( log(sizelimit) - log(rad) ) / lnsigma(imod)
  120. modfrac(imod) = 0.5 + 0.5 * ERF(z*hr2)
  121. end if
  122. end do
  123. ! And the volume. This is the nicest and cleanest line of code of this whole module.
  124. volume = ( gph_dat(region)%data(is,js,ls+1) - gph_dat(region)%data(is,js,ls) ) * &
  125. region_dat(region)%dxyp(js)
  126. pmx = pmx + mass_dat(region)%rm(is,js,ls, iso4nus) * modfrac(1) / volume
  127. pmx = pmx + mass_dat(region)%rm(is,js,ls, iso4ais) * modfrac(2) / volume
  128. pmx = pmx + mass_dat(region)%rm(is,js,ls, iso4acs) * modfrac(3) / volume
  129. pmx = pmx + mass_dat(region)%rm(is,js,ls, iso4cos) * modfrac(4) / volume
  130. pmx = pmx + mass_dat(region)%rm(is,js,ls, ibcais ) * modfrac(2) / volume
  131. pmx = pmx + mass_dat(region)%rm(is,js,ls, ibcacs ) * modfrac(3) / volume
  132. pmx = pmx + mass_dat(region)%rm(is,js,ls, ibccos ) * modfrac(4) / volume
  133. pmx = pmx + mass_dat(region)%rm(is,js,ls, ibcaii ) * modfrac(5) / volume
  134. pmx = pmx + mass_dat(region)%rm(is,js,ls, ipomais) * modfrac(2) / volume
  135. pmx = pmx + mass_dat(region)%rm(is,js,ls, ipomacs) * modfrac(3) / volume
  136. pmx = pmx + mass_dat(region)%rm(is,js,ls, ipomcos) * modfrac(4) / volume
  137. pmx = pmx + mass_dat(region)%rm(is,js,ls, ipomaii) * modfrac(5) / volume
  138. pmx = pmx + mass_dat(region)%rm(is,js,ls, issacs ) * modfrac(3) / volume
  139. pmx = pmx + mass_dat(region)%rm(is,js,ls, isscos ) * modfrac(4) / volume
  140. pmx = pmx + mass_dat(region)%rm(is,js,ls, iduacs ) * modfrac(3) / volume
  141. pmx = pmx + mass_dat(region)%rm(is,js,ls, iducos ) * modfrac(4) / volume
  142. pmx = pmx + mass_dat(region)%rm(is,js,ls, iduaci ) * modfrac(6) / volume
  143. pmx = pmx + mass_dat(region)%rm(is,js,ls, iducoi ) * modfrac(7) / volume
  144. pmx = pmx + mass_dat(region)%rm(is,js,ls, ino3_a ) * modfrac(3) / volume
  145. pmx = pmx + mass_dat(region)%rm(is,js,ls, inh4 ) * modfrac(3) / volume
  146. ! Count the water
  147. pmx = pmx + h2o_mode(region,1)%d3(is,js,ls)*modfrac(1) / volume
  148. pmx = pmx + h2o_mode(region,2)%d3(is,js,ls)*modfrac(2) / volume
  149. pmx = pmx + h2o_mode(region,3)%d3(is,js,ls)*modfrac(3) / volume
  150. pmx = pmx + h2o_mode(region,4)%d3(is,js,ls)*modfrac(4) / volume
  151. status = 0
  152. End Subroutine PMX_INTEGRATE_0D
  153. !EOC
  154. !--------------------------------------------------------------------------
  155. ! TM5 !
  156. !--------------------------------------------------------------------------
  157. !BOP
  158. !
  159. ! !IROUTINE: PMX_Integrate_3d
  160. !
  161. ! !DESCRIPTION: This routine uses PMX_Integrate_0d for generating a 3d
  162. ! array (over im, jm, lm) of pmx.
  163. ! Arbitrary radii may be specified.
  164. !\\
  165. !\\
  166. ! !INTERFACE:
  167. !
  168. SUBROUTINE PMX_Integrate_3d( region, isizelimit, pmx, status )
  169. !
  170. ! !USES:
  171. !
  172. USE DIMS, ONLY : im, jm, lm
  173. USE TM5_DISTGRID, ONLY : dgrid, Get_DistGrid, gather, scatter_i_band
  174. !
  175. ! !INPUT PARAMETERS:
  176. !
  177. INTEGER, INTENT(in) :: region
  178. REAL, INTENT(in) :: isizelimit
  179. !
  180. ! !OUTPUT PARAMETERS:
  181. !
  182. INTEGER, INTENT(out) :: status
  183. REAL, DIMENSION(:,:,:), INTENT(out) :: pmx
  184. !
  185. ! !REVISION HISTORY:
  186. ! 7 Oct 2010 - Achim Strunk - v0
  187. ! 19 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  188. !
  189. ! !REMARKS:
  190. !
  191. !EOP
  192. !------------------------------------------------------------------------
  193. !BOC
  194. CHARACTER(len=*), PARAMETER :: rname = mname//'/PMX_Integrate_3d'
  195. INTEGER :: is, js, ls, i1, i2, j1, j2
  196. REAL :: pmxl
  197. ! reset value
  198. pmx = 0.0
  199. CALL GET_DISTGRID( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  200. DO ls = 1, lm(region)
  201. DO js = j1, j2
  202. DO is = i1, i2
  203. CALL pmx_integrate_0d( region, is, js, ls, isizelimit, pmxl, status )
  204. IF_NOTOK_RETURN( status=1 )
  205. pmx(is,js,ls) = pmxl
  206. END DO
  207. END DO
  208. END DO
  209. status = 0
  210. END SUBROUTINE PMX_Integrate_3d
  211. !EOC
  212. END MODULE CALC_PM