Changeset 4fbe7a5 in flexpart.git for src/readcommand.f90


Ignore:
Timestamp:
May 23, 2014, 11:48:41 AM (10 years ago)
Author:
Ignacio Pisso <ip@…>
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:
0aded10
Parents:
f13406c
Message:

version 9.2 beta. Changes from HH, AST, MC, NIK, IP. Changes in vert transform. New SPECIES input includes scavenging coefficients

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/readcommand.f90

    rf13406c r4fbe7a5  
    8080  character(len=50) :: line
    8181  logical :: old
    82   logical :: nmlout=.true. !.false.
     82  logical :: nml_COMMAND=.true. , nmlout=.true. !.false.
    8383  integer :: readerror
    8484
    8585  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   
     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   
    111111
    112112  ! Presetting namelist command
     
    144144  open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old', &
    145145         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 
    156   read(unitcommand,command,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
     160 
     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
    157171  close(unitcommand)
    158172
     173  !write(*,*) 'readcommand > readerror read=' , readerror
    159174  ! If error in namelist format, try to open with old input code
    160   if (readerror.ne.0) then
     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
    161181
    162182    open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old', &
     
    173193    if (index(line,'LDIRECT') .eq. 0) then
    174194      old = .false.
     195    !write(*,*) 'readcommand old short'
    175196    else
    176197      old = .true.
     198    !write(*,*) 'readcommand old long'
    177199    endif
    178200    rewind(unitcommand)
    179201
     202
    180203    ! Read parameters
    181204    !****************
     
    231254    if (old) call skplin(3,unitcommand)
    232255    read(unitcommand,*) linit_cond
     256    if (old) call skplin(3,unitcommand)
     257    read(unitcommand,*) surf_only
    233258    close(unitcommand)
    234259
     
    237262  ! write command file in namelist format to output directory if requested
    238263  if (nmlout.eqv..true.) then
    239     !open(unitcommand,file=path(2)(1:length(2))//'COMMAND.namelist.out',status='new',err=1000)
    240264    open(unitcommand,file=path(2)(1:length(2))//'COMMAND.namelist',err=1000)
    241265    write(unitcommand,nml=command)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG