source: flexpart.git/src/partoutput.f90 @ 5f2e8f6

flexpart-noresm
Last change on this file since 5f2e8f6 was 5f2e8f6, checked in by Ignacio Pisso <Ignacio.Pisso@…>, 8 years ago

new flexpart noresm code in src

  • Property mode set to 100755
File size: 7.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 partoutput(itime)
23  !                        i
24  !*****************************************************************************
25  !                                                                            *
26  !     Dump all particle positions                                            *
27  !                                                                            *
28  !     Author: A. Stohl                                                       *
29  !                                                                            *
30  !     12 March 1999                                                          *
31  !                                                                            *
32  !*****************************************************************************
33  !                                                                            *
34  ! Variables:                                                                 *
35  !                                                                            *
36  !*****************************************************************************
37
38  use par_mod
39  use com_mod
40
41  implicit none
42
43  real(kind=dp) :: jul
44  integer :: itime,i,j,jjjjmmdd,ihmmss
45  integer :: ix,jy,ixp,jyp,indexh,m,il,ind,indz,indzp
46  real :: xlon,ylat
47  real :: dt1,dt2,dtt,ddx,ddy,rddx,rddy,p1,p2,p3,p4,dz1,dz2,dz
48  real :: topo,hm(2),hmixi,pv1(2),pvprof(2),pvi,qv1(2),qvprof(2),qvi
49  real :: tt1(2),ttprof(2),tti,rho1(2),rhoprof(2),rhoi
50  real :: tr(2),tri
51  character :: adate*8,atime*6
52
53
54  ! Determine current calendar date, needed for the file name
55  !**********************************************************
56
57  jul=bdate+real(itime,kind=dp)/86400._dp
58  call caldate(jul,jjjjmmdd,ihmmss)
59  write(adate,'(i8.8)') jjjjmmdd
60  write(atime,'(i6.6)') ihmmss
61
62
63  ! Some variables needed for temporal interpolation
64  !*************************************************
65
66  dt1=real(itime-memtime(1))
67  dt2=real(memtime(2)-itime)
68  dtt=1./(dt1+dt2)
69
70  ! Open output file and write the output
71  !**************************************
72
73  if (ipout.eq.1) then
74      open(unitpartout,file=path(2)(1:length(2))//'partposit_'//adate// &
75         atime,form='unformatted') ! for testreasons  modified by mc it should be unformatted
76   ! open(unitpartout,file=path(2)(1:length(2))//'partposit_'//adate// &
77   !      atime,form='formatted') ! for test reasons  modified by mc it should be unformatted
78  else
79    open(unitpartout,file=path(2)(1:length(2))//'partposit_end', &
80         form='unformatted') ! for testreasons  modified by mc it should be unformatted
81   ! open(unitpartout,file=path(2)(1:length(2))//'partposit_end', &
82   !      form='formatted')    ! for test reasons  modified by mc it should be unformatted
83  endif
84
85  ! Write current time to file
86  !***************************
87
88  !write(unitpartout) itime !commented for testing reason by mc
89  do i=1,numpart
90
91  ! Take only valid particles
92  !**************************
93
94    if (itra1(i).eq.itime) then
95      xlon=xlon0+xtra1(i)*dx
96      ylat=ylat0+ytra1(i)*dy
97
98  !*****************************************************************************
99  ! Interpolate several variables (PV, specific humidity, etc.) to particle position
100  !*****************************************************************************
101
102      ix=xtra1(i)
103      jy=ytra1(i)
104      ixp=ix+1
105      jyp=jy+1
106      ddx=xtra1(i)-real(ix)
107      ddy=ytra1(i)-real(jy)
108      rddx=1.-ddx
109      rddy=1.-ddy
110      p1=rddx*rddy
111      p2=ddx*rddy
112      p3=rddx*ddy
113      p4=ddx*ddy
114
115  ! Topography
116  !***********
117
118      topo=p1*oro(ix ,jy) &
119           + p2*oro(ixp,jy) &
120           + p3*oro(ix ,jyp) &
121           + p4*oro(ixp,jyp)
122
123  ! Potential vorticity, specific humidity, temperature, and density
124  !*****************************************************************
125
126      do il=2,nz
127        if (height(il).gt.ztra1(i)) then
128          indz=il-1
129          indzp=il
130          goto 6
131        endif
132      end do
1336     continue
134
135      dz1=ztra1(i)-height(indz)
136      dz2=height(indzp)-ztra1(i)
137      dz=1./(dz1+dz2)
138
139
140      do ind=indz,indzp
141        do m=1,2
142          indexh=memind(m)
143
144  ! Potential vorticity
145          pv1(m)=p1*pv(ix ,jy ,ind,indexh) &
146               +p2*pv(ixp,jy ,ind,indexh) &
147               +p3*pv(ix ,jyp,ind,indexh) &
148               +p4*pv(ixp,jyp,ind,indexh)
149  ! Specific humidity
150          qv1(m)=p1*qv(ix ,jy ,ind,indexh) &
151               +p2*qv(ixp,jy ,ind,indexh) &
152               +p3*qv(ix ,jyp,ind,indexh) &
153               +p4*qv(ixp,jyp,ind,indexh)
154  ! Temperature
155          tt1(m)=p1*tt(ix ,jy ,ind,indexh) &
156               +p2*tt(ixp,jy ,ind,indexh) &
157               +p3*tt(ix ,jyp,ind,indexh) &
158               +p4*tt(ixp,jyp,ind,indexh)
159  ! Density
160          rho1(m)=p1*rho(ix ,jy ,ind,indexh) &
161               +p2*rho(ixp,jy ,ind,indexh) &
162               +p3*rho(ix ,jyp,ind,indexh) &
163               +p4*rho(ixp,jyp,ind,indexh)
164        end do
165        pvprof(ind-indz+1)=(pv1(1)*dt2+pv1(2)*dt1)*dtt
166        qvprof(ind-indz+1)=(qv1(1)*dt2+qv1(2)*dt1)*dtt
167        ttprof(ind-indz+1)=(tt1(1)*dt2+tt1(2)*dt1)*dtt
168        rhoprof(ind-indz+1)=(rho1(1)*dt2+rho1(2)*dt1)*dtt
169      end do
170      pvi=(dz1*pvprof(2)+dz2*pvprof(1))*dz
171      qvi=(dz1*qvprof(2)+dz2*qvprof(1))*dz
172      tti=(dz1*ttprof(2)+dz2*ttprof(1))*dz
173      rhoi=(dz1*rhoprof(2)+dz2*rhoprof(1))*dz
174
175  ! Tropopause and PBL height
176  !**************************
177
178      do m=1,2
179        indexh=memind(m)
180
181  ! Tropopause
182        tr(m)=p1*tropopause(ix ,jy ,1,indexh) &
183             + p2*tropopause(ixp,jy ,1,indexh) &
184             + p3*tropopause(ix ,jyp,1,indexh) &
185             + p4*tropopause(ixp,jyp,1,indexh)
186
187  ! PBL height
188        hm(m)=p1*hmix(ix ,jy ,1,indexh) &
189             + p2*hmix(ixp,jy ,1,indexh) &
190             + p3*hmix(ix ,jyp,1,indexh) &
191             + p4*hmix(ixp,jyp,1,indexh)
192      end do
193
194      hmixi=(hm(1)*dt2+hm(2)*dt1)*dtt
195      tri=(tr(1)*dt2+tr(2)*dt1)*dtt
196
197
198  ! Write the output
199  !*****************
200
201      write(unitpartout) npoint(i),xlon,ylat,ztra1(i), & !original writing comemnted out for test reason by mc
202           itramem(i),topo,pvi,qvi,rhoi,hmixi,tri,tti, &
203           (xmass1(i,j),j=1,nspec)
204     !write(unitpartout,*)xlon,ylat,ztra1(i) !modified for testreaosn by mc, to be removed and but as above
205     
206    endif
207  end do
208  write(unitpartout) -99999,-9999.9,-9999.9,-9999.9,-99999, &   !comemnted out for test reason by mc|!
209       -9999.9,-9999.9,-9999.9,-9999.9,-9999.9,-9999.9,-9999.9, &
210       (-9999.9,j=1,nspec)
211
212 
213  close(unitpartout)
214
215end subroutine partoutput
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG