Changeset dba4221 in flexpart.git for src/FLEXPART.f90


Ignore:
Timestamp:
Nov 9, 2022, 4:50:39 PM (18 months ago)
Author:
Pirmin Kaufmann <pirmin.kaufmann@…>
Branches:
bugfixes+enhancements
Children:
8ad70c7
Parents:
49e63b9
Message:

Bugfixes:

  • options/SPECIES/SPECIES_009: corrected wrong number format, replaced comma by decimal point
  • options/SPECIES/SPECIES_028: corrected wrong number format, moved sign of exponent to after the E
  • options/SPECIES/specoverview.f90: added namelist parameters that appear in SPECIES files but were missing here
  • src/FLEXPART.f90: replaced compiler-specific command line argument routines by standard Fortran intrinsic routines
  • src/FLEXPART_MPI.f90: ditto
  • src/gridcheck_ecmwf.f90: corrected handling of vertical levels when input files do not contain uppermost layers
  • src/gridcheck_nests.f90: ditto
  • src/readwind_ecmwf.f90: corrected handling of vertical levels when input files do not contain uppermost layers
  • readwind_ecmwf_mpi.f90: ditto

Code enhancements:

  • options/OUTGRID: added comments describing contents
  • options/SPECIES/SPECIES_*: aligned comments
  • options/SPECIES/specoverview.f90: removed commented lines, rectified lines indenting
  • src/FLEXPART.f90: rectified lines indenting, updated date in version string
  • src/FLEXPART_MPI.f90: ditto, and realigned code with src/FLEXPART.f90
  • src/gridcheck_*.f90: added code to write out name of file before it is opened (helps a lot when an input file causes troubles)
  • src/par_mod.f90: added comment explaining relevance of nuvzmax for GRIB input
  • src/readreleases.f90: write out warning if too few particles are used to randomize release
  • src/readspecies.f90: write out name of SPECIES file before it is read
  • src/readwind_*.f90: write out name of input file before opening it
  • src/writeheader_txt.f90: removed wrong comment
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/FLEXPART.f90

    r49e63b9 rdba4221  
    4444  implicit none
    4545
    46   integer :: i,j,ix,jy,inest, iopt
     46  integer :: i, j, ix, jy, inest, iopt
    4747  integer :: idummy = -320
    4848  character(len=256) :: inline_options  !pathfile, flexversion, arg2
     
    6262  ! FLEXPART version string
    6363  flexversion_major = '10' ! Major version number, also used for species file names
    64   flexversion='Version '//trim(flexversion_major)//'.4.1 (2020-08-05)'
     64  flexversion='Version '//trim(flexversion_major)//'.4.1 (2022-11-09)'
    6565  verbosity=0
    6666
     
    6969
    7070  inline_options='none'
    71   select case (iargc())
     71  select case (command_argument_count())  ! Portable standard Fortran intrinsic procedure
    7272  case (2)
    73     call getarg(1,arg1)
     73    call get_command_argument(1,arg1)     ! Portable standard Fortran intrinsic procedure
    7474    pathfile=arg1
    75     call getarg(2,arg2)
     75    call get_command_argument(2,arg2)     ! Portable standard Fortran intrinsic procedure
    7676    inline_options=arg2
    7777  case (1)
    78     call getarg(1,arg1)
     78    call get_command_argument(1,arg1)     ! Portable standard Fortran intrinsic procedure
    7979    pathfile=arg1
    8080    if (arg1(1:1).eq.'-') then
     
    9090  print*,'Welcome to FLEXPART ', trim(flexversion)
    9191  print*,'FLEXPART is free software released under the GNU General Public License.'
    92  
     92
    9393
    9494  ! Ingest inline options
     
    112112    endif
    113113    if (trim(inline_options).eq.'-i') then
    114        print*, 'Info mode: provide detailed run specific information and stop'
    115        verbosity=1
    116        info_flag=1
     114      print*, 'Info mode: provide detailed run specific information and stop'
     115      verbosity=1
     116      info_flag=1
    117117    endif
    118118    if (trim(inline_options).eq.'-i2') then
    119        print*, 'Info mode: provide more detailed run specific information and stop'
    120        verbosity=2
    121        info_flag=1
     119      print*, 'Info mode: provide more detailed run specific information and stop'
     120      verbosity=2
     121      info_flag=1
    122122    endif
    123123  endif
     
    138138     !print*,'length(4)',length(4)
    139139     !count=0,count_rate=1000
    140      CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
     140     call system_clock(count_clock0, count_rate, count_max)
    141141     !WRITE(*,*) 'SYSTEM_CLOCK',count, count_rate, count_max
    142142     !WRITE(*,*) 'SYSTEM_CLOCK, count_clock0', count_clock0
     
    159159      CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    160160      write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    161     endif     
     161    endif
    162162  endif
    163163
     
    217217  ! both for the mother domain and eventual nests
    218218  !**********************************************
    219  
    220   if (verbosity.gt.0) then
    221      write(*,*) 'call gridcheck'
     219
     220  if (verbosity.gt.0) then
     221    write(*,*) 'call gridcheck'
    222222  endif
    223223
     
    258258
    259259  if (verbosity.eq.1) then
    260      print*,'call readreceptors'
     260    print*,'call readreceptors'
    261261  endif
    262262  call readreceptors
     
    267267  !call readspecies
    268268
    269 
    270269  ! Read the landuse inventory
    271270  !***************************
     
    329328    if (verbosity.gt.0) then
    330329      print*,'numpart=0, numparticlecount=0'
    331     endif   
     330    endif
    332331    numpart=0
    333332    numparticlecount=0
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG