source: flexpart.git/src/get_vdep_prob.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: 4.1 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine get_vdep_prob(itime,xt,yt,zt,prob)
5  !                    i     i  i  i  o
6  !*****************************************************************************
7  !                                                                            *
8  !  Calculation of the probability for dyr deposition                         *
9  !                                                                            *
10  !  Particle positions are read in - prob returned                            *
11  !                                                                            *
12  !*****************************************************************************
13  !                                                                            *
14  ! Variables:                                                                 *
15  ! itime [s]          time at which this subroutine is entered                *
16  ! itimec [s]         actual time, which is incremented in this subroutine    *
17  ! href [m]           height for which dry deposition velocity is calculated  *
18  ! ldirect            1 forward, -1 backward                                  *
19  ! ldt [s]            Time step for the next integration                      *
20  ! lsynctime [s]      Synchronisation interval of FLEXPART                    *
21  ! ngrid              index which grid is to be used                          *
22  ! prob               probability of absorption due to dry deposition         *
23  ! vdepo              Deposition velocities for all species                   *
24  ! xt,yt,zt           Particle position                                       *
25  !                                                                            *
26  !*****************************************************************************
27
28  use point_mod
29  use par_mod
30  use com_mod
31  use interpol_mod
32
33  implicit none
34
35  real(kind=dp) :: xt,yt
36  real :: zt,xtn,ytn
37  integer :: itime,i,j,k,memindnext
38  integer :: nix,njy,ks
39  real :: prob(maxspec),vdepo(maxspec)
40  real,parameter :: eps=nxmax/3.e5
41
42  if (DRYDEP) then    ! reset probability for deposition
43    do ks=1,nspec
44      depoindicator(ks)=.true.
45      prob(ks)=0.
46    end do
47  endif
48
49
50  ! Determine whether lat/long grid or polarstereographic projection
51  ! is to be used
52  ! Furthermore, determine which nesting level to be used
53  !*****************************************************************
54
55  if (nglobal.and.(yt.gt.switchnorthg)) then
56    ngrid=-1
57  else if (sglobal.and.(yt.lt.switchsouthg)) then
58    ngrid=-2
59  else
60    ngrid=0
61    do j=numbnests,1,-1
62      if ((xt.gt.xln(j)+eps).and.(xt.lt.xrn(j)-eps).and. &
63           (yt.gt.yln(j)+eps).and.(yt.lt.yrn(j)-eps)) then
64        ngrid=j
65        goto 23
66      endif
67    end do
6823   continue
69  endif
70
71
72  !***************************
73  ! Interpolate necessary data
74  !***************************
75
76  if (abs(itime-memtime(1)).lt.abs(itime-memtime(2))) then
77    memindnext=1
78  else
79    memindnext=2
80  endif
81
82  ! Determine nested grid coordinates
83  !**********************************
84
85  if (ngrid.gt.0) then
86    xtn=(xt-xln(ngrid))*xresoln(ngrid)
87    ytn=(yt-yln(ngrid))*yresoln(ngrid)
88    ix=int(xtn)
89    jy=int(ytn)
90    nix=nint(xtn)
91    njy=nint(ytn)
92  else
93    ix=int(xt)
94    jy=int(yt)
95    nix=nint(xt)
96    njy=nint(yt)
97  endif
98  ixp=ix+1
99  jyp=jy+1
100
101
102  ! Determine probability of deposition
103  !************************************
104
105      if ((DRYDEP).and.(zt.lt.2.*href)) then
106        do ks=1,nspec
107          if (DRYDEPSPEC(ks)) then
108            if (depoindicator(ks)) then
109              if (ngrid.le.0) then
110                call interpol_vdep(ks,vdepo(ks))
111              else
112                call interpol_vdep_nests(ks,vdepo(ks))
113              endif
114            endif
115  ! correction by Petra Seibert, 10 April 2001
116  !   this formulation means that prob(n) = 1 - f(0)*...*f(n)
117  !   where f(n) is the exponential term
118               prob(ks)=vdepo(ks)
119!               prob(ks)=vdepo(ks)/2./href
120! instead of prob - return vdepo -> result kg/m2/s
121          endif
122        end do
123      endif
124
125
126end subroutine get_vdep_prob
127
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG