source: flexpart.git/src/readageclasses.f90 @ 3481cc1

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

move license from headers to a different file

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