source: flexpart.git/src/openouttraj.f90 @ e200b7a

10.4.1_peseiFPv9.3.1FPv9.3.1b_testingFPv9.3.2GFS_025NetCDFbugfixes+enhancementsdepositiondevflexpart-noresmfp9.3.1-20161214-nc4grib2nc4_repairinputlistlaptoprelease-10release-10.4.1scaling-bugsvn-petrasvn-trunkunivie
Last change on this file since e200b7a was e200b7a, checked in by Matthias Langer <matthias.langer@…>, 11 years ago

git-svn-id: http://flexpart.flexpart.eu:8088/svn/FlexPart90/trunk@4 ef8cc7e1-21b7-489e-abab-c1baa636049d

  • Property mode set to 100644
File size: 3.9 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine openouttraj
23
24  !*****************************************************************************
25  !                                                                            *
26  !   This routine opens the output file for the plume trajectory output       *
27  !   produced by the cluster analysis.                                        *
28  !                                                                            *
29  !     Author: A. Stohl                                                       *
30  !                                                                            *
31  !     27 January 2001                                                        *
32  !                                                                            *
33  !*****************************************************************************
34  !                                                                            *
35  ! Variables:                                                                 *
36  !                                                                            *
37  !*****************************************************************************
38
39  use point_mod
40  use par_mod
41  use com_mod
42
43  implicit none
44
45  integer :: i
46  real :: xp1,yp1,xp2,yp2
47
48
49  ! Open output file for trajectory output
50  !***************************************
51
52  open(unitouttraj,file=path(2)(1:length(2))//'trajectories.txt', &
53       form='formatted',err=998)
54
55  if (ldirect.eq.1) then
56  write(unitouttraj,'(i8,1x,i6,1x,a)') ibdate,ibtime,'FLEXPART V8.2'
57  else
58  write(unitouttraj,'(i8,1x,i6,1x,a)') iedate,ietime,'FLEXPART V8.2'
59  endif
60  write(unitouttraj,*) method,lsubgrid,lconvection
61  write(unitouttraj,*) numpoint
62  do i=1,numpoint
63    xp1=xpoint1(i)*dx+xlon0
64    yp1=ypoint1(i)*dy+ylat0
65    xp2=xpoint2(i)*dx+xlon0
66    yp2=ypoint2(i)*dy+ylat0
67    write(unitouttraj,*) ireleasestart(i),ireleaseend(i), &
68         xp1,yp1,xp2,yp2,zpoint1(i),zpoint2(i),kindz(i),npart(i)
69    if (numpoint.le.1000) then
70      write(unitouttraj,'(a)') compoint(i)(1:40)
71    else
72      write(unitouttraj,'(a)') compoint(1001)(1:40)
73    endif
74  end do
75
76  return
77
78998   write(*,*) ' #### FLEXPART MODEL ERROR!   THE FILE         #### '
79  write(*,*) ' #### trajectories.txt                         #### '
80  write(*,*) ' #### CANNOT BE OPENED. IF A FILE WITH THIS    #### '
81  write(*,*) ' #### NAME ALREADY EXISTS, DELETE IT AND START #### '
82  write(*,*) ' #### THE PROGRAM AGAIN.                       #### '
83  stop
84
85end subroutine openouttraj
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG