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