Changeset b4d29ce in flexpart.git for src/readcommand.f90


Ignore:
Timestamp:
Jul 3, 2014, 2:55:50 PM (10 years ago)
Author:
Harald Sodemann <harald.sodemann@…>
Branches:
master, 10.4.1_pesei, FPv9.3.1, FPv9.3.1b_testing, FPv9.3.2, GFS_025, NetCDF, bugfixes+enhancements, deposition, dev, fp9.3.1-20161214-nc4, grib2nc4_repair, inputlist, laptop, release-10, release-10.4.1, scaling-bug, svn-petra, svn-trunk, univie
Children:
4b093cc, 75dfd42, 326b31b
Parents:
87910af
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)

git-svn-id: http://flexpart.flexpart.eu:8088/svn/FlexPart90/trunk@27 ef8cc7e1-21b7-489e-abab-c1baa636049d

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/readcommand.f90

    r4fbe7a5 rb4d29ce  
    2929  !                                                                            *
    3030  !     18 May 1996                                                            *
     31  !     HSO, 1 July 2014                                                       *
     32  !     Added optional namelist input                                          *
    3133  !                                                                            *
    3234  !*****************************************************************************
     
    8082  character(len=50) :: line
    8183  logical :: old
    82   logical :: nml_COMMAND=.true. , nmlout=.true.  !.false.
    8384  integer :: readerror
    8485
     
    111112
    112113  ! Presetting namelist command
    113   ldirect=1
     114  ldirect=0
    114115  ibdate=20000101
    115116  ibtime=0
     
    142143  ! Namelist input first: try to read as namelist file
    143144  !**************************************************************************
    144   open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old', &
    145          form='formatted',iostat=readerror)
    146    ! If fail, check if file does not exist
    147    if (readerror.ne.0) then
    148      print*,'***ERROR: file COMMAND not found in '
    149      print*, path(1)(1:length(1))//'COMMAND'
    150      print*, 'Check your pathnames file.'
    151      stop
    152    endif
    153 
    154    ! print error code
    155    !write(*,*) 'readcommand > readerror open=' , readerror
    156    !probe first line 
    157    read (unitcommand,901) line
    158    !write(*,*) 'index(line,COMMAND) =', index(line,'COMMAND')
    159 
     145  open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old',form='formatted',err=999)
     146
     147  ! try namelist input (default)
     148  read(unitcommand,command,iostat=readerror)
     149  close(unitcommand)
     150
     151  ! distinguish namelist from fixed text input
     152  if ((readerror.ne.0).or.(ldirect.eq.0)) then ! parse as text file format
    160153 
    161    !default is namelist input
    162    ! distinguish namelist from fixed text input
    163    if (index(line,'COMMAND') .eq. 0) then
    164    nml_COMMAND = .false.
    165    !write(*,*) 'COMMAND file does not contain the string COMMAND in the first line'     
    166    endif
    167    !write(*,*) 'readcommand > read as namelist? ' , nml_COMMAND
    168    rewind(unitcommand)
    169    read(unitcommand,command,iostat=readerror)
    170 
    171   close(unitcommand)
    172 
    173   !write(*,*) 'readcommand > readerror read=' , readerror
    174   ! If error in namelist format, try to open with old input code
    175   ! if (readerror.ne.0) then
    176   ! IP 21/5/2014 the previous line cause the old long format
    177   ! to be confused with namelist input
    178  
    179   ! use text input
    180   if (nml_COMMAND .eqv. .false.) then
    181 
    182     open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old', &
    183          err=999)
     154    open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old', err=999)
    184155
    185156    ! Check the format of the COMMAND file (either in free format,
     
    193164    if (index(line,'LDIRECT') .eq. 0) then
    194165      old = .false.
    195     !write(*,*) 'readcommand old short'
     166      write(*,*) 'COMMAND in old short format, please update to namelist format'
    196167    else
    197168      old = .true.
    198     !write(*,*) 'readcommand old long'
     169      write(*,*) 'COMMAND in old long format, please update to namelist format'
    199170    endif
    200171    rewind(unitcommand)
     
    206177    call skplin(7,unitcommand)
    207178    if (old) call skplin(1,unitcommand)
    208 
    209179    read(unitcommand,*) ldirect
    210180    if (old) call skplin(3,unitcommand)
     
    265235    write(unitcommand,nml=command)
    266236    close(unitcommand)
    267      ! open(unitheader,file=path(2)(1:length(2))//'header_nml',status='new',err=999)
    268      ! write(unitheader,NML=COMMAND)
    269      !close(unitheader)
    270237  endif
    271238
     
    616583
    6175841000   write(*,*) ' #### FLEXPART MODEL ERROR! FILE "COMMAND"    #### '
    618        write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
    619         write(*,'(a)') path(2)(1:length(1))
    620         stop
     585  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
     586  write(*,'(a)') path(2)(1:length(1))
     587  stop
    621588end subroutine readcommand
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG