Changeset 462f74b in flexpart.git for src/releaseparticles.f90


Ignore:
Timestamp:
Jul 12, 2016, 11:02:42 AM (8 years ago)
Author:
Sabine Eckhardt <sabine@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
842074e
Parents:
f28aa0a
Message:

first version of the backward scavenging

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/releaseparticles.f90

    r8a65cb0 r462f74b  
    5757  real :: xaux,yaux,zaux,rfraction
    5858  real :: topo,rhoaux(2),r,t,rhoout,ddx,ddy,rddx,rddy,p1,p2,p3,p4
     59  real :: rhosum(nspec)
    5960  real :: dz1,dz2,dz,xtn,ytn,xlonav,timecorrect(maxspec),press,pressold
    6061  real :: presspart,average_timecorrect
     
    8687  minpart=1
    8788  do i=1,numpoint
     89    do k=1,nspec
     90      rhosum(k)=0
     91    end do
    8892    if ((itime.ge.ireleasestart(i)).and. &! are we within release interval?
    8993         (itime.le.ireleaseend(i))) then
     
    176180  ! scaled. Adjust the mass per particle by the species-dependent time correction factor
    177181  ! divided by the species-average one
     182  ! for the scavenging calculation the mass needs to be multiplied with rho of the particle layer and
     183  ! divided by the sum of rho of all particles.
    178184  !*****************************************************************************
    179185            do k=1,nspec
    180186               xmass1(ipart,k)=xmass(i,k)/real(npart(i)) &
    181187                    *timecorrect(k)/average_timecorrect
    182   !            write (*,*) 'xmass1: ',xmass1(ipart,k),ipart,k
     188              if (SCAVDEP) then ! if there is no scavenging in wetdepo it will be set to 0
     189!              if ( henry(k).gt.0 .or. &
     190!                   crain_aero(k).gt.0. .or. csnow_aero(k).gt.0. .or. &
     191!                   ccn_aero(k).gt.0. .or. in_aero(k).gt.0. )  then
     192                xscav_frac1(ipart,k)=-1.
     193!               write(*,*) '190: ',xscav_frac1(ipart,k),k,ipart,rhosum(k),rhoout,i
     194!               xscav_frac1(ipart,k)=(-1.)/real(npart(i)) &
     195!                    *timecorrect(k)/average_timecorrect
     196!                  else
     197!                     xscav_frac1(ipart,k)=0
     198!                  endif   
     199               endif
    183200  ! Assign certain properties to particle
    184201  !**************************************
     
    372389              do k=1,nspec
    373390                xmass1(ipart,k)=xmass1(ipart,k)*rhoout
     391                if (SCAVDEP) then
     392                     xscav_frac1(ipart,k)=xscav_frac1(ipart,k)
     393!mctest                     xscav_frac1(ipart,k)=xscav_frac1(ipart,k)*rhoout
     394                     rhosum(k)=rhosum(k)+rhoout
     395!               write(*,*) '391: ',xscav_frac1(ipart,k),k,ipart,rhosum(k),rhoout,i
     396                endif
    374397              end do
    375398            endif
     
    379402            goto 34      ! Storage space has been found, stop searching
    380403          endif
    381         end do
     404        end do  ! i=1:numpoint
    382405        if (ipart.gt.maxpart) goto 996
    383406
    38440734      minpart=ipart+1
    385       end do
     408      end do ! ipart=minpart,maxpart
     409      if (SCAVDEP) then
     410         do ipart=minpart,maxpart
     411            do k=1,nspec
     412              if (xscav_frac1(ipart,k).lt.0) then
     413!mctest                   xscav_frac1(ipart,k)=xscav_frac1(ipart,k)/rhosum(k)
     414!                 write(*,*) '409: ',xscav_frac1(ipart,k),k,ipart,rhosum(k),rhoout,i
     415               endif   
     416            end do
     417         end do
    386418      endif
     419      endif ! j=1,numrel
    387420  end do
    388421
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG