source: branches/flexpart91_hasod/src_parallel/readageclasses.f90 @ 10

Last change on this file since 10 was 10, checked in by hasod, 11 years ago

ADD: namelist input implemented for all common input files

  • Property svn:executable set to *
File size: 5.0 KB
RevLine 
[8]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                                                          *
[10]31  !     HSO, 14 August 2013
32  !     Added optional namelist input
[8]33  !                                                                            *
34  !*****************************************************************************
35  !                                                                            *
36  ! Variables:                                                                 *
37  !                                                                            *
38  ! Constants:                                                                 *
39  !                                                                            *
40  !*****************************************************************************
41
42  use par_mod
43  use com_mod
44
45  implicit none
46
47  integer :: i
48
[10]49  ! namelist help variables
50  integer :: readerror
[8]51
[10]52  ! namelist declaration
53  namelist /ageclass/ &
54    nageclass, &
55    lage
56
57  nageclass=-1 ! preset to negative value to identify failed namelist input
58
[8]59  ! If age spectra calculation is switched off, set number of age classes
60  ! to 1 and maximum age to a large number
61  !**********************************************************************
62
63  if (lagespectra.ne.1) then
64    nageclass=1
65    lage(nageclass)=999999999
66    return
67  endif
68
69  ! If age spectra claculation is switched on,
70  ! open the AGECLASSSES file and read user options
71  !************************************************
72
73  open(unitageclasses,file=path(1)(1:length(1))//'AGECLASSES', &
74       status='old',err=999)
75
[10]76  ! try to read in as a namelist
77  read(unitageclasses,ageclass,iostat=readerror)
[8]78
[10]79  if ((nageclass.lt.0).or.(readerror.ne.0)) then
80    rewind(unitageclasses)
81    do i=1,13
82      read(unitageclasses,*)
83    end do
84    read(unitageclasses,*) nageclass
85    read(unitageclasses,*) lage(1)
86    do i=2,nageclass
87      read(unitageclasses,*) lage(i)
88    end do
89  endif
[8]90
[10]91  close(unitageclasses)
92
[8]93  if (nageclass.gt.maxageclass) then
94    write(*,*) ' #### FLEXPART MODEL ERROR! NUMBER OF AGE     #### '
95    write(*,*) ' #### CLASSES GREATER THAN MAXIMUM ALLOWED.   #### '
96    write(*,*) ' #### CHANGE SETTINGS IN FILE AGECLASSES OR   #### '
97    write(*,*) ' #### RECOMPILE WITH LARGER MAXAGECLASS IN    #### '
98    write(*,*) ' #### FILE PAR_MOD.                        #### '
99    stop
100  endif
101
102  if (lage(1).le.0) then
103    write(*,*) ' #### FLEXPART MODEL ERROR! AGE OF FIRST      #### '
104    write(*,*) ' #### CLASS MUST BE GREATER THAN ZERO. CHANGE #### '
105    write(*,*) ' #### SETTINGS IN FILE AGECLASSES.            #### '
106    stop
107  endif
108
109  do i=2,nageclass
110    if (lage(i).le.lage(i-1)) then
111      write(*,*) ' #### FLEXPART MODEL ERROR! AGE CLASSES     #### '
112      write(*,*) ' #### MUST BE GIVEN IN TEMPORAL ORDER.      #### '
113      write(*,*) ' #### CHANGE SETTINGS IN FILE AGECLASSES.   #### '
114      stop
115    endif
116  end do
117
118  return
119
120999   write(*,*) ' #### FLEXPART MODEL ERROR! FILE "AGECLASSES" #### '
121  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
122  write(*,'(a)') path(1)(1:length(1))
123  stop
124
125end subroutine readageclasses
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG