source: flexpart.git/src/part0.f90

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

add SPDX-License-Identifier to all .f90 files

  • Property mode set to 100644
File size: 5.9 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine part0(dquer,dsigma,density,fract,schmi,cun,vsh)
5  !                  i      i       i      o     o    o   o
6  !*****************************************************************************
7  !                                                                            *
8  !      Calculation of time independent factors of the dry deposition of      *
9  !      particles:                                                            *
10  !      Log-Normal-distribution of mass [dM/dlog(dp)], unimodal               *
11  !                                                                            *
12  !      AUTHOR: Matthias Langer, adapted by Andreas Stohl, 13 November 1993   *
13  !                                                                            *
14  !      Literature:                                                           *
15  !      [1]  Scire/Yamartino/Carmichael/Chang (1989),                         *
16  !             CALGRID: A Mesoscale Photochemical Grid Model.                 *
17  !             Vol II: User's Guide. (Report No.A049-1, June, 1989)           *
18  !                                                                            *
19  !*****************************************************************************
20  !                                                                            *
21  ! Variables:                                                                 *
22  ! alpha            help variable                                             *
23  ! cun              'slip-flow' correction after Cunningham                   *
24  ! d01 [um]         upper diameter                                            *
25  ! d02 [um]         lower diameter                                            *
26  ! dc [m2/s]        coefficient of Brownian diffusion                         *
27  ! delta            distance given in standard deviation units                *
28  ! density [kg/m3]  density of the particle                                   *
29  ! dmean            geometric mean diameter of interval                       *
30  ! dquer [um]       geometric mass mean particle diameter                     *
31  ! dsigma           e.g. dsigma=10 or dsigma=0.1 means that 68% of the mass   *
32  !                  are between 0.1*dquer and 10*dquer                        *
33  ! fract(ni)        mass fraction of each diameter interval                   *
34  ! kn               Knudsen number                                            *
35  ! ni               number of diameter intervals, for which deposition        *
36  !                  is calculated                                             *
37  ! schmidt          Schmidt number                                            *
38  ! schmi            schmidt**2/3                                              *
39  ! vsh [m/s]        gravitational settling velocity of the particle           *
40  ! x01              normalized upper diameter                                 *
41  ! x02              normalized lower diameter                                 *
42  !                                                                            *
43  ! Constants:                                                                 *
44  ! g [m/s2]         Acceleration of gravity                                   *
45  ! kb [J/K]         Stefan-Boltzmann constant                                 *
46  ! lam [m]          mean free path of air molecules                           *
47  ! myl [kg/m/s]     dynamical viscosity of air                                *
48  ! nyl [m2/s]       kinematic viscosity of air                                *
49  ! tr               reference temperature                                     *
50  !                                                                            *
51  ! Function:                                                                  *
52  ! erf              calculates the integral of the Gauss function             *
53  !                                                                            *
54  !*****************************************************************************
55
56  use par_mod
57
58  implicit none
59
60  real,parameter :: tr=293.15
61
62  integer :: i
63  real :: dquer,dsigma,density,xdummy,d01,d02,delta,x01,x02,fract(ni)
64  real :: dmean,alpha,cun,dc,schmidt,schmi(ni),vsh(ni),kn,erf
65  real,parameter :: myl=1.81e-5,nyl=0.15e-4
66  real,parameter :: lam=6.53e-8,kb=1.38e-23,eps=1.2e-38
67
68
69  ! xdummy constant for all intervals
70  !**********************************
71
72  xdummy=sqrt(2.)*alog(dsigma)
73
74
75  ! particles diameters are split up to ni intervals between
76  ! dquer-3*dsigma and dquer+3*dsigma
77  !*********************************************************
78
79  delta=6./real(ni)
80
81  d01=dquer*dsigma**(-3)
82  do i=1,ni
83    d02=d01
84    d01=dquer*dsigma**(-3.+delta*real(i))
85    x01=alog(d01/dquer)/xdummy
86    x02=alog(d02/dquer)/xdummy
87    !print*,'part0:: d02=' , d02 , 'd01=', d01
88
89  ! Area under Gauss-function is calculated and gives mass fraction of interval
90  !****************************************************************************
91
92    fract(i)=0.5*(erf(x01)-erf(x02))
93    !print*,'part0:: fract(',i,')', fract(i)
94    !print*,'part0:: fract', fract(i), x01, x02, erf(x01), erf(x02)
95
96  ! Geometric mean diameter of interval in [m]
97  !*******************************************
98
99    dmean=1.E-6*exp(0.5*alog(d01*d02))
100    !print*,'part0:: dmean=', dmean
101
102  ! Calculation of time independent parameters of each interval
103  !************************************************************
104
105    kn=2.*lam/dmean
106    if ((-1.1/kn).le.log10(eps)*log(10.)) then
107      alpha=1.257
108    else
109      alpha=1.257+0.4*exp(-1.1/kn)
110    endif
111    cun=1.+alpha*kn
112    dc=kb*tr*cun/(3.*pi*myl*dmean)
113    schmidt=nyl/dc
114    schmi(i)=schmidt**(-2./3.)
115    vsh(i)=ga*density*dmean*dmean*cun/(18.*myl)
116
117    !print*,'part0:: vsh(',i,')', vsh(i)
118
119  end do
120
121  !stop 'part0'
122
123end subroutine part0
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG