Ignore:
Timestamp:
Jul 3, 2014, 2:55:50 PM (10 years ago)
Author:
hasod
Message:
  • Implemented optional namelist input for COMMAND, RELEASES, SPECIES, AGECLASSES,OUTGRID,OUTGRID_NEST,RECEPTORS
  • Implemented com_mod switch nmlout to write input files as namelist to the output directory (.true. by default)
  • Proposed updated startup and runtime output (may change back to previous info if desired)
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/readageclasses.f90

    r4 r27  
    2828  !                                                                            *
    2929  !     Author: A. Stohl                                                       *
    30   !                                                                            *
    3130  !     20 March 2000                                                          *
     31  !     HSO, 1 July 2014                                                       *
     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
     
    5767  endif
    5868
    59 
    6069  ! If age spectra claculation is switched on,
    6170  ! open the AGECLASSSES file and read user options
    6271  !************************************************
    6372
    64   open(unitageclasses,file=path(1)(1:length(1))//'AGECLASSES', &
    65        status='old',err=999)
     73  open(unitageclasses,file=path(1)(1:length(1))//'AGECLASSES',form='formatted',status='old',err=999)
    6674
    67   do i=1,13
    68     read(unitageclasses,*)
    69   end do
    70   read(unitageclasses,*) nageclass
     75  ! try to read in as a namelist
     76  read(unitageclasses,ageclass,iostat=readerror)
     77  close(unitageclasses)
    7178
     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
    7298
    7399  if (nageclass.gt.maxageclass) then
     
    80106  endif
    81107
    82   read(unitageclasses,*) lage(1)
    83108  if (lage(1).le.0) then
    84109    write(*,*) ' #### FLEXPART MODEL ERROR! AGE OF FIRST      #### '
     
    89114
    90115  do i=2,nageclass
    91     read(unitageclasses,*) lage(i)
    92116    if (lage(i).le.lage(i-1)) then
    93117      write(*,*) ' #### FLEXPART MODEL ERROR! AGE CLASSES     #### '
     
    105129  stop
    106130
     1311000  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
    107137end subroutine readageclasses
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG