source: branches/jerome/src_flexwrf_v3.1/openouttraj.f90 @ 16

Last change on this file since 16 was 16, checked in by jebri, 11 years ago

sources for flexwrf v3.1

File size: 4.9 KB
Line 
1!***********************************************************************
2!* Copyright 2012,2013                                                *
3!* Jerome Brioude, Delia Arnold, Andreas Stohl, Wayne Angevine,       *
4!* John Burkhart, Massimo Cassiani, Adam Dingwell, Richard C Easter, Sabine Eckhardt,*
5!* Stephanie Evan, Jerome D Fast, Don Morton, Ignacio Pisso,          *
6!* Petra Seibert, Gerard Wotawa, Caroline Forster, Harald Sodemann,   *
7!*                                                                     *
8!* This file is part of FLEXPART WRF                                   *
9!*                                                                     *
10!* FLEXPART is free software: you can redistribute it and/or modify    *
11!* it under the terms of the GNU General Public License as published by*
12!* the Free Software Foundation, either version 3 of the License, or   *
13!* (at your option) any later version.                                 *
14!*                                                                     *
15!* FLEXPART is distributed in the hope that it will be useful,         *
16!* but WITHOUT ANY WARRANTY; without even the implied warranty of      *
17!* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
18!* GNU General Public License for more details.                        *
19!*                                                                     *
20!* You should have received a copy of the GNU General Public License   *
21!* along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
22!***********************************************************************
23
24      subroutine openouttraj
25!*******************************************************************************
26!                                                                              *
27!   Note:  This is the FLEXPART_WRF version of subroutine openouttraj.         *
28!                                                                              *
29!   This routine opens the output file for the plume trajectory output         *
30!   produced by the cluster analysis.                                          *
31!                                                                              *
32!     Author: A. Stohl                                                         *
33!     27 January 2001                                                          *
34!                                                                              *
35!     Dec 2005, R. Easter - changed names of "*lon0*" & "*lat0*" variables     *
36!                                                                              *
37!*******************************************************************************
38!                                                                              *
39! Variables:                                                                   *
40!                                                                              *
41!*******************************************************************************
42
43  use point_mod
44  use par_mod
45  use com_mod
46!      include 'includepar'
47!      include 'includecom'
48     
49      integer i
50      real xp1,yp1,xp2,yp2
51      real xtmp, ytmp
52
53
54! Open output file for trajectory output
55!***************************************
56
57      open(unitouttraj,file=path(1)(1:length(1))//'trajectories.txt', &
58      form='formatted',err=998)
59
60      if (ldirect.eq.1) then
61      write(unitouttraj,'(i8,1x,i6,1x,a)') ibdate,ibtime,'FLEXWRF  V3.0'
62      else
63      write(unitouttraj,'(i8,1x,i6,1x,a)') iedate,ietime,'FLEXWRF  V3.0'
64      endif
65      write(unitouttraj,*) method,lsubgrid,lconvection
66      write(unitouttraj,*) numpoint
67      do i=1,numpoint
68       if (outgrid_option .eq. 0) then
69         xp1=xpoint1(i)*dx+xmet0
70         yp1=ypoint1(i)*dy+ymet0
71         xp2=xpoint2(i)*dx+xmet0
72         yp2=ypoint2(i)*dy+ymet0
73        endif
74       if (outgrid_option .eq. 1) then
75          xtmp = xpoint1(i)*dx+xmet0
76          ytmp = ypoint1(i)*dy+ymet0
77          call xymeter_to_ll_wrf( xtmp, ytmp, xp1, yp1 )
78          xtmp = xpoint2(i)*dx+xmet0
79          ytmp = ypoint2(i)*dy+ymet0
80          call xymeter_to_ll_wrf( xtmp, ytmp, xp2, yp2 )
81        endif
82!jdf    write(unitouttraj,*) ireleasestart(i),ireleaseend(i),
83!jdf +  xp1,yp1,xp2,yp2,zpoint1(i),zpoint2(i),kindz(i),npart(i)
84!jdf    write(unitouttraj,'(a)') compoint(i)(1:40)
85        write(unitouttraj,*) ireleasestart(i),ireleaseend(i), &
86        xp1,yp1,xp2,yp2,zpoint1(i),zpoint2(i),kindz(i),npart(i)
87        write(unitouttraj,'(a20)') compoint(i)(1:20)
88       enddo
89101     format(2i5,4f11.5,2f11.3,2i5)
90
91      return
92
93998   write(*,*) ' #### FLEXPART MODEL ERROR!   THE FILE         #### '
94      write(*,*) ' #### trajectories.txt                         #### '
95      write(*,*) ' #### CANNOT BE OPENED. IF A FILE WITH THIS    #### '
96      write(*,*) ' #### NAME ALREADY EXISTS, DELETE IT AND START #### '
97      write(*,*) ' #### THE PROGRAM AGAIN.                       #### '
98      stop
99
100end subroutine openouttraj
101
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG