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


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/get_wetscav.f90

    r79e0349 rc7e771d  
    7272  integer(kind=1) :: clouds_v
    7373  integer :: ks, kp
    74   integer(selected_int_kind(16)), dimension(nspec) :: blc_count, inc_count
    75 
     74  integer :: inc_count, blc_count
    7675!  integer :: n1,n2, icbot,ictop, indcloud !TEST
    7776  real :: S_i, act_temp, cl, cle ! in cloud scavenging
     
    238237        if ((dquer(ks).le.0.).and.(weta_gas(ks).gt.0..or.wetb_gas(ks).gt.0.)) then
    239238          !        if (weta(ks).gt.0. .or. wetb(ks).gt.0.) then
    240           blc_count(ks)=blc_count(ks)+1
     239          blc_count=blc_count+1
    241240          wetscav=weta_gas(ks)*prec(1)**wetb_gas(ks)
    242241
     
    244243!*********************************************************************************
    245244        else if ((dquer(ks).gt.0.).and.(crain_aero(ks).gt.0..or.csnow_aero(ks).gt.0.)) then
    246           blc_count(ks)=blc_count(ks)+1
     245          blc_count=blc_count+1
    247246
    248247!NIK 17.02.2015
     
    284283! given in species file, or if gas and positive Henry's constant
    285284        if ((ccn_aero(ks).gt.0. .or. in_aero(ks).gt.0.).or.(henry(ks).gt.0.and.dquer(ks).le.0)) then
    286           inc_count(ks)=inc_count(ks)+1
     285          inc_count=inc_count+1
    287286!          write(*,*) 'Incloud: ',inc_count
    288287! if negative coefficients (turned off) set to zero for use in equation
     
    298297          else                                  !parameterize cloudwater m2/m3
    299298!ZHG updated parameterization of cloud water to better reproduce the values coming from ECMWF
    300 ! sec test
    301 !           cl=1E6*1E-7*prec(1)**0.3 !Sec GFS new
    302             cl=1E6*2E-7*prec(1)**0.36 !Sec ECMWF new
    303 !           cl=2E-7*prec(1)**0.36 !Andreas
    304 !           cl=1.6E-6*prec(1)**0.36 !Henrik
     299            cl=1.6E-6*prec(1)**0.36
    305300          endif
    306301
     
    322317          if (dquer(ks).gt.0.) then
    323318            S_i= frac_act/cl
    324 !           write(*,*) 'Si: ',S_i
    325319
    326320! GAS
     
    339333            wetscav=incloud_ratio*S_i*(prec(1)/3.6E6)
    340334          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
     335            wetscav=incloud_ratio*S_i*(prec(1)/3.6E6)/clouds_h
    344336          endif
    345337        endif ! positive in-cloud scavenging parameters given in Species file
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG