source: flexpart.git/src/partoutput_short_mpi.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.7 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  !     12/2014 eso: Version for MPI                                           *
15  !                  Processes sequentially access and append data to file     *
16  !                  NB: Do not use yet!                                       *
17  !*****************************************************************************
18  !                                                                            *
19  ! Variables:                                                                 *
20  !                                                                            *
21  !*****************************************************************************
22
23  use par_mod
24  use com_mod
25  use mpi_mod
26
27  implicit none
28
29  real(kind=dp) :: jul
30  integer :: itime,i,j,jjjjmmdd,ihmmss,numshortout,numshortall
31  integer :: ix,jy,ixp,jyp
32  real :: xlon,ylat,zlim,dt1,dt2,dtt,ddx,ddy,rddx,rddy,p1,p2,p3,p4,topo
33  character :: adate*8,atime*6
34
35  integer(kind=2) :: idump(3,maxpart)
36  integer :: i4dump(maxpart)
37  character(LEN=8) :: file_stat='OLD'
38
39  ! MPI root process creates the file, other processes append to it
40  if (lroot) file_stat='REPLACE'
41
42  ! Determine current calendar date, needed for the file name
43  !**********************************************************
44
45  jul=bdate+real(itime,kind=dp)/86400._dp
46  call caldate(jul,jjjjmmdd,ihmmss)
47  write(adate,'(i8.8)') jjjjmmdd
48  write(atime,'(i6.6)') ihmmss
49
50
51  ! Some variables needed for temporal interpolation
52  !*************************************************
53
54  dt1=real(itime-memtime(1))
55  dt2=real(memtime(2)-itime)
56  dtt=1./(dt1+dt2)
57
58
59  ! Loop about all particles
60  !*************************
61
62  numshortout=0
63  numshortall=0
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  ! Topography
91  !***********
92
93      topo=p1*oro(ix ,jy) &
94           + p2*oro(ixp,jy) &
95           + p3*oro(ix ,jyp) &
96           + p4*oro(ixp,jyp)
97
98
99  ! Convert positions to integer*2 variables (from -32768 to 32767)
100  ! Do this only for region of main interest, i.e. extended North Atlantic region,
101  ! and for the tracer of interest, i.e. the North American one
102  !*****************************************************************************
103
104      if (xlon.gt.180.) xlon=xlon-360.
105      if (xlon.lt.-180.) xlon=xlon+360.
106
107      numshortall=numshortall+1
108      if ((xlon.gt.-140).and.(xlon.lt.60).and.(ylat.gt.10).and. &
109           (xmass1(i,1).gt.0.)) then
110        numshortout=numshortout+1
111        idump(1,numshortout)=nint(xlon*180.)
112        idump(2,numshortout)=nint(ylat*360.)
113        zlim=min(ztra1(i)+topo,32766.)
114        idump(3,numshortout)=nint(zlim)
115        i4dump(numshortout)=npoint(i)
116      endif
117
118    endif
119  end do
120
121
122  ! Open output file and write the output
123  !**************************************
124
125  open(unitshortpart,file=path(2)(1:length(2))//'shortposit_'//adate// &
126       atime,form='unformatted',status=file_stat,position='append')
127
128  ! Write current time to file
129  !***************************
130
131  if (lroot) write(unitshortpart) itime ! MPI root process only
132  ! :TODO: get total numshortout (MPI reduction), add MPI barrier, open file
133  ! sequentially below
134  write(unitshortpart) numshortout
135  write(unitshortpart) &
136       (i4dump(i),(idump(j,i),j=1,3),i=1,numshortout)
137
138
139  write(*,*) numshortout,numshortall
140
141  close(unitshortpart)
142
143end subroutine partoutput_short
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG