Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/readageclasses.f90

    r27 r4  
    2828  !                                                                            *
    2929  !     Author: A. Stohl                                                       *
     30  !                                                                            *
    3031  !     20 March 2000                                                          *
    31   !     HSO, 1 July 2014                                                       *
    32   !     Added optional namelist input                                          *
    3332  !                                                                            *
    3433  !*****************************************************************************
     
    4746  integer :: i
    4847
    49   ! namelist help variables
    50   integer :: readerror
    51 
    52   ! namelist declaration
    53   namelist /ageclass/ &
    54     nageclass, &
    55     lage
    56 
    57   nageclass=-1 ! preset to negative value to identify failed namelist input
    5848
    5949  ! If age spectra calculation is switched off, set number of age classes
     
    6757  endif
    6858
     59
    6960  ! If age spectra claculation is switched on,
    7061  ! open the AGECLASSSES file and read user options
    7162  !************************************************
    7263
    73   open(unitageclasses,file=path(1)(1:length(1))//'AGECLASSES',form='formatted',status='old',err=999)
     64  open(unitageclasses,file=path(1)(1:length(1))//'AGECLASSES', &
     65       status='old',err=999)
    7466
    75   ! try to read in as a namelist
    76   read(unitageclasses,ageclass,iostat=readerror)
    77   close(unitageclasses)
     67  do i=1,13
     68    read(unitageclasses,*)
     69  end do
     70  read(unitageclasses,*) nageclass
    7871
    79   if ((nageclass.lt.0).or.(readerror.ne.0)) then
    80     open(unitageclasses,file=path(1)(1:length(1))//'AGECLASSES',status='old',err=999)
    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     close(unitageclasses)
    90   endif
    91 
    92   ! write ageclasses file in namelist format to output directory if requested
    93   if (nmlout.eqv..true.) then
    94     open(unitageclasses,file=path(2)(1:length(2))//'AGECLASSES.namelist',err=1000)
    95     write(unitageclasses,nml=ageclass)
    96     close(unitageclasses)
    97   endif
    9872
    9973  if (nageclass.gt.maxageclass) then
     
    10680  endif
    10781
     82  read(unitageclasses,*) lage(1)
    10883  if (lage(1).le.0) then
    10984    write(*,*) ' #### FLEXPART MODEL ERROR! AGE OF FIRST      #### '
     
    11489
    11590  do i=2,nageclass
     91    read(unitageclasses,*) lage(i)
    11692    if (lage(i).le.lage(i-1)) then
    11793      write(*,*) ' #### FLEXPART MODEL ERROR! AGE CLASSES     #### '
     
    129105  stop
    130106
    131 1000  write(*,*) ' #### FLEXPART MODEL ERROR! FILE "AGECLASSES" #### '
    132   write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
    133   write(*,'(a)') path(2)(1:length(2))
    134   stop
    135 
    136 
    137107end subroutine readageclasses
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG