Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/readcommand.f90

    r20 r30  
    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 :: nmlout=.true. !.false.
    8384  integer :: readerror
    8485
    8586  namelist /command/ &
    86     ldirect, &
    87     ibdate,ibtime, &
    88     iedate,ietime, &
    89     loutstep, &
    90     loutaver, &
    91     loutsample, &
    92     itsplit, &
    93     lsynctime, &
    94     ctl, &
    95     ifine, &
    96     iout, &
    97     ipout, &
    98     lsubgrid, &
    99     lconvection, &
    100     lagespectra, &
    101     ipin, &
    102     ioutputforeachrelease, &
    103     iflux, &
    104     mdomainfill, &
    105     ind_source, &
    106     ind_receptor, &
    107     mquasilag, &
    108     nested_output, &
    109     linit_cond, &
    110     surf_only   
     87  ldirect, &
     88  ibdate,ibtime, &
     89  iedate,ietime, &
     90  loutstep, &
     91  loutaver, &
     92  loutsample, &
     93  itsplit, &
     94  lsynctime, &
     95  ctl, &
     96  ifine, &
     97  iout, &
     98  ipout, &
     99  lsubgrid, &
     100  lconvection, &
     101  lagespectra, &
     102  ipin, &
     103  ioutputforeachrelease, &
     104  iflux, &
     105  mdomainfill, &
     106  ind_source, &
     107  ind_receptor, &
     108  mquasilag, &
     109  nested_output, &
     110  linit_cond, &
     111  lnetcdfout, &
     112  surf_only   
    111113
    112114  ! Presetting namelist command
    113   ldirect=1
     115  ldirect=0
    114116  ibdate=20000101
    115117  ibtime=0
     
    137139  nested_output=0
    138140  linit_cond=0
     141  lnetcdfout=0
    139142  surf_only=0
    140143
     
    142145  ! Namelist input first: try to read as namelist file
    143146  !**************************************************************************
    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    
    149     print*,'***ERROR: file COMMAND not found in '
    150     print*, path(1)(1:length(1))//'COMMAND'
    151     print*, 'Check your pathnames file.'
    152     stop
    153 
    154   endif
    155 
     147  open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old',form='formatted',err=999)
     148
     149  ! try namelist input (default)
    156150  read(unitcommand,command,iostat=readerror)
    157151  close(unitcommand)
    158152
    159   ! If error in namelist format, try to open with old input code
    160   if (readerror.ne.0) then
    161 
    162     open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old', &
    163          err=999)
     153  ! distinguish namelist from fixed text input
     154  if ((readerror.ne.0).or.(ldirect.eq.0)) then ! parse as text file format
     155 
     156    open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old', err=999)
    164157
    165158    ! Check the format of the COMMAND file (either in free format,
     
    173166    if (index(line,'LDIRECT') .eq. 0) then
    174167      old = .false.
     168      write(*,*) 'COMMAND in old short format, please update to namelist format'
    175169    else
    176170      old = .true.
     171      write(*,*) 'COMMAND in old long format, please update to namelist format'
    177172    endif
    178173    rewind(unitcommand)
    179174
     175
    180176    ! Read parameters
    181177    !****************
     
    183179    call skplin(7,unitcommand)
    184180    if (old) call skplin(1,unitcommand)
    185 
    186181    read(unitcommand,*) ldirect
    187182    if (old) call skplin(3,unitcommand)
     
    231226    if (old) call skplin(3,unitcommand)
    232227    read(unitcommand,*) linit_cond
     228    if (old) call skplin(3,unitcommand)
     229    read(unitcommand,*) surf_only
    233230    close(unitcommand)
    234231
     
    237234  ! write command file in namelist format to output directory if requested
    238235  if (nmlout.eqv..true.) then
    239     !open(unitcommand,file=path(2)(1:length(2))//'COMMAND.namelist.out',status='new',err=1000)
    240236    open(unitcommand,file=path(2)(1:length(2))//'COMMAND.namelist',err=1000)
    241237    write(unitcommand,nml=command)
    242238    close(unitcommand)
    243      ! open(unitheader,file=path(2)(1:length(2))//'header_nml',status='new',err=999)
    244      ! write(unitheader,NML=COMMAND)
    245      !close(unitheader)
    246239  endif
    247240
     
    353346  endif
    354347
     348!  check for netcdf output switch (use for non-namelist input only!)
     349  if (iout.ge.8) then
     350     lnetcdfout = 1
     351     iout = iout - 8
     352#ifndef NETCDF_OUTPUT
     353     print*,'ERROR: netcdf output not activated during compile time but used in COMMAND file!'
     354     print*,'Please recompile with netcdf library or use standard output format.'
     355     stop
     356#endif
     357  endif
     358
    355359  ! Check whether a valid option for gridded model output has been chosen
    356360  !**********************************************************************
     
    358362  if ((iout.lt.1).or.(iout.gt.5)) then
    359363    write(*,*) ' #### FLEXPART MODEL ERROR! FILE COMMAND:     #### '
    360     write(*,*) ' #### IOUT MUST BE 1, 2, 3, 4, OR 5!          #### '
     364    write(*,*) ' #### IOUT MUST BE 1, 2, 3, 4, OR 5 FOR       #### '
     365    write(*,*) ' #### STANDARD FLEXPART OUTPUT OR  9 - 13     #### '
     366    write(*,*) ' #### FOR NETCDF OUTPUT                       #### '
    361367    stop
    362368  endif
     
    370376    stop
    371377  endif
    372 
    373378
    374379
     
    592597
    5935981000   write(*,*) ' #### FLEXPART MODEL ERROR! FILE "COMMAND"    #### '
    594        write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
    595         write(*,'(a)') path(2)(1:length(1))
    596         stop
     599  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
     600  write(*,'(a)') path(2)(1:length(1))
     601  stop
    597602end subroutine readcommand
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG