source: flexpart.git/src/partoutput_short.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: 4.0 KB
Line 
1subroutine partoutput_short(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,numshortout,numshortall
24  integer :: ix,jy,ixp,jyp
25  real :: xlon,ylat,zlim,dt1,dt2,dtt,ddx,ddy,rddx,rddy,p1,p2,p3,p4,topo
26  character :: adate*8,atime*6
27
28  integer(kind=2) :: idump(3,maxpart)
29  integer :: i4dump(maxpart)
30
31
32  ! Determine current calendar date, needed for the file name
33  !**********************************************************
34
35  jul=bdate+real(itime,kind=dp)/86400._dp
36  call caldate(jul,jjjjmmdd,ihmmss)
37  write(adate,'(i8.8)') jjjjmmdd
38  write(atime,'(i6.6)') ihmmss
39
40
41  ! Some variables needed for temporal interpolation
42  !*************************************************
43
44  dt1=real(itime-memtime(1))
45  dt2=real(memtime(2)-itime)
46  dtt=1./(dt1+dt2)
47
48
49  ! Loop about all particles
50  !*************************
51
52  numshortout=0
53  numshortall=0
54  do i=1,numpart
55
56  ! Take only valid particles
57  !**************************
58
59    if (itra1(i).eq.itime) then
60      xlon=xlon0+xtra1(i)*dx
61      ylat=ylat0+ytra1(i)*dy
62
63  !*****************************************************************************
64  ! Interpolate several variables (PV, specific humidity, etc.) to particle position
65  !*****************************************************************************
66
67      ix=xtra1(i)
68      jy=ytra1(i)
69      ixp=ix+1
70      jyp=jy+1
71      ddx=xtra1(i)-real(ix)
72      ddy=ytra1(i)-real(jy)
73      rddx=1.-ddx
74      rddy=1.-ddy
75      p1=rddx*rddy
76      p2=ddx*rddy
77      p3=rddx*ddy
78      p4=ddx*ddy
79
80  ! Topography
81  !***********
82
83      topo=p1*oro(ix ,jy) &
84           + p2*oro(ixp,jy) &
85           + p3*oro(ix ,jyp) &
86           + p4*oro(ixp,jyp)
87
88
89  ! Convert positions to integer*2 variables (from -32768 to 32767)
90  ! Do this only for region of main interest, i.e. extended North Atlantic region,
91  ! and for the tracer of interest, i.e. the North American one
92  !*****************************************************************************
93
94      if (xlon.gt.180.) xlon=xlon-360.
95      if (xlon.lt.-180.) xlon=xlon+360.
96
97      numshortall=numshortall+1
98      if ((xlon.gt.-140).and.(xlon.lt.60).and.(ylat.gt.10).and. &
99           (xmass1(i,1).gt.0.)) then
100        numshortout=numshortout+1
101        idump(1,numshortout)=nint(xlon*180.)
102        idump(2,numshortout)=nint(ylat*360.)
103        zlim=min(ztra1(i)+topo,32766.)
104        idump(3,numshortout)=nint(zlim)
105        i4dump(numshortout)=npoint(i)
106      endif
107
108    endif
109  end do
110
111
112  ! Open output file and write the output
113  !**************************************
114
115  open(unitshortpart,file=path(2)(1:length(2))//'shortposit_'//adate// &
116       atime,form='unformatted')
117
118  ! Write current time to file
119  !***************************
120
121  write(unitshortpart) itime
122  write(unitshortpart) numshortout
123  write(unitshortpart) &
124       (i4dump(i),(idump(j,i),j=1,3),i=1,numshortout)
125
126
127  !write(*,*) numshortout,numshortall
128
129  close(unitshortpart)
130
131end subroutine partoutput_short
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG