source: flexpart.git/src/getvdep.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 getvdep(n,ix,jy,ust,temp,pa,L,gr,rh,rr,snow,vdepo)
5  !                   i i  i   i   i   i  i i  i  i    i o
6  !*****************************************************************************
7  !                                                                            *
8  !  This routine calculates the dry deposition velocities.                    *
9  !                                                                            *
10  !     Author: A. Stohl                                                       *
11  !                                                                            *
12  !     20 December 1996                                                       *
13  !     Sabine Eckhardt, Jan 07                                                *
14  !     if the latitude is negative: add half a year to the julian day         *
15  !                                                                            *
16  !*****************************************************************************
17  !                                                                            *
18  ! Variables:                                                                 *
19  ! gr [W/m2]         global radiation                                         *
20  ! L [m]             Obukhov length                                           *
21  ! nyl               kinematic viscosity                                      *
22  ! pa [Pa]           surface air pressure                                     *
23  ! ra [s/m]          aerodynamic resistance                                   *
24  ! raquer [s/m]      average aerodynamic resistance                           *
25  ! rh [0-1]          relative humidity                                        *
26  ! rhoa              density of the air                                       *
27  ! rr [mm/h]         precipitation rate                                       *
28  ! temp [K]          2m temperature                                           *
29  ! tc [C]            2m temperature                                           *
30  ! ust [m/s]         friction velocity                                        *
31  ! snow [m of water equivalent] snow depth                                    *
32  ! xlanduse          fractions of numclasS landuses for each model grid point *
33  !                                                                            *
34  !*****************************************************************************
35
36  use par_mod
37  use com_mod
38
39  implicit none
40
41  integer :: yyyymmdd,hhmmss,yyyy,mmdd,n,lseason,i,j,ix,jy
42  real :: vdepo(maxspec),vd,rb(maxspec),rc(maxspec),raquer,ylat
43  real :: raerod,ra,ust,temp,tc,pa,L,gr,rh,rr,myl,nyl,rhoa,diffh2o,snow
44  real :: slanduse(numclass)
45  real,parameter :: eps=1.e-5
46  real(kind=dp) :: jul
47
48  ! Calculate month and determine the seasonal category
49  !****************************************************
50
51  jul=bdate+real(wftime(n),kind=dp)/86400._dp
52
53  ylat=jy*dy+ylat0
54  if (ylat.lt.0) then
55      jul=jul+365/2
56  endif
57
58
59  call caldate(jul,yyyymmdd,hhmmss)
60  yyyy=yyyymmdd/10000
61  mmdd=yyyymmdd-10000*yyyy
62
63  if ((ylat.gt.-20).and.(ylat.lt.20)) then
64     mmdd=600 ! summer
65  endif
66
67  if ((mmdd.ge.1201).or.(mmdd.le.301)) then
68    lseason=4
69  else if ((mmdd.ge.1101).or.(mmdd.le.331)) then
70    lseason=3
71  else if ((mmdd.ge.401).and.(mmdd.le.515)) then
72    lseason=5
73  else if ((mmdd.ge.516).and.(mmdd.le.915)) then
74    lseason=1
75  else
76    lseason=2
77  endif
78
79  ! Calculate diffusivity of water vapor
80  !************************************
81  diffh2o=2.11e-5*(temp/273.15)**1.94*(101325/pa)
82
83  ! Conversion of temperature from K to C
84  !**************************************
85
86  tc=temp-273.15
87
88  ! Calculate dynamic viscosity
89  !****************************
90
91  if (tc.lt.0) then
92    myl=(1.718+0.0049*tc-1.2e-05*tc**2)*1.e-05
93  else
94    myl=(1.718+0.0049*tc)*1.e-05
95  endif
96
97  ! Calculate kinematic viscosity
98  !******************************
99
100  rhoa=pa/(287.*temp)
101  nyl=myl/rhoa
102
103
104  ! 0. Set all deposition velocities zero
105  !**************************************
106
107  do i=1,nspec
108    vdepo(i)=0.
109  end do
110
111
112  ! 1. Compute surface layer resistances rb
113  !****************************************
114
115  call getrb(nspec,ust,nyl,diffh2o,reldiff,rb)
116
117  ! change for snow
118  do j=1,numclass
119    if (snow.gt.0.001) then ! 10 mm
120       if (j.eq.12) then
121         slanduse(j)=1.
122       else
123         slanduse(j)=0.
124       endif
125    else
126       slanduse(j)=xlanduse(ix,jy,j)
127    endif
128  end do
129
130  raquer=0.
131  do j=1,numclass            ! loop over all landuse classes
132
133    if (slanduse(j).gt.eps)  then
134
135  ! 2. Calculate aerodynamic resistance ra
136  !***************************************
137
138      ra=raerod(L,ust,z0(j))
139      raquer=raquer+ra*slanduse(j)
140
141  ! 3. Calculate surface resistance for gases
142  !******************************************
143
144      call getrc(nspec,lseason,j,tc,gr,rh,rr,rc)
145
146  ! 4. Calculate deposition velocities for gases and ...
147  ! 5. ... sum deposition velocities for all landuse classes
148  !*********************************************************
149
150      do i=1,nspec
151        if (reldiff(i).gt.0.) then
152          if ((ra+rb(i)+rc(i)).gt.0.) then
153            vd=1./(ra+rb(i)+rc(i))
154          else
155            vd=9.999
156          endif
157          vdepo(i)=vdepo(i)+vd*slanduse(j)
158        endif
159      end do
160    endif
161  end do
162
163
164  ! 6. Calculate deposition velocities for particles
165  !*************************************************
166
167  call partdep(nspec,density,fract,schmi,vset,raquer,ust,nyl,vdepo)
168
169  !if (debug_mode) then
170  !  print*,'getvdep:188: vdepo=', vdepo
171    !stop
172  !endif
173
174  ! 7. If no detailed parameterization available, take constant deposition
175  !    velocity if that is available
176  !***********************************************************************
177
178  do i=1,nspec
179    if ((reldiff(i).lt.0.).and.(density(i).lt.0.).and. &
180         (dryvel(i).gt.0.)) then
181      vdepo(i)=dryvel(i)
182    endif
183  end do
184
185
186end subroutine getvdep
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG