source: flexpart.git/src/openouttraj.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: 2.6 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine openouttraj
5
6  !*****************************************************************************
7  !                                                                            *
8  !   This routine opens the output file for the plume trajectory output       *
9  !   produced by the cluster analysis.                                        *
10  !                                                                            *
11  !     Author: A. Stohl                                                       *
12  !                                                                            *
13  !     27 January 2001                                                        *
14  !                                                                            *
15  !*****************************************************************************
16  !                                                                            *
17  ! Variables:                                                                 *
18  !                                                                            *
19  !*****************************************************************************
20
21  use point_mod
22  use par_mod
23  use com_mod
24
25  implicit none
26
27  integer :: i
28  real :: xp1,yp1,xp2,yp2
29
30
31  ! Open output file for trajectory output
32  !***************************************
33
34  open(unitouttraj,file=path(2)(1:length(2))//'trajectories.txt', &
35       form='formatted',err=998)
36
37  if (ldirect.eq.1) then
38  write(unitouttraj,'(i8,1x,i6,1x,a)') ibdate,ibtime, trim(flexversion)
39  else
40  write(unitouttraj,'(i8,1x,i6,1x,a)') iedate,ietime, trim(flexversion)
41  endif
42  write(unitouttraj,*) method,lsubgrid,lconvection
43  write(unitouttraj,*) numpoint
44  do i=1,numpoint
45    xp1=xpoint1(i)*dx+xlon0
46    yp1=ypoint1(i)*dy+ylat0
47    xp2=xpoint2(i)*dx+xlon0
48    yp2=ypoint2(i)*dy+ylat0
49    write(unitouttraj,*) ireleasestart(i),ireleaseend(i), &
50         xp1,yp1,xp2,yp2,zpoint1(i),zpoint2(i),kindz(i),npart(i)
51    if (numpoint.le.1000) then
52      write(unitouttraj,'(a)') compoint(i)(1:40)
53    else
54      write(unitouttraj,'(a)') compoint(1001)(1:40)
55    endif
56  end do
57
58  return
59
60998   write(*,*) ' #### FLEXPART MODEL ERROR!   THE FILE         #### '
61  write(*,*) ' #### trajectories.txt                         #### '
62  write(*,*) ' #### CANNOT BE OPENED. IF A FILE WITH THIS    #### '
63  write(*,*) ' #### NAME ALREADY EXISTS, DELETE IT AND START #### '
64  write(*,*) ' #### THE PROGRAM AGAIN.                       #### '
65  stop
66
67end subroutine openouttraj
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG