source: flexpart.git/src/drydepokernel.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.0 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine drydepokernel(nunc,deposit,x,y,nage,kp)
5  !                          i      i    i i  i
6  !*****************************************************************************
7  !                                                                            *
8  !     Attribution of the deposition to the grid using a uniform kernel with  *
9  !     bandwidths dx and dy.                                                  *
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
30  use unc_mod
31  use par_mod
32  use com_mod
33
34  implicit none
35
36  real(dep_prec), dimension(maxspec) :: deposit
37  real :: x,y,ddx,ddy,xl,yl,wx,wy,w
38  integer :: ix,jy,ixp,jyp,ks,nunc,nage,kp
39
40
41  xl=(x*dx+xoutshift)/dxout
42  yl=(y*dy+youtshift)/dyout
43  ix=int(xl)
44  jy=int(yl)
45  ddx=xl-real(ix)                   ! distance to left cell border
46  ddy=yl-real(jy)                   ! distance to lower cell border
47
48  if (ddx.gt.0.5) then
49    ixp=ix+1
50    wx=1.5-ddx
51  else
52    ixp=ix-1
53    wx=0.5+ddx
54  endif
55
56  if (ddy.gt.0.5) then
57    jyp=jy+1
58    wy=1.5-ddy
59  else
60    jyp=jy-1
61    wy=0.5+ddy
62  endif
63
64  ! If no kernel is used, direct attribution to grid cell
65  !******************************************************
66
67  if (.not.lusekerneloutput) then
68    do ks=1,nspec
69      if ((abs(deposit(ks)).gt.0).and.DRYDEPSPEC(ks)) then
70        if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
71             (jy.le.numygrid-1)) then
72          drygridunc(ix,jy,ks,kp,nunc,nage)= &
73               drygridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)
74        end if
75      end if
76    end do
77  else ! use kernel
78
79
80  ! Determine mass fractions for four grid points
81  !**********************************************
82  do ks=1,nspec
83
84   if ((abs(deposit(ks)).gt.0).and.DRYDEPSPEC(ks)) then
85
86      if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
87        (jy.le.numygrid-1)) then
88        w=wx*wy
89        drygridunc(ix,jy,ks,kp,nunc,nage)= &
90           drygridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
91     endif
92
93    if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgrid-1).and. &
94       (jyp.le.numygrid-1)) then
95    w=(1.-wx)*(1.-wy)
96      drygridunc(ixp,jyp,ks,kp,nunc,nage)= &
97           drygridunc(ixp,jyp,ks,kp,nunc,nage)+deposit(ks)*w
98    endif
99
100    if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgrid-1).and. &
101       (jy.le.numygrid-1)) then
102      w=(1.-wx)*wy
103      drygridunc(ixp,jy,ks,kp,nunc,nage)= &
104           drygridunc(ixp,jy,ks,kp,nunc,nage)+deposit(ks)*w
105    endif
106
107    if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgrid-1).and. &
108       (jyp.le.numygrid-1)) then
109      w=wx*(1.-wy)
110      drygridunc(ix,jyp,ks,kp,nunc,nage)= &
111           drygridunc(ix,jyp,ks,kp,nunc,nage)+deposit(ks)*w
112    endif
113
114    endif ! deposit>0
115  end do
116end if
117
118end subroutine drydepokernel
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG