Changeset 8a65cb0 in flexpart.git for src/wetdepo.f90


Ignore:
Timestamp:
Mar 2, 2015, 3:11:55 PM (9 years ago)
Author:
Espen Sollum ATMOS <espen@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
1d207bb
Parents:
60403cd
Message:

Added code, makefile for dev branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/wetdepo.f90

    r4fbe7a5 r8a65cb0  
    7373  integer :: ngrid,itage,nage,hz,il,interp_time, n, clouds_v
    7474  integer :: ks, kp
     75  integer :: n1,n2, icbot,ictop, indcloud !TEST
    7576  real :: S_i, act_temp, cl, cle ! in cloud scavenging
    7677  real :: clouds_h ! cloud height for the specific grid point
    77   real :: xtn,ytn,lsp,convp,cc,grfraction,prec,wetscav
     78  real :: xtn,ytn,lsp,convp,cc,grfraction(3),prec(3),wetscav,totprec
    7879  real :: wetdeposit(maxspec),restmass
    7980  real,parameter :: smallnum = tiny(0.0) ! smallest number that can be handled
    8081  save lfr,cfr
    8182
    82 
    8383  real :: lfr(5) = (/ 0.5,0.65,0.8,0.9,0.95/)
    8484  real :: cfr(5) = (/ 0.4,0.55,0.7,0.8,0.9 /)
     85
     86!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)
     89  real :: frac_act, liq_frac, dquer_m
     90
     91  integer :: blc_count, inc_count
     92
     93
    8594
    8695  ! Compute interval since radioactive decay of deposited mass was computed
     
    93102  endif
    94103
    95 
    96104  ! Loop over all particles
    97105  !************************
     106
     107
     108  blc_count=0
     109  inc_count=0
    98110
    99111  do jpart=1,numpart
     
    105117      if (itra1(jpart).lt.itime) goto 20
    106118    endif
     119
    107120  ! Determine age class of the particle
    108121    itage=abs(itra1(jpart)-itramem(jpart))
     
    157170    endif
    158171
    159     if ((lsp.lt.0.01).and.(convp.lt.0.01)) goto 20
     172!  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
     174
    160175  ! get the level were the actual particle is in
    161176    do il=2,nz
     
    171186    n=memind(1)
    172187
    173   ! if there is no precipitation or the particle is above the clouds no
    174   ! scavenging is done
    175 
    176188    if (ngrid.eq.0) then
    177189      clouds_v=clouds(ix,jy,hz,n)
     
    181193      clouds_h=cloudsnh(ix,jy,n,ngrid)
    182194    endif
    183   !write(*,*) 'there is
    184   !    + precipitation',(clouds(ix,jy,ihz,n),ihz=1,20),lsp,convp,hz
    185     if (clouds_v.le.1) goto 20
    186   !write (*,*) 'there is scavenging'
    187 
     195
     196  ! if there is no precipitation or the particle is above the clouds no
     197  ! scavenging is done
     198
     199     if (clouds_v.le.1) goto 20
     200 
    188201  ! 1) Parameterization of the the area fraction of the grid cell where the
    189202  !    precipitation occurs: the absolute limit is the total cloud cover, but
     
    217230    endif
    218231
    219     grfraction=max(0.05,cc*(lsp*lfr(i)+convp*cfr(j))/(lsp+convp))
     232
     233!ZHG calculated for 1) both 2) lsp 3) convp
     234    grfraction(1)=max(0.05,cc*(lsp*lfr(i)+convp*cfr(j))/(lsp+convp))
     235    grfraction(2)=max(0.05,cc*(lfr(i)))
     236    grfraction(3)=max(0.05,cc*(cfr(j)))
     237
    220238
    221239  ! 2) Computation of precipitation rate in sub-grid cell
    222240  !******************************************************
    223 
    224     prec=(lsp+convp)/grfraction
     241    prec(1)=(lsp+convp)/grfraction(1)
     242    prec(2)=(lsp)/grfraction(2)
     243    prec(3)=(convp)/grfraction(3)
     244
    225245
    226246  ! 3) Computation of scavenging coefficients for all species
     
    232252      wetscav=0.   
    233253
    234   ! NIK 09.12.13: allowed to turn off either below cloud or in-cloud by including TWO separate blocks of if tests
    235 
     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
     259     
    236260
    237261  !****i*******************
    238262  ! BELOW CLOUD SCAVENGING
    239263  !*********************** 
    240       if (weta(ks).gt.0. .and. clouds_v.ge.4) then !if positive below-cloud coefficient given in SPECIES file, and if in below cloud regime
    241  !       for aerosols and not highliy soluble substances weta=5E-6
    242         wetscav=weta(ks)*prec**wetb(ks)  ! scavenging coefficient
     264      if (clouds_v.ge.4) then !below cloud
     265
     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
     268
     269!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
     272            wetscav=weta(ks)*prec(1)**wetb(ks)
     273
     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         
     294
     295!             write(*,*) 'bl-cloud, act_temp=',act_temp, ',prec=',prec(1),',wetscav=', wetscav, ', jpart=',jpart
     296
     297           endif !gas or particle
     298         endif ! positive below-cloud scavenging parameters given in Species file
    243299      endif !end below-cloud
    244300
     
    247303  ! IN CLOUD SCAVENGING
    248304  !********************
    249       if (weta_in(ks).gt.0. .and. clouds_v.lt.4) then !if positive in-cloud coefficient given in SPECIES file, and if in in-cloud regime
    250 
    251         if (ngrid.gt.0) then
    252           act_temp=ttn(ix,jy,hz,n,ngrid)
    253         else
    254           act_temp=tt(ix,jy,hz,n)
    255         endif
    256 
    257 ! NIK 31.01.2013: SPECIES defined parameters for the in-cloud scavening
    258 ! weta_in=2.0E-07 (default)
    259 ! wetb_in=0.36 (default)
    260 ! wetc_in=0.9 (default)
    261 ! wetd_in: Scaling factor for the total in-cloud scavenging (default 1.0-no scaling)
    262         cl=weta_in(ks)*prec**wetb_in(ks)
    263         if (dquer(ks).gt.0) then ! is particle
    264           S_i=wetc_in(ks)/cl
    265         else ! is gas
    266           cle=(1-cl)/(henry(ks)*(r_air/3500.)*act_temp)+cl
    267           S_i=1/cle
    268         endif
    269         wetscav=S_i*prec/3.6E6/clouds_h/wetd_in(ks)
    270   !     write(*,*) 'in. wetscav:'
    271   !     +  ,wetscav,cle,cl,act_temp,prec,clouds_h
    272        
    273       endif ! end in-cloud
    274 
    275 
    276      
     305      if (clouds_v.lt.4) then !in-cloud
     306
     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
     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)
     331 
     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
     343
     344!          write(*,*) 'in-cloud, act_temp=',act_temp,',prec=',prec(1),',wetscav=',wetscav,',jpart=',jpart,',clouds_h=,', &
     345!          clouds_h,',cl=',cl, 'diff to old scheme=', cl-2E-7*prec(1)**0.36
     346
     347      endif !incloud
     348
    277349  !**************************************************
    278350  ! CALCULATE DEPOSITION
     
    283355      if (wetscav.gt.0.) then
    284356        wetdeposit(ks)=xmass1(jpart,ks)* &
    285         (1.-exp(-wetscav*abs(ltsample)))*grfraction  ! wet deposition
     357        (1.-exp(-wetscav*abs(ltsample)))*grfraction(1)  ! wet deposition
    286358      else ! if no scavenging
    287359        wetdeposit(ks)=0.
    288360      endif
    289 
    290361
    291362      restmass = xmass1(jpart,ks)-wetdeposit(ks)
     
    310381
    311382
    312 
    313383    end do !all species
    314384
     
    327397  end do ! all particles
    328398
     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
     402
    329403end subroutine wetdepo
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG