source: flexpart.git/src/writeheader_txt.f90

bugfixes+enhancements
Last change on this file was dba4221, checked in by Pirmin Kaufmann <pirmin.kaufmann@…>, 18 months ago

Bugfixes:

  • options/SPECIES/SPECIES_009: corrected wrong number format, replaced comma by decimal point
  • options/SPECIES/SPECIES_028: corrected wrong number format, moved sign of exponent to after the E
  • options/SPECIES/specoverview.f90: added namelist parameters that appear in SPECIES files but were missing here
  • src/FLEXPART.f90: replaced compiler-specific command line argument routines by standard Fortran intrinsic routines
  • src/FLEXPART_MPI.f90: ditto
  • src/gridcheck_ecmwf.f90: corrected handling of vertical levels when input files do not contain uppermost layers
  • src/gridcheck_nests.f90: ditto
  • src/readwind_ecmwf.f90: corrected handling of vertical levels when input files do not contain uppermost layers
  • readwind_ecmwf_mpi.f90: ditto

Code enhancements:

  • options/OUTGRID: added comments describing contents
  • options/SPECIES/SPECIES_*: aligned comments
  • options/SPECIES/specoverview.f90: removed commented lines, rectified lines indenting
  • src/FLEXPART.f90: rectified lines indenting, updated date in version string
  • src/FLEXPART_MPI.f90: ditto, and realigned code with src/FLEXPART.f90
  • src/gridcheck_*.f90: added code to write out name of file before it is opened (helps a lot when an input file causes troubles)
  • src/par_mod.f90: added comment explaining relevance of nuvzmax for GRIB input
  • src/readreleases.f90: write out warning if too few particles are used to randomize release
  • src/readspecies.f90: write out name of SPECIES file before it is read
  • src/readwind_*.f90: write out name of input file before opening it
  • src/writeheader_txt.f90: removed wrong comment
  • Property mode set to 100644
File size: 6.4 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine writeheader_txt
5
6  !*****************************************************************************
7  !                                                                            *
8  !  This routine produces a file header containing basic information on the   *
9  !  settings of the FLEXPART run.                                             *
10  !  The header file is essential and must be read in by any postprocessing    *
11  !  program before reading in the output data.                                *
12  !                                                                            *
13  !     Author: A. Stohl                                                       *
14  !                                                                            *
15  !     7 August 2002                                                          *
16  !     modified IP 2013 for text output                                       *
17  !*****************************************************************************
18  !                                                                            *
19  ! Variables:                                                                 *
20  !                                                                            *
21  ! xlon                   longitude                                           *
22  ! xl                     model x coordinate                                  *
23  ! ylat                   latitude                                            *
24  ! yl                     model y coordinate                                  *
25  !                                                                            *
26  !*****************************************************************************
27
28  use point_mod
29  use outg_mod
30  use par_mod
31  use com_mod
32
33  implicit none
34
35!  integer :: jjjjmmdd,ihmmss,i,ix,jy,j
36  integer :: jjjjmmdd,ihmmss,i,j
37  real :: xp1,yp1,xp2,yp2
38
39
40  !************************
41  ! Open header output file
42  !************************
43
44  open(unitheader,file=path(2)(1:length(2))//'header_txt', &
45       form='formatted',err=998)
46  open(unitheader_txt,file=path(2)(1:length(2))//'header_txt_releases', &
47       form='formatted',err=998)
48
49
50  ! Write the header information
51  !*****************************
52 
53  write(unitheader,*) '# ibdate,ibtime, iedate, ietime, flexversion'
54  write(unitheader,*) ibdate, ibtime, iedate, ietime, trim(flexversion)
55  !if (ldirect.eq.1) then
56  !  write(unitheader,*) ibdate,ibtime,trim(flexversion) !  'FLEXPART V9.0'
57  !else
58  !  write(unitheader,*) iedate,ietime,trim(flexversion) ! 'FLEXPART V9.0'
59  !endif
60
61  ! Write info on output interval, averaging time, sampling time
62  !*************************************************************
63 
64  write(unitheader,*) '# interval, averaging time, sampling time'
65  write(unitheader,*) loutstep,loutaver,loutsample
66
67  ! Write information on output grid setup
68  !***************************************
69 
70  write(unitheader,*) '# information on grid setup    '
71  write(unitheader,*) '#outlon0,outlat0,numxgrid,numygrid,dxout,dyout'
72  write(unitheader,*) outlon0,outlat0,numxgrid,numygrid, &
73       dxout,dyout 
74  write(unitheader,*) '# numzgrid, outheight(.) '
75  write(unitheader,*) numzgrid,(outheight(i),i=1,numzgrid)
76
77  write(unitheader,*) '# jjjjmmdd,ihmmss'
78  call caldate(bdate,jjjjmmdd,ihmmss)
79  write(unitheader,*) jjjjmmdd,ihmmss
80
81  ! Write number of species, and name for each species (+extra name for depositions)
82  ! Indicate the vertical dimension of the fields (i.e., 1 for deposition fields, numzgrid for
83  ! concentration fields
84  !*****************************************************************************
85
86  write(unitheader,*) '# information on species'
87  write(unitheader,*) '# 3*nspec,maxpointspec_act'
88  write(unitheader,*) 3*nspec,maxpointspec_act
89  write(unitheader,*) '# for nspec:'
90  write(unitheader,*) '# 1, WD_ '
91  write(unitheader,*) '# 1, DD_ '
92  write(unitheader,*) '# numzgrid,species'
93  do i=1,nspec
94    write(unitheader,*) 1,'WD_'//species(i)(1:7)
95    write(unitheader,*) 1,'DD_'//species(i)(1:7)
96    write(unitheader,*) numzgrid,species(i)
97  end do
98
99  ! Write information on release points: total number, then for each point:
100  ! start, end, coordinates, # of particles, name, mass
101  !************************************************************************
102
103
104  write(unitheader_txt,*) '# information on release points'
105  write(unitheader_txt,*) '# numpoint'
106  write(unitheader_txt,*) numpoint
107  write(unitheader_txt,*) '# for numpoint:'
108  do i=1,numpoint
109    write(unitheader_txt,*) ireleasestart(i),ireleaseend(i),kindz(i)
110    xp1=xpoint1(i)*dx+xlon0
111    yp1=ypoint1(i)*dy+ylat0
112    xp2=xpoint2(i)*dx+xlon0
113    yp2=ypoint2(i)*dy+ylat0
114    write(unitheader_txt,*) xp1,yp1,xp2,yp2,zpoint1(i),zpoint2(i)
115    write(unitheader_txt,*) npart(i),1
116    if (numpoint.le.1000) then
117      write(unitheader_txt,*) compoint(i)
118    else
119      write(unitheader_txt,*) compoint(1001)
120    endif
121    do j=1,nspec
122      write(unitheader_txt,*) xmass(i,j)
123      write(unitheader_txt,*) xmass(i,j)
124      write(unitheader_txt,*) xmass(i,j)
125    end do
126  end do
127
128  ! Write information on model switches
129  !*****************************************
130
131  write(unitheader,*) '# information on model switches'
132  write(unitheader,*) '# method,lsubgrid,lconvection, ind_source,ind_receptor'
133  write(unitheader,*) method,lsubgrid,lconvection, &
134       ind_source,ind_receptor
135
136  ! Write age class information
137  !****************************
138 
139  write(unitheader,*) '# information on age class     '
140  write(unitheader,*) nageclass,(lage(i),i=1,nageclass)
141
142
143  !Do not write topography to text output file. Keep it on the binary one
144  !********************************
145
146  !do ix=0,numxgrid-1
147  !  write(unitheader,*) (oroout(ix,jy),jy=0,numygrid-1)
148  !end do
149
150
151 
152
153
154  close(unitheader)
155  close(unitheader_txt)
156
157
158!  open(unitheader,file=path(2)(1:length(2))//'header_nml', &
159!        form='formatted',err=998)
160!  write(unitheader,NML=COMMAND)
161!  close(unitheader)
162
163  return
164
165
166998   write(*,*) ' #### FLEXPART MODEL ERROR!   THE FILE         #### '
167  write(*,*) ' #### '//path(2)(1:length(2))//'header_txt'//' #### '
168  write(*,*) ' #### CANNOT BE OPENED. IF A FILE WITH THIS    #### '
169  write(*,*) ' #### NAME ALREADY EXISTS, DELETE IT AND START #### '
170  write(*,*) ' #### THE PROGRAM AGAIN.                       #### '
171  stop
172
173end subroutine writeheader_txt
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG