Changeset 341f4b7 in flexpart.git for src/wetdepo.f90


Ignore:
Timestamp:
Apr 20, 2016, 1:39:51 PM (8 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
61df8d9
Parents:
32b49c3
Message:

SPECIES files converted to namelist format. Fixed-format SPCIES files renamed with .oldformat extension. Added 2 wet depo parameters to old-format SPECIES. Renamed internal variables and parameters used for wet deposition. incloud_ratio increased to 2.2

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/wetdepo.f90

    rec7fc72 r341f4b7  
    270270      if (clouds_v.ge.4) then !below cloud
    271271
    272         if (weta(ks).gt.0. .or. wetb(ks).gt.0.) then !if positive below-cloud parameters given in SPECIES file (either A or B)
     272! For gas: if positive below-cloud parameters (A or B), and dquer<=0
     273!******************************************************************
     274        if ((dquer(ks).le.0.).and.(weta_gas(ks).gt.0..or.wetb_gas(ks).gt.0.)) then
     275          !        if (weta(ks).gt.0. .or. wetb(ks).gt.0.) then
    273276          blc_count=blc_count+1
    274 
    275 !GAS
    276           if (dquer(ks) .le. 0.) then  !is gas
    277             wetscav=weta(ks)*prec(1)**wetb(ks)
    278 
    279 !AEROSOL
    280           else !is particle
     277          wetscav=weta_gas(ks)*prec(1)**wetb_gas(ks)
     278
     279! For aerosols: if positive below-cloud parameters (Crain/Csnow or B), and dquer>0
     280!*********************************************************************************
     281        else if ((dquer(ks).gt.0.).and.(crain_aero(ks).gt.0..or.csnow_aero(ks).gt.0.)) then
     282          blc_count=blc_count+1
     283
    281284!NIK 17.02.2015
    282 ! For the calculation here particle size needs to be in meter and not um as dquer is changed to in readreleases
    283 ! for particles larger than 10 um use the largest size defined in the parameterizations (10um)
    284             dquer_m=min(10.,dquer(ks))/1000000. !conversion from um to m
    285             if (act_temp .ge. 273. .and. weta(ks).gt.0.)  then !Rain
     285! For the calculation here particle size needs to be in meter and not um as dquer is
     286! changed in readreleases
     287! For particles larger than 10 um use the largest size defined in the parameterizations (10um)
     288          dquer_m=min(10.,dquer(ks))/1000000. !conversion from um to m
     289
     290! Rain:
     291          if (act_temp .ge. 273. .and. crain_aero(ks).gt.0.)  then
     292
    286293! ZHG 2014 : Particle RAIN scavenging coefficient based on Laakso et al 2003,
    287 ! the below-cloud scavenging (rain efficienty)
    288 ! parameter A (=weta) from SPECIES file
    289               wetscav= weta(ks)*10**(bclr(1)+ (bclr(2)*(log10(dquer_m))**(-4))+(bclr(3)*(log10(dquer_m))**(-3))+ (bclr(4)* &
    290                    (log10(dquer_m))**(-2))+ (bclr(5)*(log10(dquer_m))**(-1))+ bclr(6)* (prec(1))**(0.5))
    291 
    292             elseif (act_temp .lt. 273. .and. wetb(ks).gt.0.)  then ! Snow
     294! the below-cloud scavenging (rain efficienty) parameter Crain (=crain_aero) from SPECIES file
     295            wetscav=crain_aero(ks)*10**(bclr(1)+(bclr(2)*(log10(dquer_m))**(-4))+ &
     296                 & (bclr(3)*(log10(dquer_m))**(-3))+ (bclr(4)*(log10(dquer_m))**(-2))+&
     297                 &(bclr(5)*(log10(dquer_m))**(-1))+bclr(6)* (prec(1))**(0.5))
     298
     299! Snow:
     300          elseif (act_temp .lt. 273. .and. csnow_aero(ks).gt.0.)  then
    293301! ZHG 2014 : Particle SNOW scavenging coefficient based on Kyro et al 2009,
    294 ! the below-cloud scavenging (Snow efficiency)
    295 ! parameter B (=wetb) from SPECIES file
    296               wetscav= wetb(ks)*10**(bcls(1)+ (bcls(2)*(log10(dquer_m))**(-4))+(bcls(3)*(log10(dquer_m))**(-3))+ (bcls(4)* &
    297                    (log10(dquer_m))**(-2))+ (bcls(5)*(log10(dquer_m))**(-1))+ bcls(6)* (prec(1))**(0.5))
    298 
    299             endif
    300 
     302! the below-cloud scavenging (Snow efficiency) parameter Csnow (=csnow_aero) from SPECIES file
     303            wetscav=csnow_aero(ks)*10**(bcls(1)+(bcls(2)*(log10(dquer_m))**(-4))+&
     304                 &(bcls(3)*(log10(dquer_m))**(-3))+ (bcls(4)*(log10(dquer_m))**(-2))+&
     305                 &(bcls(5)*(log10(dquer_m))**(-1))+ bcls(6)* (prec(1))**(0.5))
     306
     307          endif
     308         
    301309!             write(*,*) 'bl-cloud, act_temp=',act_temp, ',prec=',prec(1),',wetscav=', wetscav, ', jpart=',jpart
    302310
    303           endif !gas or particle
    304         endif ! positive below-cloud scavenging parameters given in Species file
     311        endif ! gas or particle
     312!      endif ! positive below-cloud scavenging parameters given in Species file
    305313      endif !end BELOW
    306 
    307314
    308315!********************
     
    310317!********************
    311318      if (clouds_v.lt.4) then ! In-cloud
    312 ! NIK 13 may 2015: only do incloud if positive in-cloud scavenging parameters are given in species file
    313         if (weta_in(ks).gt.0. .or. wetb_in(ks).gt.0.) then
     319! NIK 13 may 2015: only do incloud if positive in-cloud scavenging parameters are
     320! given in species file, or if gas and positive Henry's constant
     321        if ((ccn_aero(ks).gt.0. .or. in_aero(ks).gt.0.).or.(henry(ks).gt.0.and.dquer(ks).le.0)) then
    314322          inc_count=inc_count+1
    315323! if negative coefficients (turned off) set to zero for use in equation
    316           if (weta_in(ks).lt.0.) weta_in(ks)=0.
    317           if (wetb_in(ks).lt.0.) wetb_in(ks)=0.
     324          if (ccn_aero(ks).lt.0.) ccn_aero(ks)=0.
     325          if (in_aero(ks).lt.0.) in_aero(ks)=0.
    318326
    319327!ZHG 2015 Cloud liquid & ice water (CLWC+CIWC) from ECMWF
    320328! nested fields
    321329          if (ngrid.gt.0.and.readclouds_this_nest) then
    322             cl=clw4n(ix,jy,n,ngrid)*(grfraction(1)/cc)
     330            cl=ctwcn(ix,jy,n,ngrid)*(grfraction(1)/cc)
    323331          else if (ngrid.eq.0.and.readclouds) then
    324             cl=clw4(ix,jy,n)*(grfraction(1)/cc)
     332            cl=ctwc(ix,jy,n)*(grfraction(1)/cc)
    325333          else                                  !parameterize cloudwater m2/m3
    326334!ZHG updated parameterization of cloud water to better reproduce the values coming from ECMWF
     
    337345          end if
    338346! ZHG: Calculate the aerosol partition based on cloud phase and Ai and Bi
    339           frac_act = liq_frac*weta_in(ks) +(1-liq_frac)*wetb_in(ks)
     347          frac_act = liq_frac*ccn_aero(ks) +(1-liq_frac)*in_aero(ks)
    340348
    341349!ZHG Use the activated fraction and the liqid water to calculate the washout
     
    343351! AEROSOL
    344352!**************************************************
    345           if (dquer(ks).gt. 0.) then ! is particle
     353          if (dquer(ks).gt.0.) then ! is particle
    346354
    347355            S_i= frac_act/cl
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG