source: flexpart.git/src/readageclasses.f90

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file was 92fab65, checked in by Ignacio Pisso <ip@…>, 4 years ago

add SPDX-License-Identifier to all .f90 files

  • Property mode set to 100644
File size: 4.3 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine readageclasses
5
6  !*****************************************************************************
7  !                                                                            *
8  !     This routine reads the age classes to be used for the current model    *
9  !     run.                                                                   *
10  !                                                                            *
11  !     Author: A. Stohl                                                       *
12  !     20 March 2000                                                          *
13  !     HSO, 1 July 2014                                                       *
14  !     Added optional namelist input                                          *
15  !                                                                            *
16  !*****************************************************************************
17  !                                                                            *
18  ! Variables:                                                                 *
19  !                                                                            *
20  ! Constants:                                                                 *
21  !                                                                            *
22  !*****************************************************************************
23
24  use par_mod
25  use com_mod
26
27  implicit none
28
29  integer :: i
30
31  ! namelist help variables
32  integer :: readerror
33
34  ! namelist declaration
35  namelist /ageclass/ &
36    nageclass, &
37    lage
38
39  nageclass=-1 ! preset to negative value to identify failed namelist input
40
41  ! If age spectra calculation is switched off, set number of age classes
42  ! to 1 and maximum age to a large number
43  !**********************************************************************
44
45  if (lagespectra.ne.1) then
46    nageclass=1
47    lage(nageclass)=999999999
48    return
49  endif
50
51  ! If age spectra claculation is switched on,
52  ! open the AGECLASSSES file and read user options
53  !************************************************
54
55  open(unitageclasses,file=path(1)(1:length(1))//'AGECLASSES',form='formatted',status='old',err=999)
56
57  ! try to read in as a namelist
58  read(unitageclasses,ageclass,iostat=readerror)
59  close(unitageclasses)
60
61  if ((nageclass.lt.0).or.(readerror.ne.0)) then
62    open(unitageclasses,file=path(1)(1:length(1))//'AGECLASSES',status='old',err=999)
63    do i=1,13
64      read(unitageclasses,*)
65    end do
66    read(unitageclasses,*) nageclass
67    read(unitageclasses,*) lage(1)
68    do i=2,nageclass
69      read(unitageclasses,*) lage(i)
70    end do
71    close(unitageclasses)
72  endif
73
74  ! write ageclasses file in namelist format to output directory if requested
75  if (nmlout.and.lroot) then
76    open(unitageclasses,file=path(2)(1:length(2))//'AGECLASSES.namelist',err=1000)
77    write(unitageclasses,nml=ageclass)
78    close(unitageclasses)
79  endif
80
81  if (nageclass.gt.maxageclass) then
82    write(*,*) ' #### FLEXPART MODEL ERROR! NUMBER OF AGE     #### '
83    write(*,*) ' #### CLASSES GREATER THAN MAXIMUM ALLOWED.   #### '
84    write(*,*) ' #### CHANGE SETTINGS IN FILE AGECLASSES OR   #### '
85    write(*,*) ' #### RECOMPILE WITH LARGER MAXAGECLASS IN    #### '
86    write(*,*) ' #### FILE PAR_MOD.                        #### '
87    stop
88  endif
89
90  if (lage(1).le.0) then
91    write(*,*) ' #### FLEXPART MODEL ERROR! AGE OF FIRST      #### '
92    write(*,*) ' #### CLASS MUST BE GREATER THAN ZERO. CHANGE #### '
93    write(*,*) ' #### SETTINGS IN FILE AGECLASSES.            #### '
94    stop
95  endif
96
97  do i=2,nageclass
98    if (lage(i).le.lage(i-1)) then
99      write(*,*) ' #### FLEXPART MODEL ERROR! AGE CLASSES     #### '
100      write(*,*) ' #### MUST BE GIVEN IN TEMPORAL ORDER.      #### '
101      write(*,*) ' #### CHANGE SETTINGS IN FILE AGECLASSES.   #### '
102      stop
103    endif
104  end do
105
106  return
107
108999   write(*,*) ' #### FLEXPART MODEL ERROR! FILE "AGECLASSES" #### '
109  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
110  write(*,'(a)') path(1)(1:length(1))
111  stop
112
1131000  write(*,*) ' #### FLEXPART MODEL ERROR! FILE "AGECLASSES" #### '
114  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
115  write(*,'(a)') path(2)(1:length(2))
116  stop
117
118
119end subroutine readageclasses
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG