source: flexpart.git/src/get_vdep_prob.f90 @ 3481cc1

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

move license from headers to a different file

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