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


Ignore:
Timestamp:
Oct 12, 2016, 1:14:19 PM (8 years ago)
Author:
Sabine <sabine.eckhardt@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
df4a68e
Parents:
0581cac
Message:

first working version with backward deposition

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/wetdepo.f90

    r54cbd6c r5844866  
    2020!**********************************************************************
    2121
    22 subroutine wetdepo(itime,ltsample,loutnext,forreceptor)
    23 !                  i      i        i            i
     22subroutine wetdepo(itime,ltsample,loutnext)
     23!                  i      i        i
    2424!*****************************************************************************
    2525!                                                                            *
     
    3030! This fraction is parameterized from total cloud cover and rates of large   *
    3131! scale and convective precipitation.                                        *
    32 ! SEC: if forrecptor is true then the wetdeposition fraction is only applied *
    33 ! on the xscav_frac and not on the xmass                                     *
    3432!                                                                            *
    3533!    Author: A. Stohl                                                        *
     
    9492  integer :: blc_count, inc_count
    9593  real    :: Si_dummy, wetscav_dummy
    96   logical :: readclouds_this_nest,forreceptor
     94  logical :: readclouds_this_nest
    9795
    9896
     
    174172           memtime(1),memtime(2),interp_time,lsp,convp,cc)
    175173    endif
     174
     175!  If total precipitation is less than 0.01 mm/h - no scavenging occurs
     176!  sec this is just valid if release is over a point
     177    if ((lsp.lt.0.01).and.(convp.lt.0.01)) then
     178          if (WETBKDEP) then
     179             do ks=1,nspec
     180                if (xscav_frac1(jpart,ks).lt.0) then ! first timestep no scavenging
     181                   xmass1(jpart,ks)=0.
     182                   xscav_frac1(jpart,ks)=0.
     183!                  write (*,*) 'paricle removed - no scavenging: ',jpart,ks
     184                endif
     185             end do
     186          endif
     187          goto 20
     188    endif
     189
    176190
    177191! get the level were the actual particle is in
     
    399413        kp=1
    400414      endif
    401       if (forreceptor .eqv. .false.) then
    402          if (restmass .gt. smallnum) then
    403            xmass1(jpart,ks)=restmass
     415      if (restmass .gt. smallnum) then
     416        xmass1(jpart,ks)=restmass
    404417!   depostatistic
    405418!   wetdepo_sum(ks,kp)=wetdepo_sum(ks,kp)+wetdeposit(ks)
    406419!   depostatistic
    407          else
    408            xmass1(jpart,ks)=0.
    409         endif
    410      else ! for the backward deposition calculation
    411          if (wetdeposit(ks).gt.0) then ! deposition occured
    412                 xscav_frac1(jpart,ks)=xscav_frac1(jpart,ks)*(-1.)* &
    413                    wetdeposit(ks)/xmass1(jpart,ks)
    414 !                write (*,*) 'paricle kept: ',jpart,ks,wetdeposit(ks),xscav_frac1(jpart,ks)
    415          else
    416                 xmass1(jpart,ks)=0.
    417                 xscav_frac1(jpart,ks)=0.
    418          endif
    419      endif
     420      else
     421        xmass1(jpart,ks)=0.
     422      endif
    420423!   Correct deposited mass to the last time step when radioactive decay of
    421424!   gridded deposited mass was calculated
     
    423426        wetdeposit(ks)=wetdeposit(ks)*exp(abs(ldeltat)*decay(ks))
    424427      endif
     428
     429      if (WETBKDEP) then
     430! the calculation of the scavenged mass shall only be done once after release
     431! xscav_frac1 was initialised with a negative value
     432          if (xscav_frac1(jpart,ks).lt.0) then
     433             if (wetdeposit(ks).eq.0) then
     434! terminate particle
     435                xmass1(jpart,ks)=0.
     436                xscav_frac1(jpart,ks)=0.
     437             else
     438                xscav_frac1(jpart,ks)=xscav_frac1(jpart,ks)*(-1.)* &
     439                   wetdeposit(ks)/xmass1(jpart,ks)
     440!                write (*,*) 'paricle kept: ',jpart,ks,wetdeposit(ks),xscav_frac1(jpart,ks)
     441             endif
     442          endif
     443      endif
     444
    425445
    426446    end do !all species
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG