source: flexpart.git/src/partoutput_short.f90

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file was 92fab65, checked in by Ignacio Pisso <ip@…>, 4 years ago

add SPDX-License-Identifier to all .f90 files

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