Changeset e9e0f06 in flexpart.git for src/get_wetscav.f90


Ignore:
Timestamp:
Dec 12, 2018, 1:35:46 PM (5 years ago)
Author:
Sabine <sabine.eckhardt@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug
Children:
79996be9
Parents:
db91eb7
Message:

Removed kao and ass_spec and obsolete lines in get_wetscav.f90

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/get_wetscav.f90

    r79e0349 re9e0f06  
    151151      if (height(il).gt.ztra1(jpart)) then
    152152        hz=il-1
    153 !        goto 26
    154153        exit
    155154      endif
    156155    end do
    157 !26  continue
    158 
    159156
    160157    if (ngrid.eq.0) then
     
    203200
    204201
    205 !ZHG oct 2014 : Calculated for 1) both 2) lsp 3) convp
     202!ZHG oct 2014 : Calculated for 1) both 2) lsp 3) convp - 2 and 3 not used removed by SE
    206203! Tentatively differentiate the grfraction for lsp and convp for treating differently the two forms
    207204! for now they are treated the same
    208205    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 
    212206
    213207! 2) Computation of precipitation rate in sub-grid cell
    214208!******************************************************
    215209    prec(1)=(lsp+convp)/grfraction(1)
    216     prec(2)=(lsp)/grfraction(2)
    217     prec(3)=(convp)/grfraction(3)
    218 
    219210
    220211! 3) Computation of scavenging coefficients for all species
    221212!    Computation of wet deposition
    222213!**********************************************************
    223 
    224214
    225215      if (ngrid.gt.0) then
     
    237227!******************************************************************
    238228        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
    240229          blc_count(ks)=blc_count(ks)+1
    241230          wetscav=weta_gas(ks)*prec(1)**wetb_gas(ks)
     
    271260          endif
    272261         
    273 !             write(*,*) 'bl-cloud, act_temp=',act_temp, ',prec=',prec(1),',wetscav=', wetscav, ', jpart=',jpart
    274 
    275262        endif ! gas or particle
    276263!      endif ! positive below-cloud scavenging parameters given in Species file
     
    285272        if ((ccn_aero(ks).gt.0. .or. in_aero(ks).gt.0.).or.(henry(ks).gt.0.and.dquer(ks).le.0)) then
    286273          inc_count(ks)=inc_count(ks)+1
    287 !          write(*,*) 'Incloud: ',inc_count
    288274! if negative coefficients (turned off) set to zero for use in equation
    289275          if (ccn_aero(ks).lt.0.) ccn_aero(ks)=0.
     
    300286! sec test
    301287!           cl=1E6*1E-7*prec(1)**0.3 !Sec GFS new
    302             cl=1E6*2E-7*prec(1)**0.36 !Sec ECMWF new
     288            cl=1E6*2E-7*prec(1)**0.36 !Sec ECMWF new, is also suitable for GFS
    303289!           cl=2E-7*prec(1)**0.36 !Andreas
    304290!           cl=1.6E-6*prec(1)**0.36 !Henrik
     
    322308          if (dquer(ks).gt.0.) then
    323309            S_i= frac_act/cl
    324 !           write(*,*) 'Si: ',S_i
    325 
    326310! GAS
    327311!****
    328312          else
    329 
    330313            cle=(1-cl)/(henry(ks)*(r_air/3500.)*act_temp)+cl
    331 !REPLACE to switch old/ new scheme
    332           ! S_i=frac_act/cle
    333314            S_i=1/cle
    334315          endif ! gas or particle
    335316
    336317! scavenging coefficient based on Hertel et al 1995 - using the S_i for either gas or aerosol
    337 !OLD
    338           if ((readclouds.and.ngrid.eq.0).or.(readclouds_this_nest.and.ngrid.gt.0)) then
     318!SEC wetscav fix, the cloud height is no longer needed, it gives wrong results
    339319            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
    345320        endif ! positive in-cloud scavenging parameters given in Species file
    346321      endif !incloud
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG