source: flexpart.git/src/drydepokernel.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.9 KB
Line 
1subroutine drydepokernel(nunc,deposit,x,y,nage,kp)
2  !                          i      i    i i  i
3  !*****************************************************************************
4  !                                                                            *
5  !     Attribution of the deposition to the grid using a uniform kernel with  *
6  !     bandwidths dx and dy.                                                  *
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
27  use unc_mod
28  use par_mod
29  use com_mod
30
31  implicit none
32
33  real(dep_prec), dimension(maxspec) :: deposit
34  real :: x,y,ddx,ddy,xl,yl,wx,wy,w
35  integer :: ix,jy,ixp,jyp,ks,nunc,nage,kp
36
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 ((abs(deposit(ks)).gt.0).and.DRYDEPSPEC(ks)) then
67        if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
68             (jy.le.numygrid-1)) then
69          drygridunc(ix,jy,ks,kp,nunc,nage)= &
70               drygridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)
71        end if
72      end if
73    end do
74  else ! use kernel
75
76
77  ! Determine mass fractions for four grid points
78  !**********************************************
79  do ks=1,nspec
80
81   if ((abs(deposit(ks)).gt.0).and.DRYDEPSPEC(ks)) then
82
83      if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
84        (jy.le.numygrid-1)) then
85        w=wx*wy
86        drygridunc(ix,jy,ks,kp,nunc,nage)= &
87           drygridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
88     endif
89
90    if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgrid-1).and. &
91       (jyp.le.numygrid-1)) then
92    w=(1.-wx)*(1.-wy)
93      drygridunc(ixp,jyp,ks,kp,nunc,nage)= &
94           drygridunc(ixp,jyp,ks,kp,nunc,nage)+deposit(ks)*w
95    endif
96
97    if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgrid-1).and. &
98       (jy.le.numygrid-1)) then
99      w=(1.-wx)*wy
100      drygridunc(ixp,jy,ks,kp,nunc,nage)= &
101           drygridunc(ixp,jy,ks,kp,nunc,nage)+deposit(ks)*w
102    endif
103
104    if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgrid-1).and. &
105       (jyp.le.numygrid-1)) then
106      w=wx*(1.-wy)
107      drygridunc(ix,jyp,ks,kp,nunc,nage)= &
108           drygridunc(ix,jyp,ks,kp,nunc,nage)+deposit(ks)*w
109    endif
110
111    endif ! deposit>0
112  end do
113end if
114
115end subroutine drydepokernel
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG