source: flexpart.git/src/partdep.f90 @ 332fbbd

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file since 332fbbd was 332fbbd, checked in by Ignacio Pisso <ip@…>, 4 years ago

Revert "move license from headers to a different file"
Adding the full GPL license it was apparent that the FSF recommends to
have the statements as file headers

This reverts commit 3481cc180a6b19f71d9d2d04240a91d23f0a2800.

  • Property mode set to 100644
File size: 6.7 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine partdep(nc,density,fract,schmi,vset,ra,ustar,nyl,vdep)
23  !                   i     i      i     i    i   i    i    i  i/o
24  !*****************************************************************************
25  !                                                                            *
26  !      Calculation of the dry deposition velocities of particles.            *
27  !      This routine is based on Stokes' law for considering settling and     *
28  !      assumes constant dynamic viscosity of the air.                        *
29  !                                                                            *
30  !     AUTHOR: Andreas Stohl, 12 November 1993                                *
31  !                            Update: 20 December 1996                        *
32  !                                                                            *
33  !     Literature:                                                            *
34  !     [1]  Hicks/Baldocchi/Meyers/Hosker/Matt (1987), A Preliminary          *
35  !             Multiple Resistance Routine for Deriving Dry Deposition        *
36  !             Velocities from Measured Quantities.                           *
37  !             Water, Air and Soil Pollution 36 (1987), pp.311-330.           *
38  !     [2]  Slinn (1982), Predictions for Particle Deposition to              *
39  !             Vegetative Canopies. Atm.Env.16-7 (1982), pp.1785-1794.        *
40  !     [3]  Slinn/Slinn (1980),  Predictions for Particle Deposition on       *
41  !             Natural Waters. Atm.Env.14 (1980), pp.1013-1016.               *
42  !     [4]  Scire/Yamartino/Carmichael/Chang (1989),                          *
43  !             CALGRID: A Mesoscale Photochemical Grid Model.                 *
44  !             Vol II: User's Guide. (Report No.A049-1, June, 1989)           *
45  !     [5]  Langer M. (1992): Ein einfaches Modell zur Abschaetzung der       *
46  !             Depositionsgeschwindigkeit von Teilchen und Gasen.             *
47  !             Internal report.                                               *
48  !                                                                            *
49  !*****************************************************************************
50  !                                                                            *
51  ! Variables:                                                                 *
52  ! alpha                help variable                                         *
53  ! fract(nc,ni)         mass fraction of each diameter interval               *
54  ! lpdep(nc)            1 for particle deposition, 0 else                     *
55  ! nc                   actual number of chemical components                  *
56  ! ni                   number of diameter intervals, for which vdepj is calc.*
57  ! rdp [s/m]            deposition layer resistance                           *
58  ! ra [s/m]             aerodynamical resistance                              *
59  ! schmi(nc,ni)         Schmidt number**2/3 of each diameter interval         *
60  ! stokes               Stokes number                                         *
61  ! ustar [m/s]          friction velocity                                     *
62  ! vdep(nc) [m/s]       deposition velocities of all components               *
63  ! vdepj [m/s]          help, deposition velocity of 1 interval               *
64  ! vset(nc,ni)          gravitational settling velocity of each interval      *
65  !                                                                            *
66  ! Constants:                                                                 *
67  ! nc                   number of chemical species                            *
68  ! ni                   number of diameter intervals, for which deposition    *
69  !                      is calculated                                         *
70  !                                                                            *
71  !*****************************************************************************
72
73  use par_mod
74  use com_mod, only: debug_mode
75
76  implicit none
77
78  real :: density(maxspec),schmi(maxspec,ni),fract(maxspec,ni)
79  real :: vset(maxspec,ni)
80  real :: vdep(maxspec),stokes,vdepj,rdp,ustar,alpha,ra,nyl
81  real,parameter :: eps=1.e-5
82  integer :: ic,j,nc
83
84
85  do ic=1,nc                  ! loop over all species
86    if (density(ic).gt.0.) then
87      do j=1,ni              ! loop over all diameter intervals
88        if (ustar.gt.eps) then
89
90  ! Stokes number for each diameter interval
91  !*****************************************
92
93          stokes=vset(ic,j)/ga*ustar*ustar/nyl
94          alpha=-3./stokes
95
96  ! Deposition layer resistance
97  !****************************
98
99          if (alpha.le.log10(eps)) then
100            rdp=1./(schmi(ic,j)*ustar)
101          else
102            rdp=1./((schmi(ic,j)+10.**alpha)*ustar)
103          endif
104          vdepj=vset(ic,j)+1./(ra+rdp+ra*rdp*vset(ic,j))
105        else
106          vdepj=vset(ic,j)
107        endif
108
109  ! deposition velocities of each interval are weighted with mass fraction
110  !***********************************************************************
111
112        vdep(ic)=vdep(ic)+vdepj*fract(ic,j)
113       
114        !print*, 'partdep:113: ic', ic, 'vdep', vdep
115        !stop
116      end do
117    endif
118
119
120  end do
121
122  !if (debug_mode) then
123  !  print*, 'partdep:122:'
124  !  write(*,*) (vdep(ic), ic=1,nc)
125    !stop
126  !endif
127
128end subroutine partdep
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG