Changes in src/get_wetscav.f90 [e9e0f06:79e0349] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/get_wetscav.f90

    re9e0f06 r79e0349  
    151151      if (height(il).gt.ztra1(jpart)) then
    152152        hz=il-1
     153!        goto 26
    153154        exit
    154155      endif
    155156    end do
     157!26  continue
     158
    156159
    157160    if (ngrid.eq.0) then
     
    200203
    201204
    202 !ZHG oct 2014 : Calculated for 1) both 2) lsp 3) convp - 2 and 3 not used removed by SE
     205!ZHG oct 2014 : Calculated for 1) both 2) lsp 3) convp
    203206! Tentatively differentiate the grfraction for lsp and convp for treating differently the two forms
    204207! for now they are treated the same
    205208    grfraction(1)=max(0.05,cc*(lsp*lfr(i)+convp*cfr(j))/(lsp+convp))
     209    grfraction(2)=max(0.05,cc*(lfr(i)))
     210    grfraction(3)=max(0.05,cc*(cfr(j)))
     211
    206212
    207213! 2) Computation of precipitation rate in sub-grid cell
    208214!******************************************************
    209215    prec(1)=(lsp+convp)/grfraction(1)
     216    prec(2)=(lsp)/grfraction(2)
     217    prec(3)=(convp)/grfraction(3)
     218
    210219
    211220! 3) Computation of scavenging coefficients for all species
    212221!    Computation of wet deposition
    213222!**********************************************************
     223
    214224
    215225      if (ngrid.gt.0) then
     
    227237!******************************************************************
    228238        if ((dquer(ks).le.0.).and.(weta_gas(ks).gt.0..or.wetb_gas(ks).gt.0.)) then
     239          !        if (weta(ks).gt.0. .or. wetb(ks).gt.0.) then
    229240          blc_count(ks)=blc_count(ks)+1
    230241          wetscav=weta_gas(ks)*prec(1)**wetb_gas(ks)
     
    260271          endif
    261272         
     273!             write(*,*) 'bl-cloud, act_temp=',act_temp, ',prec=',prec(1),',wetscav=', wetscav, ', jpart=',jpart
     274
    262275        endif ! gas or particle
    263276!      endif ! positive below-cloud scavenging parameters given in Species file
     
    272285        if ((ccn_aero(ks).gt.0. .or. in_aero(ks).gt.0.).or.(henry(ks).gt.0.and.dquer(ks).le.0)) then
    273286          inc_count(ks)=inc_count(ks)+1
     287!          write(*,*) 'Incloud: ',inc_count
    274288! if negative coefficients (turned off) set to zero for use in equation
    275289          if (ccn_aero(ks).lt.0.) ccn_aero(ks)=0.
     
    286300! sec test
    287301!           cl=1E6*1E-7*prec(1)**0.3 !Sec GFS new
    288             cl=1E6*2E-7*prec(1)**0.36 !Sec ECMWF new, is also suitable for GFS
     302            cl=1E6*2E-7*prec(1)**0.36 !Sec ECMWF new
    289303!           cl=2E-7*prec(1)**0.36 !Andreas
    290304!           cl=1.6E-6*prec(1)**0.36 !Henrik
     
    308322          if (dquer(ks).gt.0.) then
    309323            S_i= frac_act/cl
     324!           write(*,*) 'Si: ',S_i
     325
    310326! GAS
    311327!****
    312328          else
     329
    313330            cle=(1-cl)/(henry(ks)*(r_air/3500.)*act_temp)+cl
     331!REPLACE to switch old/ new scheme
     332          ! S_i=frac_act/cle
    314333            S_i=1/cle
    315334          endif ! gas or particle
    316335
    317336! scavenging coefficient based on Hertel et al 1995 - using the S_i for either gas or aerosol
    318 !SEC wetscav fix, the cloud height is no longer needed, it gives wrong results
     337!OLD
     338          if ((readclouds.and.ngrid.eq.0).or.(readclouds_this_nest.and.ngrid.gt.0)) then
    319339            wetscav=incloud_ratio*S_i*(prec(1)/3.6E6)
     340          else
     341!SEC wetscav fix
     342             wetscav=incloud_ratio*S_i*(prec(1)/3.6E6)
     343!            wetscav=incloud_ratio*S_i*(prec(1)/3.6E6)/clouds_h
     344          endif
    320345        endif ! positive in-cloud scavenging parameters given in Species file
    321346      endif !incloud
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG