Changeset 5f9d14a in flexpart.git for src/wetdepo.f90


Ignore:
Timestamp:
Apr 8, 2015, 2:23:27 PM (9 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:
1585284
Parents:
cd85138
Message:

Updated wet depo scheme

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/wetdepo.f90

    r8a65cb0 r5f9d14a  
    7979  real :: wetdeposit(maxspec),restmass
    8080  real,parameter :: smallnum = tiny(0.0) ! smallest number that can be handled
    81   save lfr,cfr
    82 
    83   real :: lfr(5) = (/ 0.5,0.65,0.8,0.9,0.95/)
    84   real :: cfr(5) = (/ 0.4,0.55,0.7,0.8,0.9 /)
     81  !save lfr,cfr
     82
     83  real, parameter :: lfr(5) = (/ 0.5,0.65,0.8,0.9,0.95/)
     84  real, parameter :: cfr(5) = (/ 0.4,0.55,0.7,0.8,0.9 /)
    8585
    8686!ZHG aerosol below-cloud scavenging removal polynomial constants for rain and snow
    87   real :: bclr(6) = (/274.35758, 332839.59273, 226656.57259, 58005.91340, 6588.38582, 0.244984/) !rain (Laakso et al 2003)
    88   real :: bcls(6) = (/ 22.7, 0.0, 0.0, 1321.0, 381.0, 0.0/) !now (Kyro et al 2009)
     87  real, parameter :: bclr(6) = (/274.35758, 332839.59273, 226656.57259, 58005.91340, 6588.38582, 0.244984/) !rain (Laakso et al 2003)
     88  real, parameter :: bcls(6) = (/22.7, 0.0, 0.0, 1321.0, 381.0, 0.0/) !now (Kyro et al 2009)
    8989  real :: frac_act, liq_frac, dquer_m
    9090
     
    159159  !********************************************************************
    160160    interp_time=nint(itime-0.5*ltsample)
    161 
     161   
    162162    if (ngrid.eq.0) then
    163163      call interpol_rain(lsprec,convprec,tcc,nxmax,nymax, &
     
    171171
    172172!  If total precipitation is less than 0.01 mm/h - no scavenging occurs
    173      if ((lsp.lt.0.01).and.(convp.lt.0.01)) goto 20
     173    if ((lsp.lt.0.01).and.(convp.lt.0.01)) goto 20
    174174
    175175  ! get the level were the actual particle is in
     
    231231
    232232
    233 !ZHG calculated for 1) both 2) lsp 3) convp
     233  !ZHG calculated for 1) both 2) lsp 3) convp
    234234    grfraction(1)=max(0.05,cc*(lsp*lfr(i)+convp*cfr(j))/(lsp+convp))
    235235    grfraction(2)=max(0.05,cc*(lfr(i)))
     
    252252      wetscav=0.   
    253253
    254      if (ngrid.gt.0) then
    255        act_temp=ttn(ix,jy,hz,n,ngrid)
    256      else
    257        act_temp=tt(ix,jy,hz,n)
    258      endif
     254      if (ngrid.gt.0) then
     255        act_temp=ttn(ix,jy,hz,n,ngrid)
     256      else
     257        act_temp=tt(ix,jy,hz,n)
     258      endif
    259259     
    260260
     
    264264      if (clouds_v.ge.4) then !below cloud
    265265
    266          if (weta(ks).gt.0. .or. wetb(ks).gt.0) then !if positive below-cloud parameters given in SPECIES file (either A or B)
    267             blc_count=blc_count+1
     266        if (weta(ks).gt.0. .or. wetb(ks).gt.0) then !if positive below-cloud parameters given in SPECIES file (either A or B)
     267          blc_count=blc_count+1
    268268
    269269!GAS
    270            if (dquer(ks) .le. 0.) then  !is gas
    271             !Gas scavenging coefficient based on Hertel et al 1995 using the below-cloud scavenging parameters A (=weta) and B (=wetb) from SPECIES file
     270          if (dquer(ks) .le. 0.) then  !is gas
     271  ! Gas scavenging coefficient based on Hertel et al 1995 using the below-cloud scavenging parameters A (=weta) and B (=wetb) from SPECIES file
    272272            wetscav=weta(ks)*prec(1)**wetb(ks)
    273273
    274 !AEROSOL
    275            else !is particle
    276              !NIK 17.02.2015
    277              ! For the calculation here particle size needs to be in meter and not um as dquer is changed to in readreleases
    278              dquer_m=dquer(ks)/1000000. !conversion from um to m
    279 
    280              !ZHG snow or rain removal is applied based on the temperature.
    281              if (act_temp .ge. 273)  then !Rain
    282  
    283              !Particle RAIN scavenging coefficient based on Laakso et al 2003, the below-cloud scavenging (rain efficienty) parameter A (=weta) from SPECIES file
    284                  wetscav= weta(ks)*10**(bclr(1)+ (bclr(2)*(log10(dquer_m))**(-4))+(bclr(3)*(log10(dquer_m))**(-3))+ (bclr(4)* &
    285                 (log10(dquer_m))**(-2))+ (bclr(5)*(log10(dquer_m))**(-1))+ bclr(6)* (prec(1))**(0.5))
    286 
    287              elseif (act_temp .lt. 273)  then !snow
    288  
    289              !Particle SNOW scavenging coefficient based on Kyro et al 2009, the below-cloud scavenging (Snow efficiency) parameter B (=wetb) from SPECIES file
    290                 wetscav= wetb(ks)*10**(bcls(1)+ (bcls(2)*(log10(dquer_m))**(-4))+(bcls(3)*(log10(dquer_m))**(-3))+ (bcls(4)* &
    291                 (log10(dquer_m))**(-2))+ (bcls(5)*(log10(dquer_m))**(-1))+ bcls(6)* (prec(1))**(0.5))
    292 
    293              endif         
     274  !AEROSOL
     275          else !is particle
     276  !NIK 17.02.2015
     277  ! For the calculation here particle size needs to be in meter and not um as dquer is changed to in readreleases
     278            dquer_m=dquer(ks)/1000000. !conversion from um to m
     279           
     280  !ZHG snow or rain removal is applied based on the temperature.
     281            if (act_temp .ge. 273)  then !Rain
     282
     283  !Particle RAIN scavenging coefficient based on Laakso et al 2003, the below-cloud scavenging (rain efficienty) parameter A (=weta) from SPECIES file
     284              wetscav= weta(ks)*10**(bclr(1)+ (bclr(2)*(log10(dquer_m))**(-4))+(bclr(3)*(log10(dquer_m))**(-3))+ (bclr(4)* &
     285                   (log10(dquer_m))**(-2))+ (bclr(5)*(log10(dquer_m))**(-1))+ bclr(6)* (prec(1))**(0.5))
     286
     287            elseif (act_temp .lt. 273)  then !snow
     288
     289  !Particle SNOW scavenging coefficient based on Kyro et al 2009, the below-cloud scavenging (Snow efficiency) parameter B (=wetb) from SPECIES file
     290              wetscav= wetb(ks)*10**(bcls(1)+ (bcls(2)*(log10(dquer_m))**(-4))+(bcls(3)*(log10(dquer_m))**(-3))+ (bcls(4)* &
     291                   (log10(dquer_m))**(-2))+ (bcls(5)*(log10(dquer_m))**(-1))+ bcls(6)* (prec(1))**(0.5))
     292
     293            endif
    294294
    295295!             write(*,*) 'bl-cloud, act_temp=',act_temp, ',prec=',prec(1),',wetscav=', wetscav, ', jpart=',jpart
    296296
    297            endif !gas or particle
    298          endif ! positive below-cloud scavenging parameters given in Species file
     297          endif !gas or particle
     298        endif ! positive below-cloud scavenging parameters given in Species file
    299299      endif !end below-cloud
    300300
     
    305305      if (clouds_v.lt.4) then !in-cloud
    306306
    307           inc_count=inc_count+1
    308 
    309           !ZHG liquid water parameterization (CLWC+CIWC)
    310           if (readclouds) then !get cloud water clwc & ciwc units Kg/Kg
    311              cl=clwc(ix,jy,hz,n)+ciwc(ix,jy,hz,n)
    312           else !parameterize cloudwater
    313              cl=2E-7*prec(1)**0.36
     307        inc_count=inc_count+1
     308
     309  !ZHG liquid water parameterization (CLWC+CIWC)
     310        if (readclouds) then !get cloud water clwc & ciwc units Kg/Kg
     311          cl=clwc(ix,jy,hz,n)+ciwc(ix,jy,hz,n)
     312        else !parameterize cloudwater
     313          cl=2E-7*prec(1)**0.36
     314        endif
     315
     316  ! AEROSOL
     317        if (dquer(ks).gt. 0.) then ! is particle
     318          if (act_temp .le. 253) then
     319            liq_frac=0
     320          else if (act_temp .ge. 273) then
     321            liq_frac=1
     322          else
     323            liq_frac =((act_temp-273)/(273-253))**2
    314324          endif
    315325
    316 ! AEROSOL
    317           if (dquer(ks).gt. 0.) then ! is particle
    318             if (act_temp .le. 253) then
    319               liq_frac=0
    320             else if (act_temp .ge. 273) then
    321               liq_frac=1
    322             else
    323               liq_frac =((act_temp-273)/(273-253))**2
    324             endif
    325 
    326             !ZHG  calculate the activated fraction based on the In-cloud scavenging parameters Ai (=weta_in) and Bi (=wetb_in) from SPECIES file
    327             ! frac_act is the combined IN and CCN efficiency
    328             ! The default values are 0.9 for CCN and 0.1 IN
    329             ! This parameterization is based on Verheggen et al. (2007) & Cozich et al. (2006)
    330             frac_act = liq_frac*weta_in(ks) +(1-liq_frac)*wetb_in(ks)
     326! ZHG  calculate the activated fraction based on the In-cloud scavenging parameters Ai (=weta_in) and Bi (=wetb_in) from SPECIES file
     327! frac_act is the combined IN and CCN efficiency
     328! The default values are 0.9 for CCN and 0.1 IN
     329! This parameterization is based on Verheggen et al. (2007) & Cozich et al. (2006)
     330          frac_act = liq_frac*weta_in(ks) +(1-liq_frac)*wetb_in(ks)
    331331 
    332             !ZHG Use the activated fraction and the liqid water to calculate the washout
    333             S_i= frac_act/cl
    334 
    335 ! GAS
    336           else ! is gas
    337             cle=(1-cl)/(henry(ks)*(r_air/3500.)*act_temp)+cl
    338             S_i=1/cle
    339           endif
    340 
    341           ! scavenging coefficient based on Hertel et al 1995 - using the S_i for either gas or aerosol
    342           wetscav=S_i*(prec(1)/3.6E6)/clouds_h
     332  !ZHG Use the activated fraction and the liqid water to calculate the washout
     333          S_i= frac_act/cl
     334
     335  ! GAS
     336        else ! is gas
     337          cle=(1-cl)/(henry(ks)*(r_air/3500.)*act_temp)+cl
     338          S_i=1/cle
     339        endif
     340
     341  ! scavenging coefficient based on Hertel et al 1995 - using the S_i for either gas or aerosol
     342        wetscav=S_i*(prec(1)/3.6E6)/clouds_h
    343343
    344344!          write(*,*) 'in-cloud, act_temp=',act_temp,',prec=',prec(1),',wetscav=',wetscav,',jpart=',jpart,',clouds_h=,', &
     
    346346
    347347      endif !incloud
    348 
     348     
    349349  !**************************************************
    350350  ! CALCULATE DEPOSITION
     
    355355      if (wetscav.gt.0.) then
    356356        wetdeposit(ks)=xmass1(jpart,ks)* &
    357         (1.-exp(-wetscav*abs(ltsample)))*grfraction(1)  ! wet deposition
     357             (1.-exp(-wetscav*abs(ltsample)))*grfraction(1)  ! wet deposition
    358358      else ! if no scavenging
    359359        wetdeposit(ks)=0.
     
    389389    if (ldirect.eq.1) then
    390390      call wetdepokernel(nclass(jpart),wetdeposit,real(xtra1(jpart)), &
    391       real(ytra1(jpart)),nage,kp)
     391           real(ytra1(jpart)),nage,kp)
    392392      if (nested_output.eq.1) call wetdepokernel_nest(nclass(jpart), &
    393         wetdeposit,real(xtra1(jpart)),real(ytra1(jpart)),nage,kp)
     393           wetdeposit,real(xtra1(jpart)),real(ytra1(jpart)),nage,kp)
    394394    endif
    395395
     
    397397  end do ! all particles
    398398
    399 ! count the total number of below-cloud and in-cloud occurences:
    400    tot_blc_count=tot_blc_count+blc_count
    401    tot_inc_count=tot_inc_count+inc_count
     399  ! count the total number of below-cloud and in-cloud occurences:
     400  tot_blc_count=tot_blc_count+blc_count
     401  tot_inc_count=tot_inc_count+inc_count
    402402
    403403end subroutine wetdepo
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG