Changeset dba4221 in flexpart.git for src/FLEXPART_MPI.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_MPI.f90

    r92fab65 rdba4221  
    4444  implicit none
    4545
    46   integer :: i,j,ix,jy,inest
     46  integer :: i, j, ix, jy, inest, iopt
    4747  integer :: idummy = -320
    4848  character(len=256) :: inline_options  !pathfile, flexversion, arg2
     
    7171  call gasdev1(idummy,rannumb(maxrand),rannumb(maxrand-1))
    7272
     73
    7374  ! FLEXPART version string
    7475  flexversion_major = '10' ! Major version number, also used for species file names
    75   flexversion='Ver. '//trim(flexversion_major)//'.2beta MPI (2017-08-01)'
     76  flexversion='Version '//trim(flexversion_major)//'.4.1 MPI (2022-11-09)'
    7677  verbosity=0
    7778
     
    8081
    8182  inline_options='none'
    82   select case (iargc())
     83  select case (command_argument_count())  ! Portable standard Fortran intrinsic procedure
    8384  case (2)
    84     call getarg(1,arg1)
     85    call get_command_argument(1,arg1)     ! Portable standard Fortran intrinsic procedure
    8586    pathfile=arg1
    86     call getarg(2,arg2)
     87    call get_command_argument(2,arg2)     ! Portable standard Fortran intrinsic procedure
    8788    inline_options=arg2
    8889  case (1)
    89     call getarg(1,arg1)
     90    call get_command_argument(1,arg1)     ! Portable standard Fortran intrinsic procedure
    9091    pathfile=arg1
    9192    if (arg1(1:1).eq.'-') then
     
    9798  end select
    9899 
    99   if (lroot) then
    100100  ! Print the GPL License statement
    101101  !*******************************************************
     102  if (lroot) then
    102103    print*,'Welcome to FLEXPART ', trim(flexversion)
    103104    print*,'FLEXPART is free software released under the GNU General Public License.'
    104105  endif
    105  
     106
     107
     108  ! Ingest inline options
     109  !*******************************************************
    106110  if (inline_options(1:1).eq.'-') then
    107     if (trim(inline_options).eq.'-v'.or.trim(inline_options).eq.'-v1') then
    108       print*, 'Verbose mode 1: display detailed information during run'
     111    print*,'inline_options:',inline_options
     112    !verbose mode
     113    iopt=index(inline_options,'v')
     114    if (iopt.gt.0) then
    109115      verbosity=1
    110     endif
    111     if (trim(inline_options).eq.'-v2') then
    112       print*, 'Verbose mode 2: display more detailed information during run'
    113       verbosity=2
     116      !print*, iopt, inline_options(iopt+1:iopt+1)
     117      if  (trim(inline_options(iopt+1:iopt+1)).eq.'2') then
     118        print*, 'Verbose mode 2: display more detailed information during run'
     119        verbosity=2
     120      endif
     121    endif
     122    !debug mode
     123    iopt=index(inline_options,'d')
     124    if (iopt.gt.0) then
     125      debug_mode=.true.
    114126    endif
    115127    if (trim(inline_options).eq.'-i') then
     
    125137  endif
    126138           
     139  if (verbosity.gt.0) then
     140    print*, 'nxmax=',nxmax
     141    print*, 'nymax=',nymax
     142    print*, 'nzmax=',nzmax
     143    print*,'nxshift=',nxshift
     144  endif
     145 
    127146  if (verbosity.gt.0) then
    128147    write(*,*) 'call readpaths'
     
    133152     !print*,'length(4)',length(4)
    134153     !count=0,count_rate=1000
    135     call system_clock(count_clock0, count_rate, count_max)
     154     call system_clock(count_clock0, count_rate, count_max)
    136155     !WRITE(*,*) 'SYSTEM_CLOCK',count, count_rate, count_max
    137156     !WRITE(*,*) 'SYSTEM_CLOCK, count_clock0', count_clock0
     
    157176  endif
    158177
    159   ! Initialize arrays in com_mod 
     178  ! Initialize arrays in com_mod
    160179  !*****************************
    161 
    162180  if(.not.(lmpreader.and.lmp_use_reader)) call com_mod_allocate_part(maxpart_mpi)
    163181
    164182
    165 ! Read the age classes to be used
    166 !********************************
     183  ! Read the age classes to be used
     184  !********************************
    167185  if (verbosity.gt.0 .and. lroot) then
    168186    write(*,*) 'call readageclasses'
     
    185203  ! Detect metdata format
    186204  !**********************
     205  if (verbosity.gt.0 .and. lroot) then
     206    write(*,*) 'call detectformat'
     207  endif
    187208
    188209  metdata_format = detectformat()
     
    207228  call com_mod_allocate_nests
    208229
    209 ! Read the model grid specifications,
    210 ! both for the mother domain and eventual nests
    211 !**********************************************
     230  ! Read the model grid specifications,
     231  ! both for the mother domain and eventual nests
     232  !**********************************************
    212233
    213234  if (verbosity.gt.0 .and. lroot) then
     
    221242  end if
    222243
    223 
    224244  if (verbosity.gt.1 .and. lroot) then   
    225245    call system_clock(count_clock, count_rate, count_max)
     
    227247  endif     
    228248
    229 
    230249  if (verbosity.gt.0 .and. lroot) then
    231250    write(*,*) 'call gridcheck_nests'
     
    233252  call gridcheck_nests
    234253
    235 
    236 ! Read the output grid specifications
    237 !************************************
    238 
    239   if (verbosity.gt.0 .and. lroot) then
    240     WRITE(*,*) 'call readoutgrid'
     254  ! Read the output grid specifications
     255  !************************************
     256
     257  if (verbosity.gt.0 .and. lroot) then
     258    write(*,*) 'call readoutgrid'
    241259  endif
    242260
     
    246264    call readoutgrid_nest
    247265    if (verbosity.gt.0.and.lroot) then
    248       WRITE(*,*) '# readoutgrid_nest'
     266      write(*,*) '# readoutgrid_nest'
    249267    endif
    250268  endif
     
    263281  !call readspecies
    264282
    265 
    266283  ! Read the landuse inventory
    267284  !***************************
     
    272289  call readlanduse
    273290
    274 
    275 ! Assign fractional cover of landuse classes to each ECMWF grid point
    276 !********************************************************************
     291  ! Assign fractional cover of landuse classes to each ECMWF grid point
     292  !********************************************************************
    277293
    278294  if (verbosity.gt.0 .and. lroot) then
     
    289305  call readreleases
    290306
    291 
    292 ! Read and compute surface resistances to dry deposition of gases
    293 !****************************************************************
     307  ! Read and compute surface resistances to dry deposition of gases
     308  !****************************************************************
    294309
    295310  if (verbosity.gt.0 .and. lroot) then
     
    305320    print*,'call coordtrafo'
    306321  endif
    307 
    308322
    309323  ! Initialize all particles to non-existent
     
    337351  endif
    338352
    339 
    340353  ! Calculate volume, surface area, etc., of all output grid cells
    341354  ! Allocate fluxes and OHfield if necessary
    342355  !***************************************************************
    343 
    344356
    345357  if (verbosity.gt.0 .and. lroot) then
     
    387399
    388400    call writeheader
    389 ! FLEXPART 9.2 ticket ?? write header in ASCII format
     401    ! FLEXPART 9.2 ticket ?? write header in ASCII format
    390402    call writeheader_txt
    391403
     
    445457  end if
    446458
    447 ! Calculate particle trajectories
    448 !********************************
     459  ! Calculate particle trajectories
     460  !********************************
    449461
    450462  if (verbosity.gt.0.and. lroot) then
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG