source: flexpart.git/src/calcfluxes.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: 5.8 KB
Line 
1subroutine calcfluxes(nage,jpart,xold,yold,zold)
2  !                       i     i    i    i    i
3  !*****************************************************************************
4  !                                                                            *
5  !     Calculation of the gross fluxes across horizontal, eastward and        *
6  !     northward facing surfaces. The routine calculates the mass flux        *
7  !     due to the motion of only one particle. The fluxes of subsequent calls *
8  !     to this subroutine are accumulated until the next output is due.       *
9  !     Upon output, flux fields are re-set to zero in subroutine fluxoutput.f.*
10  !                                                                            *
11  !     Author: A. Stohl                                                       *
12  !                                                                            *
13  !     04 April 2000                                                          *
14  !                                                                            *
15  !*****************************************************************************
16  !                                                                            *
17  ! Variables:                                                                 *
18  !                                                                            *
19  ! nage                  Age class of the particle considered                 *
20  ! jpart                 Index of the particle considered                     *
21  ! xold,yold,zold        "Memorized" old positions of the particle            *
22  !                                                                            *
23  !*****************************************************************************
24
25  use flux_mod
26  use outg_mod
27  use par_mod
28  use com_mod
29
30  implicit none
31
32  integer :: jpart,nage,ixave,jyave,kz,kzave,kp
33  integer :: k,k1,k2,ix,ix1,ix2,ixs,jy,jy1,jy2
34  real :: xold,yold,zold,xmean,ymean
35
36
37  ! Determine average positions
38  !****************************
39
40  if ((ioutputforeachrelease.eq.1).and.(mdomainfill.eq.0)) then
41     kp=npoint(jpart)
42  else
43     kp=1
44  endif
45
46  xmean=(xold+xtra1(jpart))/2.
47  ymean=(yold+ytra1(jpart))/2.
48
49  ixave=int((xmean*dx+xoutshift)/dxout)
50  jyave=int((ymean*dy+youtshift)/dyout)
51  do kz=1,numzgrid                ! determine height of cell
52    if (outheight(kz).gt.ztra1(jpart)) goto 16
53  end do
5416   kzave=kz
55
56
57  ! Determine vertical fluxes
58  !**************************
59
60  if ((ixave.ge.0).and.(jyave.ge.0).and.(ixave.le.numxgrid-1).and. &
61       (jyave.le.numygrid-1)) then
62    do kz=1,numzgrid                ! determine height of cell
63      if (outheighthalf(kz).gt.zold) goto 11
64    end do
6511   k1=min(numzgrid,kz)
66    do kz=1,numzgrid                ! determine height of cell
67      if (outheighthalf(kz).gt.ztra1(jpart)) goto 21
68    end do
6921   k2=min(numzgrid,kz)
70
71    do k=1,nspec
72      do kz=k1,k2-1
73        flux(5,ixave,jyave,kz,k,kp,nage)= &
74             flux(5,ixave,jyave,kz,k,kp,nage)+ &
75             xmass1(jpart,k)
76      end do
77      do kz=k2,k1-1
78        flux(6,ixave,jyave,kz,k,kp,nage)= &
79             flux(6,ixave,jyave,kz,k,kp,nage)+ &
80             xmass1(jpart,k)
81      end do
82    end do
83  endif
84
85
86  ! Determine west-east fluxes (fluxw) and east-west fluxes (fluxe)
87  !****************************************************************
88
89  if ((kzave.le.numzgrid).and.(jyave.ge.0).and. &
90       (jyave.le.numygrid-1)) then
91
92  ! 1) Particle does not cross domain boundary
93
94    if (abs(xold-xtra1(jpart)).lt.real(nx)/2.) then
95      ix1=int((xold*dx+xoutshift)/dxout+0.5)
96      ix2=int((xtra1(jpart)*dx+xoutshift)/dxout+0.5)
97      do k=1,nspec
98        do ix=ix1,ix2-1
99          if ((ix.ge.0).and.(ix.le.numxgrid-1)) then
100            flux(1,ix,jyave,kzave,k,kp,nage)= &
101                 flux(1,ix,jyave,kzave,k,kp,nage) &
102                 +xmass1(jpart,k)
103          endif
104        end do
105        do ix=ix2,ix1-1
106          if ((ix.ge.0).and.(ix.le.numxgrid-1)) then
107            flux(2,ix,jyave,kzave,k,kp,nage)= &
108                 flux(2,ix,jyave,kzave,k,kp,nage) &
109                 +xmass1(jpart,k)
110          endif
111        end do
112      end do
113
114  ! 2) Particle crosses domain boundary: use cyclic boundary condition
115  !    and attribute flux to easternmost grid row only (approximation valid
116  !    for relatively slow motions compared to output grid cell size)
117
118    else
119      ixs=int(((real(nxmin1)-1.e5)*dx+xoutshift)/dxout)
120      if ((ixs.ge.0).and.(ixs.le.numxgrid-1)) then
121        if (xold.gt.xtra1(jpart)) then       ! west-east flux
122          do k=1,nspec
123            flux(1,ixs,jyave,kzave,k,kp,nage)= &
124                 flux(1,ixs,jyave,kzave,k,kp,nage) &
125                 +xmass1(jpart,k)
126          end do
127        else                                 ! east-west flux
128          do k=1,nspec
129            flux(2,ixs,jyave,kzave,k,kp,nage)= &
130                 flux(2,ixs,jyave,kzave,k,kp,nage) &
131                 +xmass1(jpart,k)
132          end do
133        endif
134      endif
135    endif
136  endif
137
138
139  ! Determine south-north fluxes (fluxs) and north-south fluxes (fluxn)
140  !********************************************************************
141
142  if ((kzave.le.numzgrid).and.(ixave.ge.0).and. &
143       (ixave.le.numxgrid-1)) then
144    jy1=int((yold*dy+youtshift)/dyout+0.5)
145    jy2=int((ytra1(jpart)*dy+youtshift)/dyout+0.5)
146
147    do k=1,nspec
148      do jy=jy1,jy2-1
149        if ((jy.ge.0).and.(jy.le.numygrid-1)) then
150          flux(3,ixave,jy,kzave,k,kp,nage)= &
151               flux(3,ixave,jy,kzave,k,kp,nage) &
152               +xmass1(jpart,k)
153        endif
154      end do
155      do jy=jy2,jy1-1
156        if ((jy.ge.0).and.(jy.le.numygrid-1)) then
157          flux(4,ixave,jy,kzave,k,kp,nage)= &
158               flux(4,ixave,jy,kzave,k,kp,nage) &
159               +xmass1(jpart,k)
160        endif
161      end do
162    end do
163  endif
164
165end subroutine calcfluxes
166
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG