Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/readcommand.f90

    r30 r20  
    2929  !                                                                            *
    3030  !     18 May 1996                                                            *
    31   !     HSO, 1 July 2014                                                       *
    32   !     Added optional namelist input                                          *
    3331  !                                                                            *
    3432  !*****************************************************************************
     
    8280  character(len=50) :: line
    8381  logical :: old
     82  logical :: nmlout=.true. !.false.
    8483  integer :: readerror
    8584
    8685  namelist /command/ &
    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   
     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   
    113111
    114112  ! Presetting namelist command
    115   ldirect=0
     113  ldirect=1
    116114  ibdate=20000101
    117115  ibtime=0
     
    139137  nested_output=0
    140138  linit_cond=0
    141   lnetcdfout=0
    142139  surf_only=0
    143140
     
    145142  ! Namelist input first: try to read as namelist file
    146143  !**************************************************************************
    147   open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old',form='formatted',err=999)
    148 
    149   ! try namelist input (default)
     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
    150156  read(unitcommand,command,iostat=readerror)
    151157  close(unitcommand)
    152158
    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)
     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)
    157164
    158165    ! Check the format of the COMMAND file (either in free format,
     
    166173    if (index(line,'LDIRECT') .eq. 0) then
    167174      old = .false.
    168       write(*,*) 'COMMAND in old short format, please update to namelist format'
    169175    else
    170176      old = .true.
    171       write(*,*) 'COMMAND in old long format, please update to namelist format'
    172177    endif
    173178    rewind(unitcommand)
    174179
    175 
    176180    ! Read parameters
    177181    !****************
     
    179183    call skplin(7,unitcommand)
    180184    if (old) call skplin(1,unitcommand)
     185
    181186    read(unitcommand,*) ldirect
    182187    if (old) call skplin(3,unitcommand)
     
    226231    if (old) call skplin(3,unitcommand)
    227232    read(unitcommand,*) linit_cond
    228     if (old) call skplin(3,unitcommand)
    229     read(unitcommand,*) surf_only
    230233    close(unitcommand)
    231234
     
    234237  ! write command file in namelist format to output directory if requested
    235238  if (nmlout.eqv..true.) then
     239    !open(unitcommand,file=path(2)(1:length(2))//'COMMAND.namelist.out',status='new',err=1000)
    236240    open(unitcommand,file=path(2)(1:length(2))//'COMMAND.namelist',err=1000)
    237241    write(unitcommand,nml=command)
    238242    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)
    239246  endif
    240247
     
    346353  endif
    347354
    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 
    359355  ! Check whether a valid option for gridded model output has been chosen
    360356  !**********************************************************************
     
    362358  if ((iout.lt.1).or.(iout.gt.5)) then
    363359    write(*,*) ' #### FLEXPART MODEL ERROR! FILE COMMAND:     #### '
    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                       #### '
     360    write(*,*) ' #### IOUT MUST BE 1, 2, 3, 4, OR 5!          #### '
    367361    stop
    368362  endif
     
    376370    stop
    377371  endif
     372
    378373
    379374
     
    597592
    5985931000   write(*,*) ' #### FLEXPART MODEL ERROR! FILE "COMMAND"    #### '
    599   write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
    600   write(*,'(a)') path(2)(1:length(1))
    601   stop
     594       write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
     595        write(*,'(a)') path(2)(1:length(1))
     596        stop
    602597end subroutine readcommand
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG