source: flexpart.git/src/wetdepokernel.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: 3.8 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine wetdepokernel(nunc,deposit,x,y,nage,kp)
5  !                          i      i    i i  i
6  !*****************************************************************************
7  !                                                                            *
8  !     Attribution of the deposition from an individual particle to the       *
9  !     deposition fields using a uniform kernel with bandwidths dxout and dyout.*
10  !                                                                            *
11  !     Author: A. Stohl                                                       *
12  !                                                                            *
13  !     26 December 1996                                                       *
14  !                                                                            *
15  !*****************************************************************************
16  !                                                                            *
17  ! Variables:                                                                 *
18  !                                                                            *
19  ! nunc             uncertainty class of the respective particle              *
20  ! nage             age class of the respective particle                      *
21  ! deposit          amount (kg) to be deposited                               *
22  !                                                                            *
23  !*****************************************************************************
24  ! Changes:
25  ! eso 10/2016: Added option to disregard kernel
26  !
27  !*****************************************************************************
28
29  use unc_mod
30  use par_mod
31  use com_mod
32
33  implicit none
34
35  real :: x,y,deposit(maxspec),ddx,ddy,xl,yl,wx,wy,w
36  integer :: ix,jy,ixp,jyp,nunc,nage,ks,kp
37
38  xl=(x*dx+xoutshift)/dxout
39  yl=(y*dy+youtshift)/dyout
40  ix=int(xl)
41  jy=int(yl)
42  ddx=xl-real(ix)                   ! distance to left cell border
43  ddy=yl-real(jy)                   ! distance to lower cell border
44
45  if (ddx.gt.0.5) then
46    ixp=ix+1
47    wx=1.5-ddx
48  else
49    ixp=ix-1
50    wx=0.5+ddx
51  endif
52
53  if (ddy.gt.0.5) then
54    jyp=jy+1
55    wy=1.5-ddy
56  else
57    jyp=jy-1
58    wy=0.5+ddy
59  endif
60
61  ! If no kernel is used, direct attribution to grid cell
62  !******************************************************
63
64  if (.not.lusekerneloutput) then
65    do ks=1,nspec
66      if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
67           (jy.le.numygrid-1)) then
68        wetgridunc(ix,jy,ks,kp,nunc,nage)= &
69             wetgridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)
70      end if
71    end do
72  else ! use kernel
73   
74  ! Determine mass fractions for four grid points
75  !**********************************************
76
77  do ks=1,nspec
78
79    if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
80       (jy.le.numygrid-1)) then
81      w=wx*wy
82      wetgridunc(ix,jy,ks,kp,nunc,nage)= &
83           wetgridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
84    endif
85
86    if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgrid-1).and. &
87       (jyp.le.numygrid-1)) then
88      w=(1.-wx)*(1.-wy)
89      wetgridunc(ixp,jyp,ks,kp,nunc,nage)= &
90           wetgridunc(ixp,jyp,ks,kp,nunc,nage)+deposit(ks)*w
91    endif
92
93    if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgrid-1).and. &
94       (jy.le.numygrid-1)) then
95      w=(1.-wx)*wy
96      wetgridunc(ixp,jy,ks,kp,nunc,nage)= &
97           wetgridunc(ixp,jy,ks,kp,nunc,nage)+deposit(ks)*w
98    endif
99
100    if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgrid-1).and. &
101       (jyp.le.numygrid-1)) then
102      w=wx*(1.-wy)
103      wetgridunc(ix,jyp,ks,kp,nunc,nage)= &
104           wetgridunc(ix,jyp,ks,kp,nunc,nage)+deposit(ks)*w
105    endif
106
107  end do
108  end if
109
110end subroutine wetdepokernel
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG