source: flexpart.git/src/readageclasses.f90 @ d7935de

univie
Last change on this file since d7935de was d7935de, checked in by pesei <petra seibert at univie ac at>, 6 years ago

modify most input read subroutines

changed some variable names (mostly for I-N reasons)
includes two names appearing also in timemanager, com_mod
corrected a few mistakes
simplified some parts of code
changed options/RELEASES which is in nml fmt correspondingly

  • Property mode set to 100644
File size: 6.1 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 readageclasses
23
24  !*****************************************************************************
25  !                                                                            *
26  !     This routine reads the age classes to be used for the current model    *
27  !     run.                                                                   *
28  !                                                                            *
29  !     Author: A. Stohl                                                       *
30  !     20 March 2000                                                          *
31  !
32  !     HSO, 1 July 2014                                                       *
33  !     Added optional namelist input                                          *
34  !                                                                            *
35  !     PS, 6/2015-9/2018 some variable names changed as in readreleases.f90   *
36  !       catch nageclass>maxage properly                                      *
37  !                                                                            *
38  !*****************************************************************************
39  !                                                                            *
40  ! Variables:                                                                 *
41  !                                                                            *
42  ! Constants:                                                                 *
43  !                                                                            *
44  !*****************************************************************************
45
46  use par_mod
47  use com_mod
48
49  implicit none
50
51  integer :: i
52
53  ! namelist aux variables
54  integer :: ios
55
56  ! namelist declaration
57  namelist /nml_ageclass/ &
58    nageclass, &
59    lage
60
61  nageclass=-1 ! preset to negative value to identify failed namelist input
62
63  ! If age spectra calculation is switched off, set number of age classes
64  ! to 1 and maximum age to a large number
65  !**********************************************************************
66
67  if (lagespectra.ne.1) then
68    nageclass=1
69    lage(nageclass)=999999999
70    return
71  endif
72
73  ! If age spectra claculation is switched on,
74  ! open the AGECLASSSES file and read user options
75  !************************************************
76
77  open(unitageclasses,file=path(1)(1:length(1))//'AGECLASSES', &
78    form='formatted',status='old',err=999)
79
80  ! try to read in as a namelist
81  read(unitageclasses, nml_ageclass, iostat=ios)
82  close(unitageclasses)
83
84  if (ios .ne. 0) then ! failed to read nml, assume simple text
85    open(unitageclasses,file=path(1)(1:length(1))// &
86      'AGECLASSES',status='old',err=999)
87    call skplin(13,unitageclasses)
88    read(unitageclasses,*) nageclass ! number of classes
89    if (nageclass.gt.maxageclass) goto 1001
90    do i=1,nageclass
91      read(unitageclasses,*) lage(i) ! max age per classes
92    end do
93    close(unitageclasses)
94  endif
95
96  if (nageclass.lt.1) goto 1002
97
98  ! write ageclasses file in namelist format to output directory if requested
99  if (nmlout.and.lroot) then
100    open(unitageclasses,file=path(2)(1:length(2))//'AGECLASSES.namelist', &
101      err=1000)
102    write(unitageclasses,nml=nml_ageclass)
103    close(unitageclasses)
104  endif
105
106  if (lage(1).le.0) then
107    write(*,*) ' #### FLEXPART MODEL ERROR! AGE OF FIRST      #### '
108    write(*,*) ' #### CLASS MUST BE GREATER THAN ZERO. CHANGE #### '
109    write(*,*) ' #### SETTINGS IN FILE AGECLASSES.            #### '
110    stop
111  endif
112
113  do i=2,nageclass
114    if (lage(i).le.lage(i-1)) then
115      write(*,*) ' #### FLEXPART MODEL ERROR! AGE CLASSES     #### '
116      write(*,*) ' #### MUST BE GIVEN IN TEMPORAL ORDER.      #### '
117      write(*,*) ' #### CHANGE SETTINGS IN FILE AGECLASSES.   #### '
118      stop
119    endif
120  end do
121
122  return
123
124999   write(*,*) ' #### FLEXPART MODEL ERROR! FILE "AGECLASSES" #### '
125  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
126  write(*,'(a)') trim(path(1))
127  stop
128
1291000  write(*,*) ' #### FLEXPART MODEL ERROR! FILE "AGECLASSES" #### '
130  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
131  write(*,'(a)') path(2)(1:length(2))
132  stop
133
1341001 continue
135    write(*,*) ' #### FLEXPART MODEL ERROR! NUMBER OF AGE     #### '
136    write(*,*) ' #### CLASSES GREATER THAN MAXIMUM ALLOWED.   #### '
137    write(*,*) ' #### CHANGE SETTINGS IN FILE AGECLASSES OR   #### '
138    write(*,*) ' #### RECOMPILE WITH LARGER MAXAGECLASS IN    #### '
139    write(*,*) ' #### FILE PAR_MOD.                           #### '
140    stop
141
1421002 continue
143    write(*,*) ' #### FLEXPART MODEL ERROR! NUMBER OF AGE     #### '
144    write(*,*) ' #### CLASSES < 1                             #### '
145    write(*,*) ' #### CHANGE SETTINGS IN FILE AGECLASSES      #### '
146    stop
147
148end subroutine readageclasses
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG