wet_deposition.F90 60 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602
  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: WET_DEPOSITION
  15. !
  16. ! !DESCRIPTION: holds convective precipitation (CP) and large scale
  17. ! precipitation (LSP) budgets variables.
  18. !
  19. ! has all routines to deal with LSP, since it is done here. CP
  20. ! is done in convection.
  21. !
  22. ! **** THIS VERSION DIFFERS FROM THE BASE IN TWO THRESHOLD VALUES ****
  23. !
  24. ! (1) Scale factor relative to 100% scavenging (of HNO3) for scavenging
  25. ! type = 2 (ie variable factor, using henry solubility) is non-zero and
  26. ! computed if henry coeff > 1 (instead of 10 in base code).
  27. !
  28. ! (2) Wet removal rates: in case of in-cloud scavenging, test on cloud
  29. ! cover has a threshold of 0.02 instead of 0.05
  30. !\\
  31. !\\
  32. ! !INTERFACE:
  33. !
  34. MODULE WET_DEPOSITION
  35. !
  36. ! !USES:
  37. !
  38. use GO, only : gol, goErr, goPr
  39. use dims, only : nregions
  40. use chem_param, only : ntracet
  41. use global_types, only : d3_data
  42. use tm5_distgrid, only : dgrid, Get_DistGrid, reduce, gather
  43. use ParTools, only : isRoot
  44. IMPLICIT NONE
  45. PRIVATE
  46. !
  47. ! !PUBLIC MEMBER FUNCTIONS:
  48. !
  49. public :: Wet_Deposition_Init, Wet_Deposition_Done
  50. public :: calc_cvsfac, calculate_lsp_scav, lspscav
  51. !
  52. ! !PUBLIC DATA MEMBERS:
  53. !
  54. real, public :: cvsfac(ntracet) = 0.0 ! scavenging efficiencies, used in convection
  55. real, public :: cp_scale = 0.5 ! default amount of rain (converted to m/s) with maximum CP removal on 1x1 degree
  56. #ifdef with_budgets
  57. real, dimension(nregions), public :: sum_wetdep ! global wet dep budget for tracer #1 (includes both LSP and CP; meaningful on root only)
  58. type, public :: buddep_data
  59. ! budgets in each column, split vertically...
  60. real,dimension(:,:,:,:),pointer :: lsp ! (i, j, nbud_vg, ntracet) computed here
  61. real,dimension(:,:,:,:),pointer :: cp ! (i, j, nbud_vg, ntracet) computed in convection
  62. end type buddep_data
  63. type(buddep_data), dimension(nregions), target, public :: buddep_dat ! ... for each region
  64. #endif
  65. !
  66. ! !PRIVATE DATA MEMBERS:
  67. !
  68. character(len=*), parameter :: mname = 'wet_deposition'
  69. !
  70. ! Large scale scavenging coefficients [s-1]
  71. type(d3_data),dimension(nregions) :: rloss1 ! 1: incloud completely soluble gas
  72. !>>>TvN
  73. type(d3_data),dimension(nregions) :: rloss1_m7 ! as 1, but with ice as efficient as water
  74. ! now needed for M7 aerosols
  75. !<<<TvN
  76. type(d3_data),dimension(nregions) :: rloss2 ! 2: below cloud completely soluble gas
  77. type(d3_data),dimension(nregions) :: rloss3 ! 3: below cloud bulk aerosol (Whitby distribution)
  78. !
  79. ! rain-out can not be higher than maximum level of convection
  80. ! thus maximum level of convection lmax_conv(=>ntot_ed) is used
  81. !
  82. !
  83. ! used from chem_param:
  84. !
  85. ! nscav : selected species for scavenging
  86. ! nscav_index : index for scavenging:
  87. ! nscav_type : type of scavenging:
  88. ! 0 no scavenging
  89. ! 1 scavenging 100 % solubility assumed
  90. ! 2 scavenging henry solubility assumed
  91. ! 3 scavenging, bulk aerosol removal assumed
  92. ! 4 scavenging, special case for SO2 with aq phase diss.
  93. ! 5-11 scavenging, M7 aerosol removal
  94. !
  95. !----------------------------------------------
  96. ! acidity needed for explicit calculation of reactive removal of SO2.
  97. ! Parameterisation calculates reaction of SO2 with H2O2 and O3.
  98. ! Not yet implemented: for information Frank Dentener ! see routine wetS
  99. ! nacid : selected species for acidity
  100. ! nacid_index : indices of species for acidity : iso4,imsa,ihno3,inh3,inh4
  101. ! nacid_eq : equivalents acid per mole
  102. ! integer,parameter :: nacid=5
  103. ! integer,parameter,dimension(nacid) :: &
  104. ! nacid_index = (/iso4,imsa,ihno3,ino3_a,inh3,inh4/)
  105. ! integer,parameter,dimension(nacid) :: &
  106. ! nacid_eq = (/ 2, 1, 1, 1 , -1, -1/)
  107. !----------------------------------------------
  108. !
  109. ! !REVISION HISTORY:
  110. ! version March 2003, adapted for TM5 MK from KNMI version
  111. ! 29 Feb 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  112. !
  113. ! !REMARKS:
  114. !
  115. !EOP
  116. !------------------------------------------------------------------------
  117. CONTAINS
  118. !--------------------------------------------------------------------------
  119. ! TM5 !
  120. !--------------------------------------------------------------------------
  121. !BOP
  122. !
  123. ! !IROUTINE: WET_DEPOSITION_INIT
  124. !
  125. ! !DESCRIPTION:
  126. !\\
  127. !\\
  128. ! !INTERFACE:
  129. !
  130. SUBROUTINE WET_DEPOSITION_INIT( status )
  131. !
  132. ! !USES:
  133. !
  134. use GO, only : TrcFile, Init, Done, ReadRc
  135. use dims, only : lmax_conv
  136. use global_data, only : rcfile
  137. use meteodata, only : Set, temper_dat, lwc_dat, iwc_dat, cc_dat, lsp_dat
  138. #ifdef with_budgets
  139. use budget_global, only : nbud_vg
  140. #endif
  141. use chem_param, only : ntrace
  142. !
  143. ! !OUTPUT PARAMETERS:
  144. !
  145. integer, intent(out) :: status
  146. !
  147. ! !REVISION HISTORY:
  148. ! 29 Feb 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  149. !
  150. !EOP
  151. !------------------------------------------------------------------------
  152. !BOC
  153. character(len=*), parameter :: rname = mname//'/Wet_Deposition_Init'
  154. integer :: region, imr,jmr,lmr, i1, i2, j1, j2
  155. type(TrcFile) :: rcF
  156. ! --- begin ------------------------------------
  157. ! select meteo to be used
  158. do region = 1, nregions
  159. call Set( temper_dat(region), status, used=.true. )
  160. call Set( lwc_dat(region), status, used=.true. )
  161. call Set( iwc_dat(region), status, used=.true. )
  162. call Set( cc_dat(region), status, used=.true. )
  163. call Set( lsp_dat(region), status, used=.true. )
  164. end do
  165. ! allocate
  166. do region = 1, nregions
  167. lmr = lmax_conv
  168. CALL GET_DISTGRID( DGRID(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  169. allocate(rloss1(region)%d3(i1:i2, j1:j2, lmr))
  170. !>>>TvN
  171. allocate(rloss1_m7(region)%d3(i1:i2, j1:j2, lmr))
  172. !<<<TvN
  173. allocate(rloss2(region)%d3(i1:i2, j1:j2, lmr))
  174. allocate(rloss3(region)%d3(i1:i2, j1:j2, lmr))
  175. end do
  176. ! read settings from rcfile:
  177. ! o scaling factor wet removal (1.-exp(-cp/cp_scale))
  178. ! cp_scale : 0.5
  179. ! (see convection.F90 and wet_deposition.F90)
  180. !
  181. call Init( rcF, rcfile, status )
  182. IF_NOTOK_RETURN(status=1)
  183. call ReadRc( rcF, 'proces.wet_removal.cp_scale', cp_scale, status, default=0.5 )
  184. IF_NOTOK_RETURN(status=1)
  185. call Done( rcF, status )
  186. IF_NOTOK_RETURN(status=1)
  187. write (gol,*) 'maximum removal CP precip on 1x1 at rain rate (mm/hr) :', cp_scale; call goPr
  188. cp_scale = cp_scale/(1e3*3600.) ! to m/s!
  189. ! Calculate removal rates by convective precipitation
  190. ! It was commented before : JEW:called too early, KHENRY must be calculated for some species first
  191. ! Back here, since KHENRY are now calculated before hand with a call to "rates" in sources_sinks_init
  192. call calc_cvsfac
  193. ! budgets
  194. #ifdef with_budgets
  195. do region = 1, nregions
  196. CALL GET_DISTGRID( DGRID(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  197. sum_wetdep(region) = 0.0
  198. allocate( buddep_dat(region)%lsp(i1:i2, j1:j2, nbud_vg, ntracet))
  199. buddep_dat(region)%lsp = 0.0
  200. allocate( buddep_dat(region)%cp (i1:i2, j1:j2, nbud_vg, ntracet))
  201. buddep_dat(region)%cp = 0.0
  202. enddo
  203. #endif
  204. ! ok
  205. status = 0
  206. END SUBROUTINE WET_DEPOSITION_INIT
  207. !EOC
  208. !--------------------------------------------------------------------------
  209. ! TM5 !
  210. !--------------------------------------------------------------------------
  211. !BOP
  212. !
  213. ! !IROUTINE: WET_DEPOSITION_DONE
  214. !
  215. ! !DESCRIPTION: deallocate scavenging coeff. & write wet dep and convection
  216. ! budgets into file.
  217. !\\
  218. !\\
  219. ! !INTERFACE:
  220. !
  221. SUBROUTINE WET_DEPOSITION_DONE( status )
  222. !
  223. ! !USES:
  224. !
  225. use dims, only : nregions, im, jm, lm
  226. use chem_param, only : ntracet
  227. use partools, only : par_reduce_element
  228. #ifdef with_budgets
  229. use budget_global, only : budget_file_global, nbud_vg, budg_dat, nbudg, NHAB
  230. use budget_global, only : budconvg
  231. #ifdef with_hdf4
  232. use file_hdf, only : THdfFile, TSds
  233. use file_hdf, only : Init, Done, WriteAttribute, WriteData, SetDim
  234. #endif
  235. use Dims, only : region_name
  236. #endif
  237. !
  238. ! !OUTPUT PARAMETERS:
  239. !
  240. integer, intent(out) :: status
  241. !
  242. ! !REVISION HISTORY:
  243. ! 29 Feb 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  244. !
  245. !EOP
  246. !------------------------------------------------------------------------
  247. !BOC
  248. character(len=*), parameter :: rname = mname//'/Wet_Deposition_Done'
  249. #ifdef with_budgets
  250. #ifdef with_hdf4
  251. type(THdfFile) :: io
  252. type(TSds) :: sds
  253. #endif
  254. integer :: i1, i2, j1, j2
  255. integer :: nsend,j,i,n,nzone,nzone_v
  256. real,dimension(:,:,:,:),allocatable :: budget4d
  257. real,dimension(nbudg,nbud_vg,ntracet) :: budwet_cp, budwet_lsp ! for one MPI tile
  258. real,dimension(nbudg,nbud_vg,ntracet) :: budconvg_all, budwet_cp_all, budwet_lsp_all !
  259. #endif
  260. integer :: region,l
  261. ! --- begin ----------------------------------
  262. do region = 1, nregions
  263. deallocate( rloss1(region)%d3 )
  264. deallocate( rloss1_m7(region)%d3 )
  265. deallocate( rloss2(region)%d3 )
  266. deallocate( rloss3(region)%d3 )
  267. end do
  268. #ifdef with_budgets
  269. #ifdef with_hdf4
  270. if(isRoot) then
  271. call Init(io, budget_file_global, 'write', status)
  272. IF_NOTOK_RETURN(status=1)
  273. call WriteAttribute(io,'sum_wetdep',sum_wetdep,status)
  274. IF_NOTOK_RETURN(status=1)
  275. call WriteAttribute(io,'cvsfac',cvsfac,status)
  276. IF_NOTOK_RETURN(status=1)
  277. endif
  278. #endif
  279. budwet_cp = 0.0
  280. budwet_lsp = 0.0
  281. ! =============================== Aggregate and write column-like Wet Dep budgets
  282. REG : do region=1,nregions
  283. !---- horizontally aggregates LSP and CP budgets
  284. CALL GET_DISTGRID( DGRID(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  285. do n=1, ntracet
  286. do l=1, nbud_vg
  287. do j=j1,j2
  288. do i=i1,i2
  289. nzone = budg_dat(region)%nzong(i,j)
  290. budwet_lsp(nzone,l,n) = budwet_lsp(nzone,l,n) + buddep_dat(region)%lsp(i,j,l,n)
  291. budwet_cp(nzone,l,n) = budwet_cp(nzone,l,n) + buddep_dat(region)%cp(i,j,l,n)
  292. end do
  293. end do
  294. end do
  295. end do
  296. !-- write Non-Horizontally-Aggregated-Budgets
  297. if (NHAB) then
  298. ! global array to gather data
  299. if (isRoot)then
  300. allocate(budget4d(im(region), jm(region), nbud_vg, ntracet))
  301. else
  302. allocate(budget4d(1,1,1,1))
  303. end if
  304. ! gather and write column-like wet dep LSP budgets
  305. CALL GATHER( dgrid(region), buddep_dat(region)%lsp, budget4d, 0, status)
  306. #ifdef with_hdf4
  307. if(isRoot) then
  308. call Init(Sds,io, 'buddep_dat_lsp_'//region_name(region),(/im(region),jm(region),nbud_vg,ntracet/), 'real(4)', status)
  309. call SetDim(Sds, 0, 'im_'//region_name(region),'longitude', (/(j, j=1,im(region))/), status)
  310. call SetDim(Sds, 1, 'jm_'//region_name(region),'latitude', (/(j, j=1,jm(region))/), status)
  311. call SetDim(Sds, 2, 'nbud_vg','budget level', (/(j, j=1,nbud_vg)/), status)
  312. call SetDim(Sds, 3, 'ntracet','tracer index', (/(j, j=1,ntracet)/), status)
  313. IF_NOTOK_RETURN(status=1)
  314. call WriteData(Sds, budget4d, status)
  315. IF_NOTOK_RETURN(status=1)
  316. call Done(Sds, status)
  317. IF_NOTOK_RETURN(status=1)
  318. endif
  319. #endif
  320. ! gather and write column-like wet dep CP budgets
  321. CALL GATHER( dgrid(region), buddep_dat(region)%cp, budget4d, 0, status)
  322. #ifdef with_hdf4
  323. if(isRoot) then
  324. call Init(Sds,io, 'buddep_dat_cp_'//region_name(region),(/im(region),jm(region),nbud_vg,ntracet/), 'real(4)', status)
  325. call SetDim(Sds, 0, 'im_'//region_name(region),'longitude', (/(j, j=1,im(region))/), status)
  326. call SetDim(Sds, 1, 'jm_'//region_name(region),'latitude', (/(j, j=1,jm(region))/), status)
  327. call SetDim(Sds, 2, 'nbud_vg','budget level', (/(j, j=1,nbud_vg)/), status)
  328. call SetDim(Sds, 3, 'ntracet','tracer index', (/(j, j=1,ntracet)/), status)
  329. call WriteData(Sds, budget4d, status)
  330. IF_NOTOK_RETURN(status=1)
  331. call Done(Sds, status)
  332. IF_NOTOK_RETURN(status=1)
  333. endif
  334. #endif
  335. deallocate(budget4d)
  336. endif ! NHAB
  337. enddo REG ! regions
  338. !================== Write horizontally aggregated Wet Dep (& convection) budgets
  339. ! Sum up contribution from each proc into root array
  340. call PAR_REDUCE_ELEMENT( budwet_cp, 'SUM', budwet_cp_all, status )
  341. IF_NOTOK_RETURN(status=1)
  342. call PAR_REDUCE_ELEMENT( budwet_lsp, 'SUM', budwet_lsp_all, status )
  343. IF_NOTOK_RETURN(status=1)
  344. call PAR_REDUCE_ELEMENT( budconvg, 'SUM', budconvg_all, status )
  345. IF_NOTOK_RETURN(status=1)
  346. if (isRoot) then
  347. ! update convection budget
  348. budconvg_all(:,:,:) = budconvg_all(:,:,:) + budwet_cp(:,:,:)
  349. #ifdef with_hdf4
  350. call Init(Sds, io, 'budconv_cp', (/nbudg, nbud_vg, ntracet/), 'real(8)', status)
  351. IF_NOTOK_RETURN(status=1)
  352. call SetDim(Sds, 0, 'nbudg', 'horizontal region', (/(j, j=1,nbudg)/), status)
  353. call SetDim(Sds, 1, 'nbud_vg', 'vertical layer', (/(j, j=1,nbud_vg)/), status)
  354. call SetDim(Sds, 2, 'ntracet', 'tracer index', (/(j, j=1,ntracet)/), status)
  355. IF_NOTOK_RETURN(status=1)
  356. call WriteAttribute(Sds, 'comment', 'Convection budget corrected for cp removal', status)
  357. IF_NOTOK_RETURN(status=1)
  358. call WriteData(Sds, budconvg_all, status)
  359. IF_NOTOK_RETURN(status=1)
  360. call Done(Sds, status)
  361. IF_NOTOK_RETURN(status=1)
  362. call Init(Sds, io, 'budwet_cp', (/nbudg, nbud_vg, ntracet/), 'real(8)', status)
  363. IF_NOTOK_RETURN(status=1)
  364. call SetDim(Sds, 0, 'nbudg', 'horizontal region', (/(j, j=1,nbudg)/), status)
  365. call SetDim(Sds, 1, 'nbud_vg', 'vertical layer', (/(j, j=1,nbud_vg)/), status)
  366. call SetDim(Sds, 2, 'ntracet', 'tracer index', (/(j, j=1,ntracet)/), status)
  367. IF_NOTOK_RETURN(status=1)
  368. call WriteData(Sds, budwet_cp_all, status)
  369. IF_NOTOK_RETURN(status=1)
  370. call Done(Sds, status)
  371. IF_NOTOK_RETURN(status=1)
  372. call Init(Sds, io, 'budwet_lsp', (/nbudg, nbud_vg, ntracet/), 'real(8)', status)
  373. IF_NOTOK_RETURN(status=1)
  374. call SetDim(Sds, 0, 'nbudg', 'horizontal region', (/(j, j=1,nbudg)/), status)
  375. call SetDim(Sds, 1, 'nbud_vg', 'vertical layer', (/(j, j=1,nbud_vg)/), status)
  376. call SetDim(Sds, 2, 'ntracet', 'tracer index', (/(j, j=1,ntracet)/), status)
  377. IF_NOTOK_RETURN(status=1)
  378. call WriteData(Sds, budwet_lsp_all, status)
  379. IF_NOTOK_RETURN(status=1)
  380. call Done(Sds, status)
  381. IF_NOTOK_RETURN(status=1)
  382. call Done(io, status)
  383. IF_NOTOK_RETURN(status=1)
  384. #endif
  385. endif
  386. do region = 1, nregions
  387. deallocate( buddep_dat(region)%lsp )
  388. deallocate( buddep_dat(region)%cp )
  389. end do
  390. #endif /* WITH_BUDGET */
  391. ! ok
  392. status = 0
  393. END SUBROUTINE WET_DEPOSITION_DONE
  394. !EOC
  395. !--------------------------------------------------------------------------
  396. ! TM5 !
  397. !--------------------------------------------------------------------------
  398. !BOP
  399. !
  400. ! !IROUTINE: CALC_CVSFAC
  401. !
  402. ! !DESCRIPTION: lookup tables, calculate scale factor for convective scavenging
  403. ! relative to 100% scavenging (of HNO3),
  404. ! assuming constant temperature in convective updraft of 273K.
  405. !
  406. ! Factors for different scavenging types are:
  407. !
  408. ! 0) no/low solubility cvsfac=0
  409. ! 1) high solubility cvsfac=1
  410. ! 2) henry solubility cvsfac=variable
  411. ! 3) bulk aerosol cvsfac=0.99
  412. ! For the moment a value of 0.99 is assumed for bulk aerosol.
  413. ! This is the value for the soluble accumulation mode from Stier et al. (JGR, 2005).
  414. ! and presents an upper boundary for bulk aerosols.
  415. ! (A value ~0.9 would probably make more sense, but this would need to be justified
  416. ! with some quantitative argument.)
  417. ! 4) SO2 dissociation cvsfac=variable depending on T and pH and
  418. ! dissociation of H2SO3<-->HSO3(-)<--->SO3(2-)
  419. ! for convective clouds T=273K and pH=5 is chosen
  420. ! 5-11) M7 modes cvsfac set equal to the scavenging parameters from Stier et al. (2005)
  421. ! for convective in-cloud scavenging
  422. !\\
  423. !\\
  424. ! !INTERFACE:
  425. !
  426. SUBROUTINE CALC_CVSFAC
  427. !
  428. ! !USES:
  429. !
  430. use chem_param, only : nscav, nscav_index, nscav_type
  431. use chem_param, only : henry, ntlow, ntemp
  432. use chem_param, only : names
  433. !
  434. ! !REVISION HISTORY:
  435. !
  436. !EOP
  437. !------------------------------------------------------------------------
  438. !BOC
  439. integer :: iscav,n,k
  440. real :: rtl, heff
  441. cvsfac=0.0
  442. do iscav=1,nscav
  443. n=nscav_index(iscav)
  444. ! skip dummy tracers ..
  445. if ( n < 0 ) cycle
  446. ! fill cvsfac given scavenging type:
  447. select case(nscav_type(iscav))
  448. case(0)
  449. cvsfac(n) = 0.0
  450. !>>>TvN
  451. !case(1,3)
  452. case(1)
  453. !<<< TvN
  454. cvsfac(n) = 1.0
  455. case(2)
  456. rtl=8.3148e-8*273. ! phase factor: ratio of aq. phase conc. to total conc.
  457. ! assuming LWC of 1e-6
  458. k=nint(273.-float(ntlow))
  459. k = min(max(1,k),ntemp)
  460. if ( henry(n,k) > 1. ) then
  461. cvsfac(n) = rtl*henry(n,k)/(1.+rtl*henry(n,k))
  462. else
  463. cvsfac(n) = 0.0
  464. end if
  465. !>>>TvN
  466. case(3)
  467. cvsfac(n) = 0.99
  468. !<<<TvN
  469. case(4)
  470. rtl=8.3148e-8*273. ! phase factor: ratio of aq. phase conc. to total conc.o
  471. ! assuming LWC of 1e-6
  472. k=nint(273.-float(ntlow))
  473. k = min(max(1,k),ntemp)
  474. heff = henry(n,k)*3.2e3 ! 3.2e3 factor is dissociation of SO2 and HSO3- at pH=5
  475. cvsfac(n) = rtl*heff/(1.+rtl*heff)
  476. !>>>TvN
  477. case(5) ! soluble nu
  478. !cvsfac(n) = 1.0
  479. cvsfac(n) = 0.2
  480. case(6) ! soluble ai
  481. !cvsfac(n) = 1.0
  482. cvsfac(n) = 0.6
  483. case(7) ! soluble ac
  484. !cvsfac(n) = 1.0
  485. cvsfac(n) = 0.99
  486. case(8) ! soluble co
  487. !cvsfac(n) = 1.0
  488. cvsfac(n) = 0.99
  489. case(9) ! insoluble ai
  490. !cvsfac(n) = 1.0
  491. cvsfac(n) = 0.2
  492. case(10) ! insoluble ac
  493. !cvsfac(n) = 1.0
  494. cvsfac(n) = 0.4
  495. case(11) ! insoluble co
  496. !cvsfac(n) = 1.0
  497. cvsfac(n) = 0.4
  498. !<<<TvN
  499. case default
  500. cvsfac(n) = 0.0
  501. end select
  502. end do
  503. ! info ...
  504. do n = 1, ntracet
  505. if ( cvsfac(n) > 0.0 ) then
  506. write (gol,'(" calc_cvsfac: Scavenging factor species ",i3,x,a,"; factor : ",e10.3)') &
  507. n, names(n), cvsfac(n); call goPr
  508. end if
  509. end do
  510. END SUBROUTINE CALC_CVSFAC
  511. !EOC
  512. !--------------------------------------------------------------------------
  513. ! TM5 !
  514. !--------------------------------------------------------------------------
  515. !BOP
  516. !
  517. ! !IROUTINE: LSPSCAV
  518. !
  519. ! !DESCRIPTION: Calculation of wet removal by large scale precipitation of
  520. ! soluble tracers
  521. !
  522. ! Remove tracers with previously calculated rainout rate [s-1]
  523. ! separately for in- and below cloud scavenging and only for the
  524. ! cloud covered fraction of the gridcell
  525. !
  526. ! Reference:
  527. ! Langner and Rodhe (1990)
  528. ! Junge (1959)
  529. !\\
  530. !\\
  531. ! !INTERFACE:
  532. !
  533. SUBROUTINE LSPSCAV( region )
  534. !
  535. ! !USES:
  536. !
  537. use binas, only : rgas
  538. use dims, only : im, jm, lm, nchem
  539. use dims, only : tref, lmax_conv, dy
  540. use chem_param, only : ntrace, ntracet, henry, ntlow, ra, ntemp
  541. use chem_param, only : xmhno3 !, ihno3
  542. use chem_param, only : nscav, nscav_index, nscav_type
  543. #ifdef with_m7
  544. use chem_param, only : inus_n, iais_n, iacs_n, icos_n, iaii_n, iaci_n, icoi_n
  545. #endif
  546. use meteodata, only : temper_dat, cc_dat
  547. use global_data, only : mass_dat
  548. #ifdef with_budgets
  549. use budget_global, only : nzon_vg
  550. #endif
  551. !
  552. ! !INPUT PARAMETERS:
  553. !
  554. integer,intent(in) :: region
  555. !
  556. ! !REVISION HISTORY:
  557. !
  558. ! Programmed by Frank Dentener, August 1995;
  559. ! Ad Jeuken, KNMI, November 1998
  560. ! Modifications Bas Henzing, KNMI, 2002
  561. ! Adapted for TM5, Frank Dentener, JRC, 2002
  562. ! Paralel, Maarten Krol, Jul 2003
  563. ! 29 Feb 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  564. !
  565. !EOP
  566. !------------------------------------------------------------------------
  567. !BOC
  568. character(len=*), parameter :: rname = mname//'/LSPSCAV'
  569. real :: dt_lagrangian
  570. ! liquid water content of raining cloud
  571. ! rgas (8.314 J/mol/K) ---> 0.08314 atm/(mol/l)/K
  572. ! (thesis Frank Dentener, p. 31)
  573. ! 1e-6 corresponds to 1 g/m3 dimensionless
  574. real,parameter :: rtl_fac=rgas/1e2*1e-6
  575. ! assumed pH of rainwater
  576. real,parameter :: hplus = 1e-5
  577. ! assumed fraction of in-cloud interstitial aerosol:
  578. real,parameter :: interstitial_fraction = 0.3
  579. ! --- local ------------------------------
  580. real,dimension(:,:,:,:), pointer :: rm
  581. #ifdef slopes
  582. real,dimension(:,:,:,:), pointer :: rxm, rym, rzm
  583. #ifdef secmom
  584. real,dimension(:,:,:,:), pointer :: rxxm, rxym, rxzm, ryym, ryzm, rzzm
  585. #endif
  586. #endif
  587. real,dimension(:,:,:), pointer :: t,cc
  588. real :: rtl,f,f1,f2,vol1,vol2,vol3,ahelp1,ahelp2
  589. real :: incloud,belowcloud,newcov,c_old,corr_diff,fnchem
  590. integer :: n,iscav,i,j,k,itemp,nzone_v, nloc
  591. real :: ztr, dkso2, dkhso3, factor, heff
  592. ! oldcov: cloud cover in layer above, to calculate below-cloud scaveging.
  593. real,dimension(:,:),allocatable :: oldcov
  594. integer :: i1, i2, j1, j2, status
  595. ! for wetdep global budget of tracer #1
  596. real :: g_sum_wet
  597. real, allocatable :: l_sum_wet(:,:)
  598. !
  599. ! --- begin ------------------------------
  600. !
  601. !>>> TvN
  602. ! Tests have been performed at various resolutions
  603. ! using mixing times of 3, 6, 9, 12 and 24 hours.
  604. ! Simulations at 1x1 degrees are best reproduced
  605. ! by increasing the mixing time with 3 hours at 3x2 degrees
  606. ! and with 6 hours at 6x4 degrees.
  607. dt_lagrangian = 3600.0 * 3.0 ! value at 1x1 degrees or higher resolution
  608. if (dy == 2) dt_lagrangian = dt_lagrangian + 3600.0 * 3.0
  609. if (dy == 4) dt_lagrangian = dt_lagrangian + 3600.0 * 6.0
  610. !<<< TvN
  611. CALL GET_DISTGRID( DGRID(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  612. #ifdef with_budgets
  613. allocate(l_sum_wet(i1:i2,j1:j2))
  614. l_sum_wet = 0.0
  615. #endif
  616. rm => mass_dat(region)%rm ! paralel over tracers
  617. #ifdef slopes
  618. rxm => mass_dat(region)%rxm
  619. rym => mass_dat(region)%rym
  620. rzm => mass_dat(region)%rzm
  621. #ifdef secmom
  622. rxxm => mass_dat(region)%rxxm
  623. rxym => mass_dat(region)%rxym
  624. rxzm => mass_dat(region)%rxzm
  625. ryym => mass_dat(region)%ryym
  626. ryzm => mass_dat(region)%ryzm
  627. rzzm => mass_dat(region)%rzzm
  628. #endif
  629. #endif
  630. t => temper_dat(region)%data
  631. cc => cc_dat(region)%data
  632. !$OMP PARALLEL &
  633. !$OMP default (none) &
  634. #if defined (with_budgets)
  635. !$OMP shared (nzon_vg, buddep_dat) &
  636. #endif
  637. !$OMP shared (region, ier, isr, jer, jsr, tracer_loc, henry, &
  638. !$OMP tracer_active, fnchem, rm, rxm, rym, rzm, t, cc, &
  639. !$OMP nchem, rloss1, rloss1_m7, rloss2, rloss3, ra,nscav_type, &
  640. !$OMP nscav_index,tref,im ) &
  641. !$OMP private (i, j, k, n, nloc, iscav, jss, jee, rtl, itemp, &
  642. !$OMP corr_diff, belowcloud, incloud, f, f1, f2, newcov, &
  643. !$OMP vol1, vol2, vol3, c_old, nzone_v, ztr, dkso2, dkhso3, &
  644. !$OMP factor, heff, oldcov, l_sum_wet)
  645. fnchem=real(nchem/(2*tref(region)))
  646. !
  647. allocate(oldcov(i1:i2,j1:j2))
  648. do iscav=1,nscav
  649. !
  650. n=nscav_index(iscav) ! tracer number in global count
  651. nloc = n ! tracer number in local count
  652. oldcov=0.
  653. !
  654. ! assumption no stratiform precipitation above the maximum
  655. ! level of convection
  656. !
  657. do k=lmax_conv,1,-1 ! top to bottom
  658. do j=j1,j2
  659. do i=i1,i2
  660. !
  661. ! calculate, depending on solubility, scale factor relative
  662. ! to 100% scavenging (of HNO3)
  663. !
  664. ! rtl - composite factor of liquid water content, rgas
  665. ! and liquid water content
  666. rtl=rtl_fac*t(i,j,k)
  667. ! multiplaction with Henry constant gives phase factor
  668. itemp=nint(t(i,j,k)-float(ntlow))
  669. itemp = min(max(1,itemp),ntemp) ! corrected CMK dec2004 problems on ECMWF
  670. !
  671. !corr_diff=sqrt(ra(ihno3)/ra(n))
  672. corr_diff=sqrt(xmhno3/ra(n))
  673. !
  674. select case (nscav_type(iscav))
  675. case(0)
  676. incloud = 0.0
  677. belowcloud = 0.0
  678. case(1) ! 100% solubility
  679. !AJS: note that old code used factor rtl ~ 1,
  680. !AJS: computed with huge henry factor ~ 1e7 :
  681. ! rtl = rtl*henry(n,itemp) / ( 1.0 + rtl*henry(n,itemp) ) ! near 1.0
  682. ! incloud = rloss1(reion)%d3(i,j,k) * rtl
  683. incloud = rloss1(region)%d3(i,j,k)
  684. belowcloud = rloss2(region)%d3(i,j,k)*corr_diff
  685. case(2) ! henry solubility assumed
  686. rtl = rtl*henry(n,itemp) / ( 1.0 + rtl*henry(n,itemp) )
  687. incloud = rloss1(region)%d3(i,j,k)*rtl
  688. belowcloud = rloss2(region)%d3(i,j,k)*rtl*corr_diff
  689. case(3) ! bulk aerosol
  690. incloud = rloss1(region)%d3(i,j,k)*(1.0 - interstitial_fraction)
  691. !>>>TvN
  692. ! Alternative would be to make the interstitial fraction for bulk aerosols
  693. ! consistent the values used for the M7 modes,
  694. ! which are taken from Bourgeois and Bey (JGR, 2011)
  695. ! and distinguish between warm, mixed and ice clouds
  696. !<<<TvN
  697. belowcloud = rloss3(region)%d3(i,j,k)
  698. case(4) ! SO2
  699. ztr=(1./t(i,j,k)-1./298)
  700. dkso2 =1.7e-2*exp(2090.*ztr) !so2<=>hso3m+hplus
  701. dkhso3 = 6.6e-8*exp(1510.*ztr) !hso3m<=>so3-- + hplus
  702. factor = 1.0 + dkso2/hplus + (dkso2*dkhso3)/(hplus**2)
  703. heff = factor*henry(n,itemp)
  704. rtl = rtl*heff/ ( 1.0 + rtl*heff )
  705. incloud = rloss1(region)%d3(i,j,k)*rtl !
  706. belowcloud = rloss2(region)%d3(i,j,k)*rtl*corr_diff
  707. !>>>TvN
  708. ! The in-cloud scavenging coefficients are defined as the fraction of the tracer
  709. ! in the cloudy part of the grid box that is embedded in the cloud liquid or ice water,
  710. ! i.e. the non-interstitial part.
  711. ! We distinguish between liquid, mixed and ice stratiform clouds (Stier et al., 2005),
  712. ! depending on the local temperature in the grid cell (Croft et al., ACP, 2010).
  713. ! The in-cloud scavenging coefficients depend on size and composition;
  714. ! revised values for the M7 modes were provided by Bourgeois and Bey (JGR, 2011).
  715. ! For mixed clouds, an alternative method was presented by Zhang et al. (ACP, 2012),
  716. ! which uses a continuous temperature dependency.
  717. ! Note that these in-cloud scavenging coefficients account for both nucleation scavenging
  718. ! and impaction scavenging (Croft et al., ACP, 2009; 2010).
  719. ! Thus, the below-cloud scavenging rates should only account for
  720. ! the impaction scavenging by precipitation coming from clouds above the current level.
  721. !
  722. ! Estimates for below-cloud scavenging coefficients can be derived
  723. ! from Fig. 2 of Dana and Hales (AE, 1975).
  724. ! For estimating these values from the figure, I used aerodynamic radii of
  725. ! 0.007, 0.07, and 0.7 micron as the boundaries of the M7 modes
  726. ! (corresponding to a particle density of about 1800 g/cm^3).
  727. ! As in Stier et al. (2005), we do not distinguish between soluble and insoluble modes.
  728. ! Thus, dry particle radii can be used for estimating the scavenging coefficients from the figure
  729. ! (see also the mode boundaries applied in Fig. 2 in Croft et al., 2009).
  730. ! I thus arrive at the following rough estimates for below-cloud mass scavenging coefficients
  731. ! for the nucleation, aitken, accumulation, and coarse modes: ~0.01, 0.002, 0.01, and 1 mm^-1.
  732. ! These numbers are close to the estimates derived earlier from the same figure
  733. ! by Elisabetta Vignati, which were previously used: 0.005, 0.002, 0.008, and 1 mm^-1.
  734. !
  735. ! However, both sets of estimates based on Dana and Hales are substantially higher
  736. ! than the values presented by Croft et al. (2009).
  737. ! From the curves presented in their Fig. 2 for the standard Marshall-Palmer rain distribution,
  738. ! rough estimates of the mass scavenging coefficients for the four size modes can be obtained.
  739. ! My estimates are 0.002, 0.0002, 0.03, and 0.7 mm^-1.
  740. ! Note that especially the value for the accumulation mode is very sensitive to the
  741. ! actual mean particle size, and hard to estimate from the figure.
  742. ! Since the mean droplet size of the Marshall-Palmer distribution depends on the rain intensity,
  743. ! these estimates are only valid for a rain rate of 1 mm/hr.
  744. ! For simplicity, we assume that the scavenging coefficients derived from the figure at 1 mm/hr
  745. ! can also be applied at other rain intensities.
  746. !
  747. ! In the new implementation particle masses and numbers are scavenged at different rates.
  748. ! Rough estimates of the number scavenging coefficients for the four size modes
  749. ! can be obtained from the same figure in Croft et al.
  750. ! My estimates are 0.02, 0.001, 0.0003, and 0.3 mm^-1.
  751. ! Ideally, the below-cloud mass/number scavenging coefficients should be calculated
  752. ! using look-up tables to describe the dependence on median radius and precipitation rate,
  753. ! e.g. following the formulation/curves presented by Croft et al.
  754. !
  755. case(5) ! soluble nu
  756. !belowcloud=0.1*rloss3(region)%d3(i,j,k) ! 0.1*0.05=0.005 mm^-1
  757. #ifdef with_m7
  758. if (n /= inus_n) then
  759. belowcloud=0.5*rloss3(region)%d3(i,j,k) ! 0.5*0.004 = 0.002 mm^-2
  760. else
  761. #endif
  762. belowcloud=5.*rloss3(region)%d3(i,j,k) ! 5.*0.004 = 0.02 mm^-2
  763. #ifdef with_m7
  764. endif
  765. #endif
  766. !incloud=0.0
  767. incloud=0.06*rloss1_m7(region)%d3(i,j,k)
  768. case(6) ! soluble ai
  769. !belowcloud=0.04*rloss3(region)%d3(i,j,k) ! 0.04*0.05=0.002 mm^-1
  770. #ifdef with_m7
  771. if (n /= iais_n) then
  772. belowcloud=0.05*rloss3(region)%d3(i,j,k) ! 0.05*0.004 = 0.0002 mm^-2
  773. else
  774. #endif
  775. belowcloud=0.25*rloss3(region)%d3(i,j,k) ! 0.25*0.004 = 0.001 mm^-2
  776. #ifdef with_m7
  777. endif
  778. #endif
  779. !incloud=0.0
  780. if (t(i,j,k).gt.273.15) then
  781. incloud=0.25*rloss1_m7(region)%d3(i,j,k)
  782. else
  783. incloud=0.06*rloss1_m7(region)%d3(i,j,k)
  784. endif
  785. case(7) ! soluble ac
  786. !belowcloud=0.16*rloss3(region)%d3(i,j,k) ! 0.16*0.05 = 0.008 mm^-1
  787. #ifdef with_m7
  788. if (n /= iacs_n) then
  789. belowcloud=7.5*rloss3(region)%d3(i,j,k) ! 7.5*0.004 = 0.03 mm^-1
  790. else
  791. #endif
  792. belowcloud=0.075*rloss3(region)%d3(i,j,k) ! 0.075*0.004 = 0.0003 mm^-1
  793. #ifdef with_m7
  794. endif
  795. #endif
  796. !incloud=rloss1(region)%d3(i,j,k)
  797. if (t(i,j,k).gt.273.15) then
  798. incloud=0.85*rloss1_m7(region)%d3(i,j,k)
  799. else
  800. incloud=0.06*rloss1_m7(region)%d3(i,j,k)
  801. endif
  802. case(8) ! soluble co
  803. !belowcloud=20.*rloss3(region)%d3(i,j,k) ! 20*0.05 = 1 mm^-1
  804. #ifdef with_m7
  805. if (n /= icos_n) then
  806. belowcloud=175.*rloss3(region)%d3(i,j,k) ! 175*0.004 = 0.7 mm^-1
  807. else
  808. #endif
  809. belowcloud=75.*rloss3(region)%d3(i,j,k) ! 75*0.004 = 0.3 mm^-1
  810. #ifdef with_m7
  811. endif
  812. #endif
  813. !incloud=rloss1(region)%d3(i,j,k)
  814. if (t(i,j,k).gt.273.15) then
  815. incloud=0.99*rloss1_m7(region)%d3(i,j,k)
  816. else if (t(i,j,k).gt.238.15) then
  817. incloud=0.75*rloss1_m7(region)%d3(i,j,k)
  818. else
  819. incloud=0.06*rloss1_m7(region)%d3(i,j,k)
  820. endif
  821. case(9) ! insoluble ai
  822. !belowcloud = 0.04*rloss3(region)%d3(i,j,k)
  823. #ifdef with_m7
  824. if (n /= iaii_n) then
  825. belowcloud=0.05*rloss3(region)%d3(i,j,k)
  826. else
  827. #endif
  828. belowcloud=0.25*rloss3(region)%d3(i,j,k)
  829. #ifdef with_m7
  830. endif
  831. #endif
  832. !incloud=0.0
  833. if (t(i,j,k).gt.273.15) then
  834. incloud=0.2*rloss1_m7(region)%d3(i,j,k)
  835. else
  836. incloud=0.06*rloss1_m7(region)%d3(i,j,k)
  837. endif
  838. case(10) ! insoluble ac
  839. !belowcloud=0.16*rloss3(region)%d3(i,j,k)
  840. #ifdef with_m7
  841. if (n /= iaci_n) then
  842. belowcloud=7.5*rloss3(region)%d3(i,j,k)
  843. else
  844. #endif
  845. belowcloud=0.075*rloss3(region)%d3(i,j,k)
  846. #ifdef with_m7
  847. endif
  848. #endif
  849. !incloud=0.0
  850. if (t(i,j,k).gt.273.15) then
  851. incloud=0.4*rloss1_m7(region)%d3(i,j,k)
  852. else
  853. incloud=0.06*rloss1_m7(region)%d3(i,j,k)
  854. endif
  855. case(11) ! insoluble co
  856. !belowcloud=20.*rloss3(region)%d3(i,j,k)
  857. #ifdef with_m7
  858. if (n /= icoi_n) then
  859. belowcloud=175.*rloss3(region)%d3(i,j,k)
  860. else
  861. #endif
  862. belowcloud=75.*rloss3(region)%d3(i,j,k)
  863. #ifdef with_m7
  864. endif
  865. #endif
  866. !incloud=0.0
  867. if (t(i,j,k).gt.238.15) then
  868. incloud=0.4*rloss1_m7(region)%d3(i,j,k)
  869. else
  870. incloud=0.06*rloss1_m7(region)%d3(i,j,k)
  871. endif
  872. case default
  873. incloud = 0.0
  874. belowcloud = 0.0
  875. end select
  876. !if(incloud > 1e-4) then
  877. !print *, i,j,k,names(n),rtl, rloss1(region)%d3(i,j,k), rtl_fac
  878. !end if
  879. !
  880. ! f1, f2 are the fractions of the tracermass that remain in the
  881. ! gridbox after scavenging.
  882. !
  883. f1=exp(-dt_lagrangian*incloud)
  884. f2=exp(-dt_lagrangian*belowcloud)
  885. !CMK f1=exp(-fnchem*incloud)
  886. !CMK f2=exp(-fnchem*belowcloud)
  887. !
  888. ! A grid box can be divided into three volumes
  889. ! 1) incloud scavenging (newcov)
  890. ! 2) below cloud scavenging (oldcov-newcov)
  891. ! 3) no in-cloud scavenging and no below cloud
  892. ! scavenging by precipitation (no removal)
  893. !
  894. newcov=cc(i,j,k)
  895. vol1 = newcov
  896. !>>> TvN
  897. ! oldcov denotes the area fraction occupied by precipitating clouds above the current level.
  898. ! It is determined assuming maximum overlap of the cloudy fractions of the layers above (see below).
  899. ! The precipitation rate used for below-cloud scavenging correctly does not include the contribution
  900. ! from the current level.
  901. !<<<TvN
  902. vol2 = max(0.,oldcov(i,j)-newcov)
  903. vol3 = 1.-vol1-vol2
  904. !CMK f=f1*vol1+f2*vol2+vol3
  905. f=(f1*vol1+f2*vol2+vol3)**(fnchem/dt_lagrangian)
  906. c_old=rm(i,j,k,nloc)
  907. rm(i,j,k,nloc)=c_old*f
  908. #ifdef slopes
  909. rxm(i,j,k,nloc)=rxm(i,j,k,nloc)*f
  910. rym(i,j,k,nloc)=rym(i,j,k,nloc)*f
  911. rzm(i,j,k,nloc)=rzm(i,j,k,nloc)*f
  912. #ifdef secmom
  913. rxxm(i,j,k,nloc)=rxxm(i,j,k,nloc)*f
  914. rxym(i,j,k,nloc)=rxym(i,j,k,nloc)*f
  915. rxzm(i,j,k,nloc)=rxzm(i,j,k,nloc)*f
  916. ryym(i,j,k,nloc)=ryym(i,j,k,nloc)*f
  917. ryzm(i,j,k,nloc)=ryzm(i,j,k,nloc)*f
  918. rzzm(i,j,k,nloc)=rzzm(i,j,k,nloc)*f
  919. #endif
  920. #endif
  921. #ifdef with_budgets
  922. ! _____budget
  923. nzone_v = nzon_vg(k)
  924. buddep_dat(region)%lsp(i,j,nzone_v,n)= &
  925. buddep_dat(region)%lsp(i,j,nzone_v,n)+ &
  926. (c_old-rm(i,j,k,nloc))/ra(n)*1000. ! in moles
  927. if ( n == 1 ) l_sum_wet(i,j) = l_sum_wet(i,j) + &
  928. (c_old-rm(i,j,k,nloc)) ! in kg
  929. ! _____budget
  930. #endif
  931. ! oldcov is determined assuming maximum overlap of the fractions of precipitating clouds overhead:
  932. if ( rloss1(region)%d3(i,j,k) > 0.0 ) oldcov(i,j)=max(oldcov(i,j),cc(i,j,k))
  933. end do !i
  934. end do !j
  935. end do !k
  936. end do !iscav
  937. deallocate(oldcov)
  938. !$OMP END PARALLEL
  939. #ifdef with_budgets
  940. call REDUCE( dgrid(region), l_sum_wet, 0, 'SUM', g_sum_wet, status)
  941. IF_NOTOK_RETURN(status=1)
  942. if ( isRoot ) sum_wetdep(region) = sum_wetdep(region) + g_sum_wet
  943. deallocate( l_sum_wet )
  944. #endif
  945. nullify(rm)
  946. #ifdef slopes
  947. nullify(rxm)
  948. nullify(rym)
  949. nullify(rzm)
  950. #ifdef secmom
  951. nullify(rxxm)
  952. nullify(rxym)
  953. nullify(rxzm)
  954. nullify(ryym)
  955. nullify(ryzm)
  956. nullify(rzzm)
  957. #endif
  958. #endif
  959. nullify(t)
  960. nullify(cc)
  961. END SUBROUTINE LSPSCAV
  962. !EOC
  963. !--------------------------------------------------------------------------
  964. ! TM5 !
  965. !--------------------------------------------------------------------------
  966. !BOP
  967. !
  968. ! !IROUTINE: CALCULATE_LSP_SCAV
  969. !
  970. ! !DESCRIPTION:
  971. !
  972. ! Calculate wet removal rates rloss1,rloss2,rloss3 (s-1) for
  973. ! stratiform precipitation from cloud-top to ground,
  974. ! distinguishing between below-cloud and in-cloud scavenging.
  975. !
  976. ! Method:
  977. ! adapted from GJ Roelofs and Lelieveld, JGR, October 1995
  978. !
  979. ! fills array "rloss" should be called once new precipitation fields
  980. ! are available (MK: in trace_after_read)
  981. !\\
  982. !\\
  983. ! !INTERFACE:
  984. !
  985. SUBROUTINE CALCULATE_LSP_SCAV( region )
  986. !
  987. ! !USES:
  988. !
  989. use binas, only : grav, rgas, xmair
  990. use dims, only : im,jm,lm,lmax_conv
  991. use meteodata, only : temper_dat, lwc_dat, iwc_dat, cc_dat
  992. use meteodata, only : lsp_dat
  993. use global_data, only : emis_data
  994. use meteodata, only : phlb_dat
  995. use partools, only : isroot
  996. !
  997. ! !INPUT PARAMETERS:
  998. !
  999. integer, intent(in) :: region
  1000. !
  1001. ! !REVISION HISTORY:
  1002. ! Programmed by: Frank Dentener, IMAU, 1996
  1003. ! Ad Jeuken, KNMI, 1998
  1004. ! Modification, Bas Henzing, KNMI, 2002.
  1005. ! Adapted for TM5, August 2002, Frank Dentener, JRC.
  1006. ! And finally for the new version, MK, IMAU, March 2003
  1007. ! Parallel, MK Jul 2003
  1008. ! 25 Jan 2012 - P. Le Sager - adapted for mpi lat-lon domain decomposition
  1009. !
  1010. ! !REMARKS:
  1011. !
  1012. !EOP
  1013. !------------------------------------------------------------------------
  1014. !BOC
  1015. integer :: i1, i2, j1, j2
  1016. real,dimension(:,:,:),pointer :: lsp
  1017. real,dimension(:,:,:),pointer :: t, lwc, iwc, cc, phlb
  1018. real,parameter :: max_lwc=2.e-3 ! kg/m3
  1019. !
  1020. ! Microphysical parameters:
  1021. !
  1022. ! rdrad2: square of raindroplet radius (20 microns)
  1023. ! dghno3: in [cm2/s]
  1024. ! dgair: in [cm2/s]
  1025. ! rol: density of water in [kg/m3]
  1026. ! roi: density of ice in [kg/m3]
  1027. !
  1028. real,parameter :: rdrad2 = (2E-5)**2
  1029. real,parameter :: dghno3 = 0.136
  1030. real,parameter :: dgair = 0.133
  1031. real,parameter :: rol = 1000.
  1032. real,parameter :: roi = 917.
  1033. !
  1034. ! quantity used in calculation of Sherwood number
  1035. !
  1036. ! bas henzing: bug repair real,parameter :: znsc=dgair/dghno3**(-3)
  1037. ! bas henzing: should be: znsc=(dgair/dghno3)**(1./3.);
  1038. ! znsc is now defined a real
  1039. !
  1040. real,dimension(:),allocatable :: dzk
  1041. real :: rflx,beta,fac,beta1,beta2,beta3,rlwc,rdrad,rn,ru
  1042. !>>>TvN
  1043. real :: fac_m7, beta1_m7
  1044. !<<<
  1045. real :: press,aird,dgairx,dghno3x
  1046. real :: znre,znsh,znsc,zkg,totw,sfz,sfz_no
  1047. !
  1048. integer :: nfz,i,j,k,l,no_fz
  1049. integer,dimension(:,:),allocatable :: kcltop
  1050. real,dimension(:,:),allocatable :: oldcov,fz
  1051. real,dimension(:,:,:),allocatable :: precip ! precipitation per level (kg/m2/s)
  1052. real,dimension(:,:,:),allocatable :: prf ! precipitation formation rate.
  1053. ! evaporation NOT YET AVAILABLE
  1054. !
  1055. ! how much less efficient is tracer scavenged from ice
  1056. ! cloud droplet compared to water cloud droplet.
  1057. ! This should be tracer dependent.
  1058. !
  1059. real,parameter :: ice_eff=0.2
  1060. real :: inc_rdf
  1061. real,parameter :: scale_heigth= rgas/grav/xmair*1e3 ! about 29.3*T (m)
  1062. ! ---------------- START ------------------------------------------------
  1063. t => temper_dat(region)%data
  1064. lwc => lwc_dat(region)%data !mk: lm, and not lmax_conv
  1065. iwc => iwc_dat(region)%data !mk: lm, and not lmax_conv
  1066. cc => cc_dat(region)%data !mk: lm, and not lmax_conv
  1067. phlb => phlb_dat(region)%data !mk: 1:lm+1
  1068. lsp => lsp_dat(region)%data
  1069. CALL GET_DISTGRID( DGRID(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  1070. allocate( oldcov( i1:i2, j1:j2 ) )
  1071. allocate( fz( i1:i2, j1:j2 ) )
  1072. allocate( precip( i1:i2, j1:j2, lmax_conv) )
  1073. allocate( dzk( lmax_conv) )
  1074. allocate( kcltop( i1:i2, j1:j2 ) )
  1075. allocate( prf( i1:i2, j1:j2, lmax_conv) )
  1076. !
  1077. ! calculate precipitation formation rate prf
  1078. !
  1079. call calfk
  1080. !
  1081. ! initialize cloud top
  1082. !
  1083. kcltop(:,:)=lmax_conv
  1084. !
  1085. ! calculate and rescale precip
  1086. !
  1087. sfz=0.
  1088. nfz=0
  1089. precip(:,:,:)=0.
  1090. !
  1091. do j= j1, j2
  1092. do i= i1, i2
  1093. !
  1094. ! Calculate precipitation intensity at the bottom of each layer
  1095. !
  1096. do k=1,lmax_conv-1
  1097. ! thickness of layer, only correct in troposphere
  1098. dzk(k)=scale_heigth*t(i,j,k)*alog(phlb(i,j,k)/(1.+phlb(i,j,k+1)))
  1099. end do
  1100. !
  1101. do k=lmax_conv-1,1,-1
  1102. precip(i,j,k)=precip(i,j,k+1)+prf(i,j,k)*dzk(k) !precip: kg/m2/s
  1103. end do
  1104. !
  1105. ! Rescale prf and precip such that these are consistent with ground lsp
  1106. ! Note that lsp is defined as the total large-scale precipitation (rain+snow)
  1107. ! produced by the cloud scheme.
  1108. ! prf, precip and lsp thus all account for snow/ice
  1109. !
  1110. no_fz = 0 ! for statistics !CMK was not initialised!
  1111. sfz_no = 0.0
  1112. fz(i,j)=0.
  1113. !cmk if (lsp(i,j) > 1.e-5) then old data came in mm/day
  1114. if (lsp(i,j,1)*1e3*3600.*24. > 1.e-5) then !new data are in m/s
  1115. if (precip(i,j,1) > 0.) then
  1116. fz(i,j)=lsp(i,j,1)*1e3/precip(i,j,1) ! m/s ->kg/m2/s !new unit...
  1117. !cmk fz(i,j)=lsp(i,j,1)/3600./24./precip(i,j,1) ! mm/day->kg/m2/s
  1118. nfz=nfz+1
  1119. ! precipitation statistics
  1120. ! (avoid 'strange' statistics by only few values)
  1121. sfz=sfz+min(10.,fz(i,j))
  1122. else
  1123. ! no precipitation calculated, but ECMWF fields contain rain value
  1124. no_fz=no_fz+1
  1125. sfz_no=sfz_no+lsp(i,j,1)*1e3*86400. ! (in mm/day)
  1126. end if
  1127. else
  1128. precip(i,j,:)=0.
  1129. end if
  1130. do k=1,lmax_conv
  1131. precip(i,j,k)=precip(i,j,k)*fz(i,j)
  1132. prf(i,j,k)=prf(i,j,k)*fz(i,j)
  1133. end do !k
  1134. end do ! i
  1135. end do ! j
  1136. !
  1137. !if(myid == root) then
  1138. ! write(6,*) 'calculate_lsp_scav: region',region
  1139. ! write(6,*) ' rainout: average scale factor for precipitation = ',sfz/nfz
  1140. ! write(6,*) ' rainout: percentage of columns with precipitation = ', &
  1141. ! 100.*nfz/real(im(region)*jm(region)),' %'
  1142. ! if ( no_fz > 0 ) write(6,*) 'rainout: lsp and prf not consistent ', &
  1143. ! no_fz,'average rainfall [mm/day]',sfz_no/no_fz
  1144. !end if
  1145. !
  1146. ! initialise
  1147. !
  1148. oldcov=0.
  1149. ! evap=0.
  1150. rloss1(region)%d3=0.
  1151. !>>>TvN
  1152. rloss1_m7(region)%d3=0.
  1153. !<<<TvN
  1154. rloss2(region)%d3=0.
  1155. rloss3(region)%d3=0.
  1156. !
  1157. do k=lmax_conv-1,1,-1 ! top-down
  1158. do j=j1,j2
  1159. do i=i1,i2
  1160. !
  1161. ! pressure correction for diffusion coefficient
  1162. !
  1163. press = (phlb(i,j,k)+phlb(i,j,k+1))/2.
  1164. dgairx = dgair*1e5/press ! dgair at 1 atmosphere
  1165. dghno3x = dghno3*1e5/press
  1166. beta1=0.
  1167. beta1_m7=0.
  1168. beta2=0.
  1169. beta3=0.
  1170. !
  1171. ! total cloudwater (kg H2O / kg air)
  1172. !
  1173. totw=lwc(i,j,k)+iwc(i,j,k)
  1174. !
  1175. ! no influx set kcltop to low number
  1176. !
  1177. if (precip(i,j,k+1)<=1.e-15) kcltop(i,j)=0
  1178. !
  1179. !==========================================
  1180. ! below-cloud scavenging (beta2 and beta3)
  1181. !==========================================
  1182. !
  1183. ! with evaporation do:
  1184. ! precip(i,j,k+1)=precip(i,j,k+1)-evap(i,j,k))>1E-15
  1185. !
  1186. if( (precip(i,j,k+1)>1e-15) .and. (k<kcltop(i,j)) &
  1187. .and. (oldcov(i,j)>0.) )then
  1188. !
  1189. ! rflx in [mm/hr] !MK? thought precip was in kg/m2/s ??
  1190. ! rlwc in [vol mixing ratio]
  1191. ! rdrad in [cm]
  1192. ! ru in [cm/s] (terminal velocity)
  1193. ! znre = Reynolds number
  1194. ! znsc = (Sherwood number)**(1./3.)
  1195. ! zkg in [cm/s] = dghno3[cm^2/s]/rdrad[cm]
  1196. !
  1197. rflx = precip(i,j,k+1)/oldcov(i,j)*3600.
  1198. rlwc = 72.*rflx**0.88*1.e-9
  1199. rdrad = 0.1*0.3659*rflx**0.21
  1200. !*******************************************
  1201. ! correction by Twan van Noije, Bas Henzing:
  1202. ! ru = 9.58*(1.-exp(-(rdrad*10./0.885)**1.147))
  1203. ! the above equation gives an approximation to the terminal velocity in m/s !!
  1204. ! a conversion factor to cm/s should therefore be included
  1205. ! znre = 20.*rdrad*ru/dgair
  1206. ! with ru in cm/s, the above expression overestimates the Reynolds number by a factor 10
  1207. ! the combined effect of having ru in m/s and the above expression for the Reynolds number
  1208. ! is to underestimate the Reynolds number by a factor 10, resulting in an underestimation
  1209. ! of the Sherwood number and an overestimation of the below-cloud scavenging
  1210. ! Twan van Noije/Bas Henzing, 24-02-2004
  1211. !*******************************************
  1212. ru = 100.*9.58*(1.-exp(-(rdrad*10./0.885)**1.147))
  1213. ! see Seinfeld (1986), p. 632
  1214. znre = 2.*rdrad*ru/dgair
  1215. !WRONG ru = 9.58*(1.-exp(-(rdrad*10./0.885)**1.147))
  1216. !WRONG znre = 20.*rdrad*ru/dgair
  1217. znsc = (dgair/dghno3)**(1./3.)
  1218. znsh = 1.+0.3*(znre**0.5)*znsc
  1219. zkg = dghno3/rdrad*znsh
  1220. beta2 = 3.*zkg*rlwc/rdrad
  1221. !
  1222. ! beta3 for below cloud scavenging of accumulation range aerosol
  1223. ! (Dana and Hales, Atmos. Env. 1976, pp. 45-50
  1224. ! assuming a Whitby aerosol distrbution r=0.034 sigma=2;
  1225. ! mass-mean radius r=0.14 microm;
  1226. ! figure 2 gives a wash-out coefficient of 0.05 mm^-1 (raindepth)
  1227. ! for other sigma and r look-up tables can be generated
  1228. !>>>TvN
  1229. ! A mass washout coefficient of 0.05 mm^-1 in Fig. 2 of Dana and Hales (1975)
  1230. ! would correspond to a geometric mean/median particle radius of 0.14 micron.
  1231. ! At a median radius of 0.034 micron and sigma=2, the value becomes ~0.002 mm^-1.
  1232. ! However, as the aerodynamic radius is used in the plot, these values only apply
  1233. ! to unit-density particles, with a density equal to that of water (1 g/cm^3).
  1234. ! The aerodynamic radius equals the actual radius times
  1235. ! the square root of ratio of the particle density over that for water.
  1236. ! For the bulk inorganic aerosols, the particle density is about 1800 g/cm^3,
  1237. ! so the aerodynamic radius is 1.34 times the actual radius,
  1238. ! and a median aerodynamic radius of ~0.046 micron should be used.
  1239. ! This gives a mass washout coefficient of ~0.004 mm^-1.
  1240. ! Thus, based on the work by Dana and Hales, the value 0.05 mm^-1 seems too low,
  1241. ! and a value ~0.004 mm^-1 would be more appropriate.
  1242. !
  1243. ! mm-1*[mm hr-1] * [hr/s] => [s-1]
  1244. !
  1245. !beta3= 0.05*rflx/3600.
  1246. beta3= 0.004*rflx/3600.
  1247. !
  1248. !<<<TvN
  1249. end if
  1250. !
  1251. ! revaporation ( not implemented yet!, evap put to 0.)
  1252. !
  1253. ! IF ((1.-cc(i,j,k))>1E-20.AND.precip(i,j,k+1)>1E-20) THEN
  1254. ! rev1=max(0.,EVAP(i,j,k)/precip(i,j,k+1))
  1255. ! ! evaporation fraction
  1256. ! rev(i,j,k)=MIN(1.,rev1)
  1257. ! END IF
  1258. !
  1259. !==============================
  1260. ! in cloud scavenging (beta1)
  1261. !==============================
  1262. !
  1263. if (totw>1.e-9.and.prf(i,j,k)>0.and.cc(i,j,k)>0.02) then
  1264. !
  1265. if(k>kcltop(i,j)) kcltop(i,j)=k !set new cloud top
  1266. !
  1267. ! rlwc: convert mass mixing ratios to volume mixing ratios in cloud
  1268. ! aird: air density in kg air / m^3
  1269. ! max_lwc: in kg H2O / m^3
  1270. ! prf: in kg H2O / m3 / s
  1271. ! beta: in [s-1] = [vol mixing ratio]*[cm2/s]*1e-4/[m2]
  1272. ! fac, beta1: in [s-1]
  1273. !
  1274. aird=press/t(i,j,k)/rgas*xmair*1.e-3
  1275. rlwc=(lwc(i,j,k)/rol+iwc(i,j,k)/roi)*aird/cc(i,j,k)
  1276. rlwc=min(max_lwc/rol,rlwc)
  1277. !
  1278. !bas henzing: bug repair: beta=3.*rlwc*(dghno3*1e-4)/rdrad2
  1279. !bas henzing: should be:
  1280. ! beta=(3.*rlwc*(dghno3*1e-4)/(2.*rdrad2))*znsh
  1281. !bas henzing: reference: (Roelofs and Lelieveld, 1995)
  1282. !fd beta=(3.*rlwc*(dghno3*1e-4)/(2.*rdrad2))*znsh
  1283. ! fd 13/08/2002 use old defenition again (pers. comm Henzing)
  1284. beta=3.*rlwc*(dghno3*1e-4)/rdrad2
  1285. !
  1286. inc_rdf=(iwc(i,j,k)/totw)*ice_eff+lwc(i,j,k)/totw
  1287. fac=prf(i,j,k)*inc_rdf/(totw*aird)
  1288. !>>>TvN
  1289. ! In the calculation of fac (and thus fac_m7) currently the grid-cell average prf is used.
  1290. ! Question: shouldn't we use the actual value in the cloudy part, i.e. prf/cc ?
  1291. ! Note that scaling by 1/cc is also applied in the calculation of beta,
  1292. ! and that for the below-cloud scavenging parameters beta2 and beta3
  1293. ! we also use the actual precipitation intensity in the precipitating fraction,
  1294. ! i.e. precip/oldcov.
  1295. !<<<TvN
  1296. !
  1297. !resistance analogy: the slowest determines the overall resistance
  1298. !
  1299. beta1=1./(1./beta+1./fac)
  1300. !
  1301. !>>>TvN
  1302. ! The scavengy efficiency for in-cloud scavenging of M7 aerosols by ice in stratiform clouds
  1303. ! is now reduced by applying a lower scavenging coefficient for mixed and ice clouds
  1304. ! according to Bourgeois and Bey (JGR, 2011).
  1305. fac_m7=prf(i,j,k)/(totw*aird)
  1306. beta1_m7=1./(1./beta+1./fac_m7)
  1307. !<<<TvN
  1308. !
  1309. !if no precipitation formation oldcov remains old value
  1310. !
  1311. oldcov(i,j)=max(oldcov(i,j),cc(i,j,k))
  1312. !
  1313. end if ! in cloud scavenging
  1314. !
  1315. rloss1(region)%d3(i,j,k)=beta1 ! in cloud completely soluble
  1316. !>>>TvN
  1317. rloss1_m7(region)%d3(i,j,k)=beta1_m7 ! as rloss1, but with ice as efficient as liquid water
  1318. !<<<TvN
  1319. rloss2(region)%d3(i,j,k)=beta2 ! below cloud gas
  1320. rloss3(region)%d3(i,j,k)=beta3 ! below cloud aerosol
  1321. end do !i
  1322. end do !j
  1323. end do !k
  1324. !if(myid == root) then
  1325. ! write(*,*) 'calculate_lsp_scav: average rain-out loss rate 1 region', &
  1326. ! region,sum(rloss1(region)%d3)/im(region)/jm(region)/lmax_conv
  1327. ! write(*,*) 'calculate_lsp_scav: average rain-out loss rate 2 region', &
  1328. ! region,sum(rloss2(region)%d3)/im(region)/jm(region)/lmax_conv
  1329. ! write(*,*) 'calculate_lsp_scav: average rain-out loss rate 3 region', &
  1330. ! region,sum(rloss3(region)%d3)/im(region)/jm(region)/lmax_conv
  1331. !end if
  1332. deallocate(oldcov)
  1333. deallocate(fz)
  1334. deallocate(precip)
  1335. deallocate(prf)
  1336. deallocate(dzk)
  1337. deallocate(kcltop)
  1338. nullify(lsp)
  1339. nullify(t)
  1340. nullify(lwc)
  1341. nullify(iwc)
  1342. nullify(cc)
  1343. nullify(phlb)
  1344. contains
  1345. subroutine calfk
  1346. !--------------------------------------------------------------
  1347. ! calculate vertical distribution of large scale precipitation
  1348. !
  1349. ! OUTPUT: prf = precipitation formation rate (kg m-3 s-1)
  1350. !
  1351. ! Written by Ad Jeuken, KNMI, May 1998
  1352. ! Adapted for TM5, MK, march 2003
  1353. !--------------------------------------------------------------
  1354. use toolbox, only: lvlpress
  1355. !
  1356. ! microphysical constants
  1357. real,parameter :: cr1=1.e-4 ! s-1
  1358. real,parameter :: cr2=1.0 ! m2 kg-1
  1359. real,parameter :: qcrs=3.e-4 ! kg/kg
  1360. !bas henzing: replace alfa real,parameter :: alfa=1.77, beta=0.16
  1361. !bas henzing: new value alfa=3.29 (Heymsfield and Donner, 1990)
  1362. real,parameter :: alfa=3.29, beta=0.16
  1363. !bas henzing: replace b1 real,parameter :: b1=100., b2=0.5, Tberg=268.
  1364. !bas henzing: new value b1=300. (Sunquist et al., 1989)
  1365. real,parameter :: b1=300., b2=0.5, Tberg=268.
  1366. !
  1367. real :: plocal,f1,f2,delta_prec,ahelp,rain_frac,c0
  1368. real :: pr0,qcr,qcl,qci,dzk,aird,press
  1369. real :: qup,qdo,rup,rdo,vtup,vtdo,zcc,ccp,ccm
  1370. integer :: iclb,iclt,icldtop,i,j,k,l,l1,l2
  1371. real,dimension(:),allocatable :: zrho,pcl,pci
  1372. !
  1373. allocate(zrho(lmax_conv))
  1374. allocate(pci(lmax_conv))
  1375. allocate(pcl(lmax_conv))
  1376. prf=0.
  1377. do j=j1,j2
  1378. do i=i1,i2
  1379. !
  1380. ! calculate airdensity "zrho" in kg/m3
  1381. !
  1382. do l=1,lmax_conv
  1383. press=(phlb(i,j,l)+phlb(i,j,l+1))/2.
  1384. zrho(l)=press/t(i,j,l)/rgas*xmair*1.e-3
  1385. end do
  1386. !
  1387. iclb=0
  1388. iclt=0
  1389. !
  1390. ! do not consider columns with lsp less than 1.e-5 mm/day
  1391. !
  1392. ! if (lsp(i,j,1)>1.e-5) then
  1393. if ( lsp(i,j,1)*1e3*3600.*24. > 1.e-5 ) then !new data are in m/s
  1394. ! determine cloud base
  1395. k = 1
  1396. do
  1397. if ( cc(i,j,k) >= 0.01 ) exit
  1398. if ( k == lmax_conv ) exit
  1399. k = k + 1
  1400. end do
  1401. iclb = k
  1402. ! determine cloud top
  1403. k = lmax_conv
  1404. do
  1405. if ( cc(i,j,k) >= 0.01 ) exit
  1406. if ( k == 1 ) exit
  1407. k = k-1
  1408. end do
  1409. iclt = k
  1410. ! check for inconsistency in cloud cover fields
  1411. if ( iclb >= iclt ) iclb=iclt
  1412. if ( iclb < 1 ) iclb=1
  1413. !mvw: replace fixed iclb/t=14 by 120 hPa level (about 15km)
  1414. ! if (iclb>14) iclb=14
  1415. ! if (iclt>14) iclt=14
  1416. icldtop=lvlpress(region,12000., 98400.)
  1417. if ( iclb > icldtop ) iclb=icldtop
  1418. if ( iclt > icldtop ) iclt=icldtop
  1419. !
  1420. pr0=0.
  1421. pcl=0.
  1422. pci=0.
  1423. rain_frac=0.00001
  1424. !
  1425. ! start at cloudtop
  1426. do k=iclt,iclb,-1
  1427. zcc=max(0.01,cc(i,j,k))
  1428. !
  1429. ! precipitation formation from ice clouds
  1430. !
  1431. ! pci in kg_H2O / (kg_air sec)
  1432. !
  1433. if ( ( t(i,j,k) < 258.0 ) .and. ( k > 1 ) ) then
  1434. ccp=max(0.01,cc(i,j,k+1))
  1435. ccm=max(0.01,cc(i,j,k-1))
  1436. qup=(iwc(i,j,k)/zcc+iwc(i,j,k+1)/ccp)*0.5
  1437. qdo=(iwc(i,j,k)/zcc+iwc(i,j,k-1)/ccm)*0.5
  1438. rup=(zrho(k)+zrho(k+1))*0.5
  1439. rdo=(zrho(k)+zrho(k-1))*0.5
  1440. vtup=alfa*(rup*qup)**beta
  1441. vtdo=alfa*(rdo*qdo)**beta
  1442. pci(k)=grav*(vtup*qup*rup-vtdo*qdo*rdo)/ &
  1443. (phlb(i,j,k+1)-phlb(i,j,k))
  1444. pci(k)=max(pci(k),0.)
  1445. end if
  1446. !
  1447. ! precipitation formation from liquid clouds
  1448. ! formulation ECMWF
  1449. !
  1450. qcl=lwc(i,j,k)/zcc
  1451. qcl=min(max_lwc/zrho(k),qcl)
  1452. qcl=max(0.001e-3/zrho(k),qcl)
  1453. !
  1454. ! pcl in kg_H2O / (kg_air sec)
  1455. !
  1456. plocal=pr0/rain_frac
  1457. f1=1.+b1*sqrt(plocal)
  1458. f2=1.+b2*sqrt(max(0.,Tberg-t(i,j,k)))
  1459. c0=cr1*f1*f2
  1460. qcr=qcrs/(f1*f2)
  1461. pcl(k)=zcc*c0*qcl*(1.-exp(-(qcl/qcr)**2))
  1462. !
  1463. ! prec at top next layer in kg m-2 s-1
  1464. !
  1465. dzk=29.3*t(i,j,k)*alog(phlb(i,j,k)/(1.+phlb(i,j,k+1)))
  1466. delta_prec=(pcl(k)+pci(k))*zrho(k)*dzk
  1467. ahelp=(zcc*delta_prec+rain_frac*pr0)/(delta_prec+pr0)
  1468. rain_frac=max(rain_frac,ahelp)
  1469. pr0=pr0+(pcl(k)+pci(k))*zrho(k)*dzk
  1470. !
  1471. ! liquid+ice precipitation formation rates in kg m-3 s-1
  1472. !
  1473. prf(i,j,k)= (pcl(k)+pci(k))*zrho(k)
  1474. !
  1475. end do ! k
  1476. end if ! lsp gt 1.e-5
  1477. end do ! i
  1478. end do ! j
  1479. deallocate(zrho)
  1480. deallocate(pci)
  1481. deallocate(pcl)
  1482. !
  1483. end subroutine calfk
  1484. END SUBROUTINE CALCULATE_LSP_SCAV
  1485. !EOC
  1486. END MODULE WET_DEPOSITION