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