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