Changeset d6a0977 in flexpart.git for src/wetdepo.f90


Ignore:
Timestamp:
Dec 14, 2015, 3:10:04 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:
f75967d
Parents:
88d8c3d
Message:

Updates to Henrik's wet depo scheme

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/wetdepo.f90

    r0f20c31 rd6a0977  
    9090
    9191  integer :: blc_count, inc_count
     92  real    :: Si_dummy, wetscav_dummy
    9293
    9394
     
    190191      clouds_h=cloudsh(ix,jy,n)
    191192    else
     193      ! new removal not implemented for nests yet
    192194      clouds_v=cloudsn(ix,jy,hz,n,ngrid)
    193195      clouds_h=cloudsnh(ix,jy,n,ngrid)
     
    231233
    232234
    233   !ZHG calculated for 1) both 2) lsp 3) convp
     235  !ZHG oct 2014 : Calculated for 1) both 2) lsp 3) convp
     236  ! Tentatively differentiate the grfraction for lsp and convp for treating differently the two forms
     237  ! for now they are treated the same
    234238    grfraction(1)=max(0.05,cc*(lsp*lfr(i)+convp*cfr(j))/(lsp+convp))
    235239    grfraction(2)=max(0.05,cc*(lfr(i)))
     
    252256      wetscav=0.   
    253257
     258      !ZHG test if it nested?
    254259      if (ngrid.gt.0) then
    255260        act_temp=ttn(ix,jy,hz,n,ngrid)
     
    259264     
    260265
    261   !****i*******************
     266  !***********************
    262267  ! BELOW CLOUD SCAVENGING
    263268  !*********************** 
     
    267272          blc_count=blc_count+1
    268273
    269 
    270274!GAS
    271275          if (dquer(ks) .le. 0.) then  !is gas
    272   ! Gas scavenging coefficient based on Hertel et al 1995 using the below-cloud scavenging parameters A (=weta) and B (=wetb) from SPECIES file
    273             wetscav=weta(ks)*prec(1)**wetb(ks)
    274 
    275   !AEROSOL
     276            wetscav=weta(ks)*prec(1)**wetb(ks)
     277           
     278!AEROSOL
    276279          else !is particle
    277   !NIK 17.02.2015
    278   ! For the calculation here particle size needs to be in meter and not um as dquer is changed to in readreleases
    279             dquer_m=dquer(ks)/1000000. !conversion from um to m
    280            
    281   !ZHG snow or rain removal is applied based on the temperature.
     280!NIK 17.02.2015
     281! For the calculation here particle size needs to be in meter and not um as dquer is changed to in readreleases
     282! for particles larger than 10 um use the largest size defined in the parameterizations (10um)
     283            dquer_m=min(10.,dquer(ks))/1000000. !conversion from um to m
    282284            if (act_temp .ge. 273 .and. weta(ks).gt.0.)  then !Rain
    283 
    284   !Particle RAIN scavenging coefficient based on Laakso et al 2003, the below-cloud scavenging (rain efficienty) parameter A (=weta) from SPECIES file
     285              ! ZHG 2014 : Particle RAIN scavenging coefficient based on Laakso et al 2003,
     286              ! the below-cloud scavenging (rain efficienty)
     287              ! parameter A (=weta) from SPECIES file
    285288              wetscav= weta(ks)*10**(bclr(1)+ (bclr(2)*(log10(dquer_m))**(-4))+(bclr(3)*(log10(dquer_m))**(-3))+ (bclr(4)* &
    286289                   (log10(dquer_m))**(-2))+ (bclr(5)*(log10(dquer_m))**(-1))+ bclr(6)* (prec(1))**(0.5))
    287290
    288             elseif (act_temp .lt. 273 .and. wetb(ks).gt.0.)  then !snow
    289 
    290   !Particle SNOW scavenging coefficient based on Kyro et al 2009, the below-cloud scavenging (Snow efficiency) parameter B (=wetb) from SPECIES file
     291            elseif (act_temp .lt. 273 .and. wetb(ks).gt.0.)  then ! Snow
     292              ! ZHG 2014 : Particle SNOW scavenging coefficient based on Kyro et al 2009,
     293              ! the below-cloud scavenging (Snow efficiency)
     294              ! parameter B (=wetb) from SPECIES file
    291295              wetscav= wetb(ks)*10**(bcls(1)+ (bcls(2)*(log10(dquer_m))**(-4))+(bcls(3)*(log10(dquer_m))**(-3))+ (bcls(4)* &
    292296                   (log10(dquer_m))**(-2))+ (bcls(5)*(log10(dquer_m))**(-1))+ bcls(6)* (prec(1))**(0.5))
     
    298302          endif !gas or particle
    299303        endif ! positive below-cloud scavenging parameters given in Species file
    300       endif !end below-cloud
     304      endif !end BELOW
    301305
    302306
    303307  !********************
    304308  ! IN CLOUD SCAVENGING
    305   !********************
    306       if (clouds_v.lt.4) then !in-cloud
    307 
     309      !******************************************************
     310      if (clouds_v.lt.4) then ! In-cloud
    308311! NIK 13 may 2015: only do incloud if positive in-cloud scavenging parameters are given in species file
    309         if (weta_in(ks).gt.0. .or. wetb_in(ks).gt.0.) then !if positive in-cloud parameters given in SPECIES file (either Ai or Bi)
    310 
     312        if (weta_in(ks).gt.0. .or. wetb_in(ks).gt.0.) then
    311313! if negative coefficients (turned off) set to zero for use in equation
    312314          if (weta_in(ks).lt.0.) weta_in(ks)=0.
    313315          if (wetb_in(ks).lt.0.) wetb_in(ks)=0.
    314316
    315           inc_count=inc_count+1
    316 
    317   !ZHG liquid water parameterization (CLWC+CIWC)
    318           if (readclouds) then !get cloud water clwc & ciwc units Kg/Kg
    319             cl=clwc(ix,jy,hz,n)+ciwc(ix,jy,hz,n)
    320           else !parameterize cloudwater
    321             cl=2E-7*prec(1)**0.36
     317          !ZHG 2015 Cloud liquid & ice water (CLWC+CIWC) from ECMWF
     318          if (readclouds) then                  !icloud_stats(ix,jy,4,n) has units kg/m2
     319            cl =icloud_stats(ix,jy,4,n)*(grfraction(1)/cc)
     320          else                                  !parameterize cloudwater m2/m3
     321            !ZHG updated parameterization of cloud water to better reproduce the values coming from ECMWF
     322            cl=1.6E-6*prec(1)**0.36
    322323          endif
    323324
     325            !ZHG: Calculate the partition between liquid and water phase water.
    324326            if (act_temp .le. 253) then
    325327              liq_frac=0
     
    329331              liq_frac =((act_temp-273)/(273-253))**2
    330332            endif
    331 
    332 ! ZHG  calculate the activated fraction based on the In-cloud scavenging parameters Ai (=weta_in) and Bi (=wetb_in) from SPECIES file
    333 ! frac_act is the combined IN and CCN efficiency
    334 ! The default values are 0.9 for CCN and 0.1 IN
    335 ! This parameterization is based on Verheggen et al. (2007) & Cozich et al. (2006)
     333           ! ZHG: Calculate the aerosol partition based on cloud phase and Ai and Bi
    336334            frac_act = liq_frac*weta_in(ks) +(1-liq_frac)*wetb_in(ks)
    337335 
     
    339337
    340338  ! AEROSOL
     339          !**************************************************
    341340          if (dquer(ks).gt. 0.) then ! is particle
    342341
    343342            S_i= frac_act/cl
    344343
     344          !*********************
    345345  ! GAS
    346346          else ! is gas
    347347               
    348348            cle=(1-cl)/(henry(ks)*(r_air/3500.)*act_temp)+cl
    349             S_i=frac_act/cle
    350 
     349            !REPLACE to switch old/ new scheme
     350            ! S_i=frac_act/cle
     351            S_i=1/cle
    351352          endif ! gas or particle
    352353
    353354  ! scavenging coefficient based on Hertel et al 1995 - using the S_i for either gas or aerosol
     355           !OLD
     356          if (readclouds) then
     357           wetscav=S_i*(prec(1)/3.6E6)
     358          else
    354359          wetscav=S_i*(prec(1)/3.6E6)/clouds_h
    355 
    356 !          write(*,*) 'in-cloud, act_temp=',act_temp,',prec=',prec(1),',wetscav=',wetscav,',jpart=',jpart,',clouds_h=,', &
    357 !          clouds_h,',cl=',cl, 'diff to old scheme=', cl-2E-7*prec(1)**0.36
     360          endif
     361
     362!ZHG 2015 TEST
     363!          Si_dummy=frac_act/2E-7*prec(1)**0.36
     364!           wetscav_dummy=Si_dummy*(prec(1)/3.6E6)/clouds_h
     365!           if (clouds_v.lt.4) then
     366!           talltest=talltest+1
     367!if(talltest .eq. 1) OPEN(UNIT=199, FILE=utfil,FORM='FORMATTED',STATUS = 'UNKNOWN')
     368!if(talltest .lt. 100001)  write(199,*) prec(1)/3.6E6, cl, clouds_h*2E-7*prec(1)**0.36,clouds_v,ytra1(jpart)-90
     369!if(talltest .lt. 100001)  write(199,*) wetscav, wetscav_dummy,prec(1),ytra1(jpart)-90,clouds_v,cl
     370!if(talltest .eq. 100001) CLOSE(199)
     371!if(talltest .eq. 100001) STOP
     372!
     373!write(*,*)  'PREC kg/m2s CLOUD kg/m2', (prec(1)/3.6E6), cl !, '2E-7*prec(1)**0.36',  2E-7*prec(1)**0.36,'2E-7*prec(1)**0.36*clouds_h',2E-7*prec(1)**0.36*clouds_h
     374!write(*,*)  'PREC kg/m2s LSP+convp kg/m2', prec(1), convp+lsp
     375!write(*,*)  wetscav, wetscav_dummy
     376!write(*,*) cc, grfraction(1), cc/grfraction(1)
     377
     378!write(*,*)  'Lmbda_old', (prec(1)/3.6E6)/(clouds_h*2E-7*prec(1)**0.36)
     379
     380
     381!write(*,*) '**************************************************'
     382!write(*,*)  'clouds_h', clouds_h, 'clouds_v',clouds_v,'abs(ltsample)', abs(ltsample)
     383!write(*,*)  'readclouds', readclouds, 'wetscav',wetscav, 'wetscav_dummy', wetscav_dummy
     384!write(*,*)  'S_i', S_i , 'Si_dummy', Si_dummy, 'prec(1)', prec(1)
     385
     386
     387!           write(*,*) 'PRECIPITATION ,cl  ECMWF , cl PARAMETIZED, clouds_v, lat' &
     388!                      ,prec(1)/3.6E6, cl, clouds_h*2E-7*prec(1)**0.36,clouds_v,ytra1(jpart)-90
     389
     390!endif
     391
    358392        endif ! positive in-cloud scavenging parameters given in Species file
    359393      endif !incloud
     394!END ZHG TEST
    360395     
    361396  !**************************************************
     
    368403        wetdeposit(ks)=xmass1(jpart,ks)* &
    369404             (1.-exp(-wetscav*abs(ltsample)))*grfraction(1)  ! wet deposition
     405!write(*,*) 'MASS DEPOSITED: PREC, WETSCAV, WETSCAVP', prec(1), wetdeposit(ks), xmass1(jpart,ks)* &
     406!             (1.-exp(-wetscav_dummy*abs(ltsample)))*grfraction(1), clouds_v
     407
     408
    370409      else ! if no scavenging
    371410        wetdeposit(ks)=0.
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG