source: flexpart.git/src/plumetraj.f90 @ 16b61a5

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since 16b61a5 was 6a678e3, checked in by Espen Sollum ATMOS <eso@…>, 8 years ago

Added option to use double precision for calculating the deposition fields

  • Property mode set to 100644
File size: 8.8 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine plumetraj(itime)
23  !                       i
24  !*****************************************************************************
25  !                                                                            *
26  ! Determines a plume centroid trajectory for each release site, and manages  *
27  ! clustering of particle locations. Certain parameters (average PV,          *
28  ! tropopause height, etc., are provided along the plume trajectories.        *
29  ! At the end, output is written to file 'trajectories.txt'.                  *
30  !                                                                            *
31  !     Author: A. Stohl                                                       *
32  !                                                                            *
33  !     24 January 2002                                                        *
34  !                                                                            *
35  ! Variables:                                                                 *
36  ! fclust          fraction of particles belonging to each cluster            *
37  ! hmixcenter      mean mixing height for all particles                       *
38  ! ncluster        number of clusters to be used                              *
39  ! pvcenter        mean PV for all particles                                  *
40  ! pvfract         fraction of particles with PV<2pvu                         *
41  ! rms             total horizontal rms distance after clustering             *
42  ! rmsdist         total horizontal rms distance before clustering            *
43  ! rmsclust        horizontal rms distance for each individual cluster        *
44  ! topocenter      mean topography underlying all particles                   *
45  ! tropocenter     mean tropopause height at the positions of particles       *
46  ! tropofract      fraction of particles within the troposphere               *
47  ! zrms            total vertical rms distance after clustering               *
48  ! zrmsdist        total vertical rms distance before clustering              *
49  ! xclust,yclust,  Cluster centroid positions                                 *
50  ! zclust                                                                     *
51  !                                                                            *
52  !*****************************************************************************
53
54  use point_mod
55  use par_mod
56  use com_mod
57  use mean_mod
58
59  implicit none
60
61  integer :: itime,ix,jy,ixp,jyp,indexh,i,j,k,m,n,il,ind,indz,indzp
62  real :: xl(maxpart),yl(maxpart),zl(maxpart)
63  real :: xcenter,ycenter,zcenter,dist,distance,rmsdist,zrmsdist
64
65  real :: xclust(ncluster),yclust(ncluster),zclust(ncluster)
66  real :: fclust(ncluster),rms,rmsclust(ncluster),zrms
67
68  real :: dt1,dt2,dtt,ddx,ddy,rddx,rddy,p1,p2,p3,p4,dz1,dz2,dz
69  real :: topo,topocenter,hm(2),hmixi,hmixfract,hmixcenter
70  real :: pv1(2),pvprof(2),pvi,pvcenter,pvfract,tr(2),tri,tropofract
71  real :: tropocenter
72
73
74  dt1=real(itime-memtime(1))
75  dt2=real(memtime(2)-itime)
76  dtt=1./(dt1+dt2)
77
78
79  ! Loop about all release points
80  !******************************
81
82  do j=1,numpoint
83    if (abs(ireleasestart(j)-itime).gt.lage(nageclass)) goto 10
84    topocenter=0.
85    hmixcenter=0.
86    hmixfract=0.
87    tropocenter=0.
88    tropofract=0.
89    pvfract=0.
90    pvcenter=0.
91    rmsdist=0.
92    zrmsdist=0.
93
94    n=0
95    do i=1,numpart
96      if (itra1(i).ne.itime) goto 20
97      if (npoint(i).ne.j) goto 20
98      n=n+1
99      xl(n)=xlon0+xtra1(i)*dx
100      yl(n)=ylat0+ytra1(i)*dy
101      zl(n)=ztra1(i)
102
103
104  ! Interpolate PBL height, PV, and tropopause height to each
105  ! particle position in order to determine fraction of particles
106  ! within the PBL, above tropopause height, and average PV.
107  ! Interpolate topography, too, and convert to altitude asl
108  !**************************************************************
109
110      ix=int(xtra1(i))
111      jy=int(ytra1(i))
112      ixp=ix+1
113      jyp=jy+1
114      ddx=xtra1(i)-real(ix)
115      ddy=ytra1(i)-real(jy)
116      rddx=1.-ddx
117      rddy=1.-ddy
118      p1=rddx*rddy
119      p2=ddx*rddy
120      p3=rddx*ddy
121      p4=ddx*ddy
122
123  ! Topography
124  !***********
125
126      topo=p1*oro(ix ,jy) &
127           + p2*oro(ixp,jy) &
128           + p3*oro(ix ,jyp) &
129           + p4*oro(ixp,jyp)
130      topocenter=topocenter+topo
131
132  ! Potential vorticity
133  !********************
134
135      do il=2,nz
136        if (height(il).gt.zl(n)) then
137          indz=il-1
138          indzp=il
139          goto 6
140        endif
141      end do
1426     continue
143
144      dz1=zl(n)-height(indz)
145      dz2=height(indzp)-zl(n)
146      dz=1./(dz1+dz2)
147
148
149      do ind=indz,indzp
150        do m=1,2
151          indexh=memind(m)
152          pv1(m)=p1*pv(ix ,jy ,ind,indexh) &
153               +p2*pv(ixp,jy ,ind,indexh) &
154               +p3*pv(ix ,jyp,ind,indexh) &
155               +p4*pv(ixp,jyp,ind,indexh)
156        end do
157        pvprof(ind-indz+1)=(pv1(1)*dt2+pv1(2)*dt1)*dtt
158      end do
159      pvi=(dz1*pvprof(2)+dz2*pvprof(1))*dz
160      pvcenter=pvcenter+pvi
161      if (yl(n).gt.0.) then
162        if (pvi.lt.2.) pvfract=pvfract+1.
163      else
164        if (pvi.gt.-2.) pvfract=pvfract+1.
165      endif
166
167
168  ! Tropopause and PBL height
169  !**************************
170
171      do m=1,2
172        indexh=memind(m)
173
174        tr(m)=p1*tropopause(ix ,jy ,1,indexh) &
175             + p2*tropopause(ixp,jy ,1,indexh) &
176             + p3*tropopause(ix ,jyp,1,indexh) &
177             + p4*tropopause(ixp,jyp,1,indexh)
178
179        hm(m)=p1*hmix(ix ,jy ,1,indexh) &
180             + p2*hmix(ixp,jy ,1,indexh) &
181             + p3*hmix(ix ,jyp,1,indexh) &
182             + p4*hmix(ixp,jyp,1,indexh)
183      end do
184
185      hmixi=(hm(1)*dt2+hm(2)*dt1)*dtt
186      tri=(tr(1)*dt2+tr(2)*dt1)*dtt
187      if (zl(n).lt.tri) tropofract=tropofract+1.
188      tropocenter=tropocenter+tri+topo
189      if (zl(n).lt.hmixi) hmixfract=hmixfract+1.
190      zl(n)=zl(n)+topo        ! convert to height asl
191      hmixcenter=hmixcenter+hmixi
192
193
19420    continue
195    end do
196
197
198  ! Make statistics for all plumes with n>0 particles
199  !**************************************************
200
201    if (n.gt.0) then
202      topocenter=topocenter/real(n)
203      hmixcenter=hmixcenter/real(n)
204      pvcenter=pvcenter/real(n)
205      tropocenter=tropocenter/real(n)
206      hmixfract=100.*hmixfract/real(n)
207      pvfract=100.*pvfract/real(n)
208      tropofract=100.*tropofract/real(n)
209
210  ! Cluster the particle positions
211  !*******************************
212
213      call clustering(xl,yl,zl,n,xclust,yclust,zclust,fclust,rms, &
214           rmsclust,zrms)
215
216
217  ! Determine center of mass position on earth and average height
218  !**************************************************************
219
220      call centerofmass(xl,yl,n,xcenter,ycenter)
221      call mean(zl,zcenter,zrmsdist,n)
222
223  ! Root mean square distance from center of mass
224  !**********************************************
225
226      do k=1,n
227        dist=distance(yl(k),xl(k),ycenter,xcenter)
228        rmsdist=rmsdist+dist*dist
229      end do
230      if (rmsdist.gt.0.) rmsdist=sqrt(rmsdist/real(n))
231      rmsdist=max(rmsdist,0.)
232
233  ! Write out results in trajectory data file
234  !******************************************
235
236      write(unitouttraj,'(i5,i8,2f9.4,4f8.1,f8.2,4f8.1,3f6.1,&
237           &5(2f8.3,f7.0,f6.1,f8.1))')&
238           &j,itime-(ireleasestart(j)+ireleaseend(j))/2, &
239           xcenter,ycenter,zcenter,topocenter,hmixcenter,tropocenter, &
240           pvcenter,rmsdist,rms,zrmsdist,zrms,hmixfract,pvfract, &
241           tropofract, &
242           (xclust(k),yclust(k),zclust(k),fclust(k),rmsclust(k), &
243           k=1,ncluster)
244    endif
245
246
24710  continue
248  end do
249
250
251end subroutine plumetraj
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG