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


Ignore:
Timestamp:
Sep 11, 2018, 6:06:31 PM (6 years ago)
Author:
pesei <petra seibert at univie ac at>
Branches:
univie
Children:
93786a1
Parents:
34f1452
Message:

modify most input read subroutines

changed some variable names (mostly for I-N reasons)
includes two names appearing also in timemanager, com_mod
corrected a few mistakes
simplified some parts of code
changed options/RELEASES which is in nml fmt correspondingly

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/readcommand.f90

    r77778f8 rd7935de  
    3333  !     Unknown, unknown: various                                              *
    3434  !     Petra Seibert, 2018-06-08: improve error msgs                          *
     35  !     PS 6/2015: Minor changes in variable names and layout                  *
    3536  !                                                                            *
    3637  !*****************************************************************************
     
    8485  character(len=50) :: line
    8586  logical :: old
    86   integer :: readerror
    87 
    88   namelist /command/ &
    89   ldirect, &
    90   ibdate,ibtime, &
    91   iedate,ietime, &
    92   loutstep, &
    93   loutaver, &
    94   loutsample, &
    95   itsplit, &
    96   lsynctime, &
    97   ctl, &
    98   ifine, &
    99   iout, &
    100   ipout, &
    101   lsubgrid, &
    102   lconvection, &
    103   lagespectra, &
    104   ipin, &
    105   ioutputforeachrelease, &
    106   iflux, &
    107   mdomainfill, &
    108   ind_source, &
    109   ind_receptor, &
    110   mquasilag, &
    111   nested_output, &
    112   linit_cond, &
    113   lnetcdfout, &
    114   surf_only, &
    115   cblflag, &
    116   ohfields_path
    117 
    118   ! Presetting namelist command
    119   ldirect=0
    120   ibdate=20000101
    121   ibtime=0
    122   iedate=20000102
    123   ietime=0
    124   loutstep=10800
    125   loutaver=10800
    126   loutsample=900
    127   itsplit=999999999
    128   lsynctime=900
    129   ctl=-5.0
    130   ifine=4
    131   iout=3
    132   ipout=0
    133   lsubgrid=1
    134   lconvection=1
    135   lagespectra=0
    136   ipin=1
    137   ioutputforeachrelease=1
    138   iflux=1
    139   mdomainfill=0
    140   ind_source=1
    141   ind_receptor=1
    142   mquasilag=0
    143   nested_output=0
    144   linit_cond=0
    145   lnetcdfout=0
    146   surf_only=0
    147   cblflag=0 ! if using old-style COMMAND file, set to 1 here to use mc cbl routine
    148   ohfields_path="../../flexin/"
     87  integer :: ios, icmdstat
     88
     89  namelist /nml_command/ &
     90    ldirect, &
     91    ibdate,ibtime, &
     92    iedate,ietime, &
     93    loutstep, &
     94    loutaver, &
     95    loutsample, &
     96    itsplit, &
     97    lsynctime, &
     98    ctl, &
     99    ifine, &
     100    iout, &
     101    ipout, &
     102    lsubgrid, &
     103    lconvection, &
     104    lagespectra, &
     105    ipin, &
     106    ioutputforeachrelease, &
     107    iflux, &
     108    mdomainfill, &
     109    ind_source, &
     110    ind_receptor, &
     111    mquasilag, &
     112    nested_output, &
     113    linit_cond, &
     114    lnetcdfout, &
     115    surf_only, &
     116    iflagcbl, &
     117    path_ohfields
     118
     119! Set default values for namelist
     120    ldirect=0
     121    ibdate=20000101
     122    ibtime=0
     123    iedate=20000102
     124    ietime=0
     125    loutstep=10800
     126    loutaver=10800
     127    loutsample=900
     128    itsplit=999999999
     129    lsynctime=900
     130    ctl=-5.0
     131    ifine=4
     132    iout=3
     133    ipout=0
     134    lsubgrid=1
     135    lconvection=1
     136    lagespectra=0
     137    ipin=1
     138    ioutputforeachrelease=1
     139    iflux=1
     140    mdomainfill=0
     141    ind_source=1
     142    ind_receptor=1
     143    mquasilag=0
     144    nested_output=0
     145    linit_cond=0
     146    lnetcdfout=0
     147    surf_only=0
     148    iflagcbl=0 ! if using old-style COMMAND file, set to 1 here to use mc cbl routine
     149    path_ohfields="../../flexin/"
    149150
    150151  !Af set release-switch
    151   WETBKDEP=.false.
    152   DRYBKDEP=.false.
    153 
     152    wetbkdep=.false.
     153    drybkdep=.false.
     154 
    154155  ! Open the command file and read user options
    155156  ! Namelist input first: try to read as namelist file
     
    158159    form='formatted',err=999)
    159160
    160   ! try namelist input (default)
    161   read(unitcommand,command,iostat=readerror)
     161! try namelist input
     162  read(unitcommand, nml_command, iostat=ios)
    162163  close(unitcommand)
    163164
    164165  ! distinguish namelist from fixed text input
    165   if ((readerror.ne.0).or.(ldirect.eq.0)) then ! parse as text file format
     166
     167  if (ios .ne. 0) then ! simple text file format
    166168 
    167169    open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old', err=999)
    168170
    169     ! Check the format of the COMMAND file (either in free format,
    170     ! or using formatted mask)
     171    ! Check the format of the COMMAND file
     172    ! (either in free format or using formatted mask)
    171173    ! Use of formatted mask is assumed if line 10 contains the word 'DIRECTION'
    172174    !**************************************************************************
    173175
    174176    call skplin(9,unitcommand)
    175     read (unitcommand,901) line
    176   901   format (a)
     177    read (unitcommand,900) line
    177178    if (index(line,'LDIRECT') .eq. 0) then
    178179      old = .false.
     
    243244    ! Removed for backwards compatibility.
    244245    ! if (old) call skplin(3,unitcommand)  !added by mc
    245     ! read(unitcommand,*) cblflag          !added by mc
     246    ! read(unitcommand,*) iflagcbl          !added by mc
    246247
    247248    close(unitcommand)
     
    252253  if (nmlout.and.lroot) then
    253254    open(unitcommand,file=path(2)(1:length(2))//'COMMAND.namelist',err=998)
    254     write(unitcommand,nml=command)
     255    write(unitcommand,nml=nml_command)
    255256    close(unitcommand)
    256257  endif
     
    260261  ! Determine how Markov chain is formulated (for w or for w/sigw)
    261262  !***************************************************************
    262   if (cblflag.eq.1) then !---- added by mc to properly set parameters for CBL simulations
     263  if (iflagcbl.eq.1) then !added by mc to set parameters for CBL simulations
    263264    turbswitch=.true.
    264     if (lsynctime>maxtl) lsynctime=maxtl  !maxtl defined in com_mod.f90
     265    if (lsynctime.gt.maxtl) lsynctime=maxtl  !maxtl defined in com_mod.f90
    265266    if (ctl.lt.5) then
    266       print *,'WARNING: CBL flag active the ratio of TLu/dt has been set to 5'
     267      print*,'WARNING: CBL flag active; ctl (TLu/dt) has been set to 5'
    267268      ctl=5.
    268     end if
    269     if (ifine*ctl.lt.50) then
     269    endif
     270    if (ifine*ctl.lt.50.) then
    270271      ifine=int(50./ctl)+1
    271 
    272       print *,'WARNING: CBL flag active the ratio of TLW/dt was < 50, ifine has been re-set to',ifine
    273 !pause
     272      print *,'WARNING: CBL flag active; ctl (TLW/dt) was < 50,'// &
     273        ' ifine has been re-set to', ifine
    274274    endif
    275     print *,'WARNING: CBL flag active the ratio of TLW/dt is ',ctl*ifine
    276     print *,'WARNING: CBL flag active lsynctime is ',lsynctime
     275    print*,'WARNING: CBL flag active; reduced ctl is ',ctl*ifine
     276    print*,'WARNING: CBL flag active; lsynctime is ',lsynctime
    277277  else                    !added by mc
     278  ! note PS: shouldn't we print some msg as above also in the ntext case?
    278279    if (ctl.ge.0.1) then
    279280      turbswitch=.true.
     
    286287  ctl=1./ctl
    287288
    288   ! Set the switches required for the various options for input/output units
    289   !*************************************************************************
    290   !AF Set the switches IND_REL and IND_SAMP for the release and sampling
    291   !Af switches for the releasefile:
    292   !Af IND_REL =  1 : xmass * rho
    293   !Af IND_REL =  0 : xmass * 1
    294 
    295   !Af switches for the conccalcfile:
    296   !AF IND_SAMP =  0 : xmass * 1
    297   !Af IND_SAMP = -1 : xmass / rho
    298 
    299   !AF IND_SOURCE switches between different units for concentrations at the source
    300   !Af   NOTE that in backward simulations the release of computational particles
    301   !Af   takes place at the "receptor" and the sampling of p[articles at the "source".
    302   !Af          1 = mass units
    303   !Af          2 = mass mixing ratio units
    304   !Af IND_RECEPTOR switches between different units for concentrations at the receptor
    305   !Af          1 = mass units
    306   !Af          2 = mass mixing ratio units
    307   !            3 = wet deposition in outputfield
    308   !            4 = dry deposition in outputfield
     289! Set the switches required for the various options for input/output units
     290!*************************************************************************
     291!AF Set the switches IND_REL and IND_SAMP for the release and sampling
     292!Af switches for the releasefile:
     293!Af IND_REL =  1 : xmass * rho
     294!Af IND_REL =  0 : xmass * 1
     295
     296!Af switches for the conccalcfile:
     297!AF IND_SAMP =  0 : xmass * 1
     298!Af IND_SAMP = -1 : xmass / rho
     299
     300!AF IND_SOURCE switches between different units for concentrations at the source
     301!Af   NOTE that in backward simulations the release of computational particles
     302!Af   takes place at the "receptor" and the sampling of p[articles at the "source".
     303!Af          1 = mass units
     304!Af          2 = mass mixing ratio units
     305!Af IND_RECEPTOR switches between different units for concentrations at the receptor
     306!Af          1 = mass units
     307!Af          2 = mass mixing ratio units
     308!            3 = wet deposition in outputfield
     309!            4 = dry deposition in outputfield
    309310
    310311  if ( ldirect .eq. 1 ) then  ! FWD-Run
     
    328329        ind_samp = 0
    329330     endif
     331! note PS: why do we suddenly switch to CASE syntax??
     332! not helpful.
    330333     select case (ind_receptor)
    331334     case (1)  !  1 .. concentration at receptor
     
    337340        if (lroot) then
    338341          write(*,*) ' #### FLEXPART WET DEPOSITION BACKWARD MODE    #### '
    339           write(*,*) ' #### Releaseheight is forced to 0 - 20km      #### '
     342          write(*,*) ' #### Release height is forced to 0 - 20 km    #### '
    340343          write(*,*) ' #### Release is performed above ground lev    #### '
    341344        end if
    342          WETBKDEP=.true.
     345         wetbkdep=.true.
    343346         allocate(xscav_frac1(maxpart,maxspec))
    344347     case (4)  ! 4 .. dry deposition in outputfield
     
    349352           write(*,*) ' #### Release is performed above ground lev    #### '
    350353         end if
    351          DRYBKDEP=.true.
     354         drybkdep=.true.
    352355         allocate(xscav_frac1(maxpart,maxspec))
    353356     end select
     
    399402  endif
    400403
    401 ! Check for netcdf output switch
    402 !*******************************
     404!  check for netcdf output switch (use for non-namelist input only!)
    403405  if (iout.ge.8) then
    404406     lnetcdfout = 1
    405407     iout = iout - 8
    406408#ifndef USE_NCF
    407      write(*,*) 'ERROR: netcdf output not activated during compile time but used in COMMAND file!'
    408      write(*,*) 'Please recompile with netcdf library (`make [...] ncf=yes`) or use standard output format.'
     409     write(*,*) 'ERROR: netcdf output not activated during compile '// &
     410       'time but used in COMMAND file!'
     411     write(*,*) 'Please recompile with netcdf library (`make [...] ncf=yes`)'//&
     412       ' or use standard output format.'
    409413     stop
    410414#endif
     
    414418  !**********************************************************************
    415419
    416   if ((iout.lt.1).or.(iout.gt.6)) then
     420  if (iout.lt.1 .or. iout.gt.6) then
    417421    write(*,*) ' #### FLEXPART MODEL ERROR! FILE COMMAND:     #### '
    418422    write(*,*) ' #### IOUT MUST BE 1, 2, 3, 4 OR 5 FOR        #### '
     
    423427
    424428  !AF check consistency between units and volume mixing ratio
    425   if ( ((iout.eq.2).or.(iout.eq.3)).and. &
    426        (ind_source.gt.1 .or.ind_receptor.gt.1) ) then
     429  if ( (iout.eq.2       .or. iout.eq.3) .and. &
     430       (ind_source.gt.1 .or. ind_receptor.gt.1) ) then
    427431    write(*,*) ' #### FLEXPART MODEL ERROR! FILE COMMAND:     #### '
    428432    write(*,*) ' #### VOLUME MIXING RATIO ONLY SUPPORTED      #### '
     
    479483
    480484  ! For domain-filling trajectories, a plume centroid trajectory makes no sense,
    481   ! For backward runs, only residence time output (iout=1) or plume trajectories (iout=4),
    482   ! or both (iout=5) makes sense; other output options are "forbidden"
     485  ! For backward runs, only residence time output (iout=1) or plume trajectories
     486  ! (iout=4), or both (iout=5) makes sense; other output options are "forbidden"
    483487  !*****************************************************************************
    484488
     
    649653    path(2)(1:length(2))//'COMMAND.namelist'
    650654  stop 'stopped in readcommand'
     655
    651656999 write(*,900) ' #### FLEXPART MODEL ERROR! FILE "COMMAND"'
    652657  write(*,900)   ' #### CANNOT OPEN '//path(1)(1:length(1))//'COMMAND'
    653658  stop 'stopped in readcommand'
    654 900 format (a)
     659
     660900 format(a)
     661
    655662end subroutine readcommand
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG