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

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

Added parallel version of Flexpart91

  • Property svn:executable set to *
File size: 4.6 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  !                                                                            *
31  !     20 March 2000                                                          *
32  !                                                                            *
33  !*****************************************************************************
34  !                                                                            *
35  ! Variables:                                                                 *
36  !                                                                            *
37  ! Constants:                                                                 *
38  !                                                                            *
39  !*****************************************************************************
40
41  use par_mod
42  use com_mod
43
44  implicit none
45
46  integer :: i
47
48
49  ! If age spectra calculation is switched off, set number of age classes
50  ! to 1 and maximum age to a large number
51  !**********************************************************************
52
53
54  if (lagespectra.ne.1) then
55    nageclass=1
56    lage(nageclass)=999999999
57    return
58  endif
59
60
61  ! If age spectra claculation is switched on,
62  ! open the AGECLASSSES file and read user options
63  !************************************************
64
65  open(unitageclasses,file=path(1)(1:length(1))//'AGECLASSES', &
66       status='old',err=999)
67
68  do i=1,13
69    read(unitageclasses,*)
70  end do
71  read(unitageclasses,*) nageclass
72
73
74  if (nageclass.gt.maxageclass) then
75    write(*,*) ' #### FLEXPART MODEL ERROR! NUMBER OF AGE     #### '
76    write(*,*) ' #### CLASSES GREATER THAN MAXIMUM ALLOWED.   #### '
77    write(*,*) ' #### CHANGE SETTINGS IN FILE AGECLASSES OR   #### '
78    write(*,*) ' #### RECOMPILE WITH LARGER MAXAGECLASS IN    #### '
79    write(*,*) ' #### FILE PAR_MOD.                        #### '
80    stop
81  endif
82
83  read(unitageclasses,*) lage(1)
84  if (lage(1).le.0) then
85    write(*,*) ' #### FLEXPART MODEL ERROR! AGE OF FIRST      #### '
86    write(*,*) ' #### CLASS MUST BE GREATER THAN ZERO. CHANGE #### '
87    write(*,*) ' #### SETTINGS IN FILE AGECLASSES.            #### '
88    stop
89  endif
90
91  do i=2,nageclass
92    read(unitageclasses,*) lage(i)
93    if (lage(i).le.lage(i-1)) then
94      write(*,*) ' #### FLEXPART MODEL ERROR! AGE CLASSES     #### '
95      write(*,*) ' #### MUST BE GIVEN IN TEMPORAL ORDER.      #### '
96      write(*,*) ' #### CHANGE SETTINGS IN FILE AGECLASSES.   #### '
97      stop
98    endif
99  end do
100
101  return
102
103999   write(*,*) ' #### FLEXPART MODEL ERROR! FILE "AGECLASSES" #### '
104  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
105  write(*,'(a)') path(1)(1:length(1))
106  stop
107
108end subroutine readageclasses
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG