source: flexpart.git/src/drydepokernel_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.5 KB
Line 
1subroutine drydepokernel_nest(nunc,deposit,x,y,nage,kp)
2  !                               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 drydepokernel.                      *
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
25  use unc_mod
26  use par_mod
27  use com_mod
28
29  implicit none
30
31  real(dep_prec), dimension(maxspec) :: deposit
32  real :: x,y,ddx,ddy,xl,yl,wx,wy,w
33  integer :: ix,jy,ixp,jyp,ks,kp,nunc,nage
34
35
36
37  xl=(x*dx+xoutshiftn)/dxoutn
38  yl=(y*dy+youtshiftn)/dyoutn
39  ix=int(xl)
40  jy=int(yl)
41  ddx=xl-real(ix)                   ! distance to left cell border
42  ddy=yl-real(jy)                   ! distance to lower cell border
43
44  if (ddx.gt.0.5) then
45    ixp=ix+1
46    wx=1.5-ddx
47  else
48    ixp=ix-1
49    wx=0.5+ddx
50  endif
51
52  if (ddy.gt.0.5) then
53    jyp=jy+1
54    wy=1.5-ddy
55  else
56    jyp=jy-1
57    wy=0.5+ddy
58  endif
59
60
61  ! Determine mass fractions for four grid points
62  !**********************************************
63    do ks=1,nspec
64
65  if (DRYDEPSPEC(ks).and.(abs(deposit(ks)).gt.0)) then
66
67  if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgridn-1).and. &
68       (jy.le.numygridn-1)) then
69    w=wx*wy
70      drygriduncn(ix,jy,ks,kp,nunc,nage)= &
71           drygriduncn(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
72  endif
73
74  if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgridn-1).and. &
75       (jyp.le.numygridn-1)) then
76    w=(1.-wx)*(1.-wy)
77      drygriduncn(ixp,jyp,ks,kp,nunc,nage)= &
78           drygriduncn(ixp,jyp,ks,kp,nunc,nage)+deposit(ks)*w
79  endif
80
81  if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgridn-1).and. &
82       (jy.le.numygridn-1)) then
83    w=(1.-wx)*wy
84      drygriduncn(ixp,jy,ks,kp,nunc,nage)= &
85           drygriduncn(ixp,jy,ks,kp,nunc,nage)+deposit(ks)*w
86  endif
87
88  if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgridn-1).and. &
89       (jyp.le.numygridn-1)) then
90    w=wx*(1.-wy)
91      drygriduncn(ix,jyp,ks,kp,nunc,nage)= &
92           drygriduncn(ix,jyp,ks,kp,nunc,nage)+deposit(ks)*w
93  endif
94
95  endif
96
97    end do
98end subroutine drydepokernel_nest
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG