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