source: flexpart.git/src/wetdepokernel_nest.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: 3.8 KB
Line 
1subroutine wetdepokernel_nest(nunc,deposit,x,y,nage,kp)
2  !                           i    i       i i i    i
3  !*****************************************************************************
4  !                                                                            *
5  !     Attribution of the deposition from an individual particle to the       *
6  !     nested deposition fields using a uniform kernel with bandwidths        *
7  !     dxoutn and dyoutn.                                                     *
8  !                                                                            *
9  !     Author: A. Stohl                                                       *
10  !                                                                            *
11  !     26 December 1996                                                       *
12  !                                                                            *
13  !      2 September 2004: Adaptation from wetdepokernel.                      *
14  !                                                                            *
15  !                                                                            *
16  !*****************************************************************************
17  !                                                                            *
18  ! Variables:                                                                 *
19  !                                                                            *
20  ! nunc             uncertainty class of the respective particle              *
21  ! nage             age class of the respective particle                      *
22  ! deposit          amount (kg) to be deposited                               *
23  !                                                                            *
24  !*****************************************************************************
25
26  use unc_mod
27  use par_mod
28  use com_mod
29
30  implicit none
31
32  real :: x,y,deposit(maxspec),ddx,ddy,xl,yl,wx,wy,w
33  integer :: ix,jy,ixp,jyp,ks,kp,nunc,nage
34
35  xl=(x*dx+xoutshiftn)/dxoutn
36  yl=(y*dy+youtshiftn)/dyoutn
37
38  ! old:
39  ! ix=int(xl)
40  ! jy=int(yl)
41
42  ! ESO: for xl,yl in range <-.5,-1> we get ix,jy=0 and thus negative
43  ! wx,wy as the int function rounds upwards for negative numbers.
44  ! Either use the floor function, or (perhaps more correctly?) use "(xl.gt.-0.5)"
45  ! in place of "(ix.ge.0)" and similar for the upper boundary.
46
47  ! new:
48  ix=floor(xl)
49  jy=floor(yl)
50
51  ddx=xl-real(ix)                   ! distance to left cell border
52  ddy=yl-real(jy)                   ! distance to lower cell border
53
54
55  if (ddx.gt.0.5) then
56    ixp=ix+1
57    wx=1.5-ddx
58  else
59    ixp=ix-1
60    wx=0.5+ddx
61  endif
62
63  if (ddy.gt.0.5) then
64    jyp=jy+1
65    wy=1.5-ddy
66  else
67    jyp=jy-1
68    wy=0.5+ddy
69  endif
70
71! Determine mass fractions for four grid points
72!**********************************************
73
74  do ks=1,nspec
75    if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgridn-1).and. &
76         (jy.le.numygridn-1)) then
77      w=wx*wy
78      wetgriduncn(ix,jy,ks,kp,nunc,nage)= &
79           wetgriduncn(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
80    endif
81
82    if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgridn-1).and. &
83         (jyp.le.numygridn-1)) then
84      w=(1.-wx)*(1.-wy)
85      wetgriduncn(ixp,jyp,ks,kp,nunc,nage)= &
86           wetgriduncn(ixp,jyp,ks,kp,nunc,nage)+deposit(ks)*w
87    endif
88
89    if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgridn-1).and. &
90         (jy.le.numygridn-1)) then
91      w=(1.-wx)*wy
92      wetgriduncn(ixp,jy,ks,kp,nunc,nage)= &
93           wetgriduncn(ixp,jy,ks,kp,nunc,nage)+deposit(ks)*w
94    endif
95
96    if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgridn-1).and. &
97         (jyp.le.numygridn-1)) then
98      w=wx*(1.-wy)
99      wetgriduncn(ix,jyp,ks,kp,nunc,nage)= &
100           wetgriduncn(ix,jyp,ks,kp,nunc,nage)+deposit(ks)*w
101    endif
102
103  end do
104end subroutine wetdepokernel_nest
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG