Ignore:
Timestamp:
Aug 15, 2013, 3:23:48 PM (11 years ago)
Author:
hasod
Message:

ADD: namelist input implemented for all common input files

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/flexpart91_hasod/src_parallel/readageclasses.f90

    r8 r10  
    2828  !                                                                            *
    2929  !     Author: A. Stohl                                                       *
    30   !                                                                            *
    3130  !     20 March 2000                                                          *
     31  !     HSO, 14 August 2013
     32  !     Added optional namelist input
    3233  !                                                                            *
    3334  !*****************************************************************************
     
    4647  integer :: i
    4748
     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
    4858
    4959  ! If age spectra calculation is switched off, set number of age classes
    5060  ! to 1 and maximum age to a large number
    5161  !**********************************************************************
    52 
    5362
    5463  if (lagespectra.ne.1) then
     
    5766    return
    5867  endif
    59 
    6068
    6169  ! If age spectra claculation is switched on,
     
    6674       status='old',err=999)
    6775
    68   do i=1,13
    69     read(unitageclasses,*)
    70   end do
    71   read(unitageclasses,*) nageclass
     76  ! try to read in as a namelist
     77  read(unitageclasses,ageclass,iostat=readerror)
    7278
     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
     90
     91  close(unitageclasses)
    7392
    7493  if (nageclass.gt.maxageclass) then
     
    81100  endif
    82101
    83   read(unitageclasses,*) lage(1)
    84102  if (lage(1).le.0) then
    85103    write(*,*) ' #### FLEXPART MODEL ERROR! AGE OF FIRST      #### '
     
    90108
    91109  do i=2,nageclass
    92     read(unitageclasses,*) lage(i)
    93110    if (lage(i).le.lage(i-1)) then
    94111      write(*,*) ' #### FLEXPART MODEL ERROR! AGE CLASSES     #### '
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG