source: flexpart.git/src/plumetraj.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: 7.4 KB
Line 
1subroutine plumetraj(itime)
2  !                       i
3  !*****************************************************************************
4  !                                                                            *
5  ! Determines a plume centroid trajectory for each release site, and manages  *
6  ! clustering of particle locations. Certain parameters (average PV,          *
7  ! tropopause height, etc., are provided along the plume trajectories.        *
8  ! At the end, output is written to file 'trajectories.txt'.                  *
9  !                                                                            *
10  !     Author: A. Stohl                                                       *
11  !                                                                            *
12  !     24 January 2002                                                        *
13  !                                                                            *
14  ! Variables:                                                                 *
15  ! fclust          fraction of particles belonging to each cluster            *
16  ! hmixcenter      mean mixing height for all particles                       *
17  ! ncluster        number of clusters to be used                              *
18  ! pvcenter        mean PV for all particles                                  *
19  ! pvfract         fraction of particles with PV<2pvu                         *
20  ! rms             total horizontal rms distance after clustering             *
21  ! rmsdist         total horizontal rms distance before clustering            *
22  ! rmsclust        horizontal rms distance for each individual cluster        *
23  ! topocenter      mean topography underlying all particles                   *
24  ! tropocenter     mean tropopause height at the positions of particles       *
25  ! tropofract      fraction of particles within the troposphere               *
26  ! zrms            total vertical rms distance after clustering               *
27  ! zrmsdist        total vertical rms distance before clustering              *
28  ! xclust,yclust,  Cluster centroid positions                                 *
29  ! zclust                                                                     *
30  !                                                                            *
31  !*****************************************************************************
32
33  use point_mod
34  use par_mod
35  use com_mod
36  use mean_mod
37
38  implicit none
39
40  integer :: itime,ix,jy,ixp,jyp,indexh,i,j,k,m,n,il,ind,indz,indzp
41  real :: xl(maxpart),yl(maxpart),zl(maxpart)
42  real :: xcenter,ycenter,zcenter,dist,distance,rmsdist,zrmsdist
43
44  real :: xclust(ncluster),yclust(ncluster),zclust(ncluster)
45  real :: fclust(ncluster),rms,rmsclust(ncluster),zrms
46
47  real :: dt1,dt2,dtt,ddx,ddy,rddx,rddy,p1,p2,p3,p4,dz1,dz2,dz
48  real :: topo,topocenter,hm(2),hmixi,hmixfract,hmixcenter
49  real :: pv1(2),pvprof(2),pvi,pvcenter,pvfract,tr(2),tri,tropofract
50  real :: tropocenter
51
52
53  dt1=real(itime-memtime(1))
54  dt2=real(memtime(2)-itime)
55  dtt=1./(dt1+dt2)
56
57
58  ! Loop about all release points
59  !******************************
60
61  do j=1,numpoint
62    if (abs(ireleasestart(j)-itime).gt.lage(nageclass)) goto 10
63    topocenter=0.
64    hmixcenter=0.
65    hmixfract=0.
66    tropocenter=0.
67    tropofract=0.
68    pvfract=0.
69    pvcenter=0.
70    rmsdist=0.
71    zrmsdist=0.
72
73    n=0
74    do i=1,numpart
75      if (itra1(i).ne.itime) goto 20
76      if (npoint(i).ne.j) goto 20
77      n=n+1
78      xl(n)=xlon0+xtra1(i)*dx
79      yl(n)=ylat0+ytra1(i)*dy
80      zl(n)=ztra1(i)
81
82
83  ! Interpolate PBL height, PV, and tropopause height to each
84  ! particle position in order to determine fraction of particles
85  ! within the PBL, above tropopause height, and average PV.
86  ! Interpolate topography, too, and convert to altitude asl
87  !**************************************************************
88
89      ix=int(xtra1(i))
90      jy=int(ytra1(i))
91      ixp=ix+1
92      jyp=jy+1
93      ddx=xtra1(i)-real(ix)
94      ddy=ytra1(i)-real(jy)
95      rddx=1.-ddx
96      rddy=1.-ddy
97      p1=rddx*rddy
98      p2=ddx*rddy
99      p3=rddx*ddy
100      p4=ddx*ddy
101
102  ! Topography
103  !***********
104
105      topo=p1*oro(ix ,jy) &
106           + p2*oro(ixp,jy) &
107           + p3*oro(ix ,jyp) &
108           + p4*oro(ixp,jyp)
109      topocenter=topocenter+topo
110
111  ! Potential vorticity
112  !********************
113
114      do il=2,nz
115        if (height(il).gt.zl(n)) then
116          indz=il-1
117          indzp=il
118          goto 6
119        endif
120      end do
1216     continue
122
123      dz1=zl(n)-height(indz)
124      dz2=height(indzp)-zl(n)
125      dz=1./(dz1+dz2)
126
127
128      do ind=indz,indzp
129        do m=1,2
130          indexh=memind(m)
131          pv1(m)=p1*pv(ix ,jy ,ind,indexh) &
132               +p2*pv(ixp,jy ,ind,indexh) &
133               +p3*pv(ix ,jyp,ind,indexh) &
134               +p4*pv(ixp,jyp,ind,indexh)
135        end do
136        pvprof(ind-indz+1)=(pv1(1)*dt2+pv1(2)*dt1)*dtt
137      end do
138      pvi=(dz1*pvprof(2)+dz2*pvprof(1))*dz
139      pvcenter=pvcenter+pvi
140      if (yl(n).gt.0.) then
141        if (pvi.lt.2.) pvfract=pvfract+1.
142      else
143        if (pvi.gt.-2.) pvfract=pvfract+1.
144      endif
145
146
147  ! Tropopause and PBL height
148  !**************************
149
150      do m=1,2
151        indexh=memind(m)
152
153        tr(m)=p1*tropopause(ix ,jy ,1,indexh) &
154             + p2*tropopause(ixp,jy ,1,indexh) &
155             + p3*tropopause(ix ,jyp,1,indexh) &
156             + p4*tropopause(ixp,jyp,1,indexh)
157
158        hm(m)=p1*hmix(ix ,jy ,1,indexh) &
159             + p2*hmix(ixp,jy ,1,indexh) &
160             + p3*hmix(ix ,jyp,1,indexh) &
161             + p4*hmix(ixp,jyp,1,indexh)
162      end do
163
164      hmixi=(hm(1)*dt2+hm(2)*dt1)*dtt
165      tri=(tr(1)*dt2+tr(2)*dt1)*dtt
166      if (zl(n).lt.tri) tropofract=tropofract+1.
167      tropocenter=tropocenter+tri+topo
168      if (zl(n).lt.hmixi) hmixfract=hmixfract+1.
169      zl(n)=zl(n)+topo        ! convert to height asl
170      hmixcenter=hmixcenter+hmixi
171
172
17320    continue
174    end do
175
176
177  ! Make statistics for all plumes with n>0 particles
178  !**************************************************
179
180    if (n.gt.0) then
181      topocenter=topocenter/real(n)
182      hmixcenter=hmixcenter/real(n)
183      pvcenter=pvcenter/real(n)
184      tropocenter=tropocenter/real(n)
185      hmixfract=100.*hmixfract/real(n)
186      pvfract=100.*pvfract/real(n)
187      tropofract=100.*tropofract/real(n)
188
189  ! Cluster the particle positions
190  !*******************************
191
192      call clustering(xl,yl,zl,n,xclust,yclust,zclust,fclust,rms, &
193           rmsclust,zrms)
194
195
196  ! Determine center of mass position on earth and average height
197  !**************************************************************
198
199      call centerofmass(xl,yl,n,xcenter,ycenter)
200      call mean(zl,zcenter,zrmsdist,n)
201
202  ! Root mean square distance from center of mass
203  !**********************************************
204
205      do k=1,n
206        dist=distance(yl(k),xl(k),ycenter,xcenter)
207        rmsdist=rmsdist+dist*dist
208      end do
209      if (rmsdist.gt.0.) rmsdist=sqrt(rmsdist/real(n))
210      rmsdist=max(rmsdist,0.)
211
212  ! Write out results in trajectory data file
213  !******************************************
214
215      write(unitouttraj,'(i5,i8,2f9.4,4f8.1,f8.2,4f8.1,3f6.1,&
216           &5(2f8.3,f7.0,f6.1,f8.1))')&
217           &j,itime-(ireleasestart(j)+ireleaseend(j))/2, &
218           xcenter,ycenter,zcenter,topocenter,hmixcenter,tropocenter, &
219           pvcenter,rmsdist,rms,zrmsdist,zrms,hmixfract,pvfract, &
220           tropofract, &
221           (xclust(k),yclust(k),zclust(k),fclust(k),rmsclust(k), &
222           k=1,ncluster)
223    endif
224
225
22610  continue
227  end do
228
229
230end subroutine plumetraj
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG