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