source: branches/petra/src/writeheader_txt.f90 @ 36

Last change on this file since 36 was 36, checked in by pesei, 9 years ago

Implement switch for incremental deposition, see ticket:113 and many small changes, see changelog.txt

File size: 8.0 KB
Line 
1!**********************************************************************
2! Copyright 1998-2015                                                 *
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 writeheader_txt
23
24  !*****************************************************************************
25  !                                                                            *
26  !  This routine produces a file header containing basic information on the   *
27  !  settings of the FLEXPART run.                                             *
28  !  The header file is essential and must be read in by any postprocessing    *
29  !  program before reading in the output data.                                *
30  !                                                                            *
31  !     Author: A. Stohl                                                       *
32  !                                                                            *
33  !     7 August 2002                                                          *
34  !                                                                            *
35  !     2013, IP: IP, text            output                                   *
36  !     2/2015, PS: version string length written, enclose version string in '
37  !                 write out ldep_incr
38  !
39  !*****************************************************************************
40  !                                                                            *
41  ! Variables:                                                                 *
42  !                                                                            *
43  ! xlon                   longitude                                           *
44  ! xl                     model x coordinate                                  *
45  ! ylat                   latitude                                            *
46  ! yl                     model y coordinate                                  *
47  !                                                                            *
48  !*****************************************************************************
49
50  use point_mod
51  use outg_mod
52  use par_mod
53  use com_mod
54
55  implicit none
56
57  integer :: jjjjmmdd,ihmmss,i,ix,jy,j
58  real :: xp1,yp1,xp2,yp2
59
60
61  !************************
62  ! Open header output file
63  !************************
64
65  open(unitheader,file=path(2)(1:length(2))//'header.txt', &
66       form='formatted',err=998)
67  open(unitheader_rel,file=path(2)(1:length(2))//'header_releases.txt', &
68       form='formatted',err=998)
69
70
71  ! Write the header information
72  !*****************************
73 
74  write(unitheader,*) '# ibdate,ibtime, iedate, ietime, len(flexversion), flexversion'
75  write(unitheader,*) ibdate, ibtime, iedate, ietime, len_trim(flexversion), "'"//trim(flexversion)//"'" !  'FLEXPART V9.0'
76  !if (ldirect.eq.1) then
77  !  write(unitheader,*) ibdate,ibtime,trim(flexversion) !  'FLEXPART V9.0'
78  !else
79  !  write(unitheader,*) iedate,ietime,trim(flexversion) ! 'FLEXPART V9.0'
80  !endif
81
82  ! Write info on output interval, averaging time, sampling time
83  !*************************************************************
84 
85  write(unitheader,*) '# interval, averaging time, sampling time'
86  write(unitheader,*) loutstep,loutaver,loutsample
87
88  ! Write information on output grid setup
89  !***************************************
90 
91  write(unitheader,*) '# information on grid setup    '
92  write(unitheader,*) '#outlon0,outlat0,numxgrid,numygrid,dxout,dyout'
93  write(unitheader,*) outlon0,outlat0,numxgrid,numygrid, dxout,dyout
94  write(unitheader,*) '# numzgrid, outheight(.) '
95  write(unitheader,*) numzgrid,(outheight(i),i=1,numzgrid)
96
97  write(unitheader,*) '# jjjjmmdd,ihmmss'
98  call caldate(bdate,jjjjmmdd,ihmmss)
99  write(unitheader,*) jjjjmmdd,ihmmss
100
101  ! Write number of species, and name for each species (+extra name for depositions)
102  ! Indicate the vertical dimension of the fields (i.e., 1 for deposition fields, numzgrid for
103  ! concentration fields
104  !*****************************************************************************
105
106  write(unitheader,*) '# information on species'
107  write(unitheader,*) '# 3*nspec,maxpointspec_act'
108  write(unitheader,*) 3*nspec,maxpointspec_act
109  write(unitheader,*) '# for nspec:'
110  write(unitheader,*) '# 1, WD_ '
111  write(unitheader,*) '# 1, DD_ '
112  write(unitheader,*) '# numzgrid,species'
113  do i=1,nspec
114    write(unitheader,*) 1,'WD_'//species(i)(1:7)
115    write(unitheader,*) 1,'DD_'//species(i)(1:7)
116    write(unitheader,*) numzgrid,species(i)
117  end do
118
119  ! Write information on release points: total number, then for each point:
120  ! start, end, coordinates, # of particles, name, mass
121  !************************************************************************
122
123
124  write(unitheader_rel,*) '# information on release points'
125  write(unitheader_rel,*) '# numpoint'
126  write(unitheader_rel,*) numpoint
127  write(unitheader_rel,*) '# for numpoint:'
128  do i=1,numpoint
129    write(unitheader_rel,*) ireleasestart(i),ireleaseend(i),kindz(i)
130    xp1=xpoint1(i)*dx+xlon0
131    yp1=ypoint1(i)*dy+ylat0
132    xp2=xpoint2(i)*dx+xlon0
133    yp2=ypoint2(i)*dy+ylat0
134    write(unitheader_rel,*) xp1,yp1,xp2,yp2,zpoint1(i),zpoint2(i)
135    write(unitheader_rel,*) npart(i),1
136    if (numpoint.le.1000) then
137      write(unitheader_rel,*) compoint(i)
138    else
139      write(unitheader_rel,*) compoint(1001)
140    endif
141    do j=1,nspec
142      write(unitheader_rel,*) xmass(i,j)
143      write(unitheader_rel,*) xmass(i,j)
144      write(unitheader_rel,*) xmass(i,j)
145    end do
146  end do
147
148  ! Write information on model switches
149  !*****************************************
150
151  write(unitheader,*) '# information on model switches'
152  write(unitheader,*) '# method,lsubgrid,lconvection, ind_source,ind_receptor'
153  write(unitheader,*) method,lsubgrid,lconvection,ind_source,ind_receptor
154
155  ! Write age class information
156  !****************************
157 
158  write(unitheader,*) '# information on age class     '
159  write(unitheader,*) nageclass,(lage(i),i=1,nageclass)
160
161
162  !Do not write topography to text output file. Keep it on the binary one
163  !********************************
164  !do ix=0,numxgrid-1
165  !  write(unitheader,*) (oroout(ix,jy),jy=0,numygrid-1)
166  !end do
167
168  ! Write deposition type
169  !***********************
170 
171  write(unitheader,*) '# information on incremental / accum. deposition'
172  write(unitheader,*) ldep_incr
173
174  close(unitheader)
175  close(unitheader_rel)
176
177!  open(unitheader,file=path(2)(1:length(2))//'header_nml', &
178!        form='formatted',err=998)
179!  write(unitheader,NML=COMMAND)
180!  close(unitheader)
181
182  return
183
184
185998 continue
186  write(*,*) ' #### FLEXPART MODEL ERROR!   THE FILE         #### '
187  write(*,*) ' #### '//path(2)(1:length(2))//'header_txt'//' #### '
188  write(*,*) ' #### CANNOT BE OPENED. IF A FILE WITH THIS    #### '
189  write(*,*) ' #### NAME ALREADY EXISTS, DELETE IT AND START #### '
190  write(*,*) ' #### THE PROGRAM AGAIN.                       #### '
191  stop
192
193end subroutine writeheader_txt
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG