Changeset dba4221 in flexpart.git for src


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
Location:
src
Files:
13 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
  • 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
  • src/gridcheck_ecmwf.f90

    r92fab65 rdba4221  
    103103  ! OPENING OF DATA FILE (GRIB CODE)
    104104  !
     105  write(*,*)   'Reading: '//path(3)(1:length(3)) &
     106       //trim(wfname(ifn))
    1051075 call grib_open_file(ifile,path(3)(1:length(3)) &
    106108       //trim(wfname(ifn)),'r',iret)
     
    418420
    419421  nuvz=iumax
    420   nwz =iwmax
     422  nwz =iwmax + 1       ! +1 needed if input contains only lower levels
    421423  if(nuvz.eq.nlev_ec) nwz=nlev_ec+1
    422424
  • src/gridcheck_gfs.f90

    r92fab65 rdba4221  
    111111  ! OPENING OF DATA FILE (GRIB CODE)
    112112  !
     113  write(*,*)     'Reading: '//path(3)(1:length(3)) &
     114         //trim(wfname(ifn))
    1131155   call grib_open_file(ifile,path(3)(1:length(3)) &
    114116         //trim(wfname(ifn)),'r',iret)
  • src/gridcheck_nests.f90

    r92fab65 rdba4221  
    7777  igrib=0
    7878  iret=0
     79
     80  write(*,*) 'Reading: '//path(numpath+2*(l-1)+1) &
     81         (1:length(numpath+2*(l-1)+1))//trim(wfnamen(l,ifn))
    7982
    80835   call grib_open_file(ifile,path(numpath+2*(l-1)+1) &
     
    326329
    327330  nuvzn=iumax
    328   nwzn=iwmax
     331  nwzn=iwmax + 1       ! +1 needed if input contains only lower levels
    329332  if(nuvzn.eq.nlev_ec) nwzn=nlev_ecn+1
    330333
  • src/par_mod.f90

    r92fab65 rdba4221  
    131131  !*********************************************
    132132 
     133  ! NOTE: dimensioning of zsec2 in gridcheck depends on nuvzmax, therefore nuvzmax
     134  ! must represent all levels even if only lower levels are in the input files.
     135
    133136  ! ECMWF
    134137! integer,parameter :: nxmax=361,nymax=181,nuvzmax=92,nwzmax=92,nzmax=92,nxshift=359 ! 1.0 degree 92 level
  • src/readreleases.f90

    r92fab65 rdba4221  
    555555        ireleaseend(numpoint)=int((jul2-bdate)*86400.)
    556556      else
     557        write(*,*) 'FLEXPART MODEL WARNING'
     558        write(*,*) 'Too few particles to randomize release,'
     559        write(*,*) 'release time set to mid-point of release interval'
    557560        ireleasestart(numpoint)=int((julm-bdate)*86400.)
    558561        ireleaseend(numpoint)=int((julm-bdate)*86400.)
  • src/readspecies.f90

    r92fab65 rdba4221  
    104104  specnum(pos_spec)=id_spec
    105105  write(aspecnumb,'(i3.3)') specnum(pos_spec)
     106  write(*,*) 'Reading: '// &
     107                        path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb
    106108  open(unitspecies,file=path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old',form='formatted',err=998)
    107109!write(*,*) 'reading SPECIES',specnum(pos_spec)
  • src/readwind_ecmwf.f90

    r92fab65 rdba4221  
    103103! OPENING OF DATA FILE (GRIB CODE)
    104104!
     105  write(*,*)   'Reading: '//path(3)(1:length(3)) &
     106       //trim(wfname(indj))
    1051075 call grib_open_file(ifile,path(3)(1:length(3)) &
    106108       //trim(wfname(indj)),'r',iret)
     
    386388  endif
    387389
    388   if(levdiff2.eq.0) then
    389     iwmax=nlev_ec+1
     390!  if(levdiff2.eq.0) then
     391    iwmax=iwmax+1
    390392    do i=0,nxmin1
    391393      do j=0,nymin1
    392         wwh(i,j,nlev_ec+1)=0.
     394        wwh(i,j,iwmax)=0.
    393395      end do
    394396    end do
    395   endif
     397!  endif
    396398
    397399! For global fields, assign the leftmost data column also to the rightmost
  • src/readwind_ecmwf_mpi.f90

    r92fab65 rdba4221  
    113113! OPENING OF DATA FILE (GRIB CODE)
    114114!
     115  write(*,*)   'Reading: '//path(3)(1:length(3)) &
     116       //trim(wfname(indj))
    1151175 call grib_open_file(ifile,path(3)(1:length(3)) &
    116118       //trim(wfname(indj)),'r',iret)
     
    394396  endif
    395397
    396   if(levdiff2.eq.0) then
    397     iwmax=nlev_ec+1
     398!  if(levdiff2.eq.0) then
     399    iwmax=iwmax+1
    398400    do i=0,nxmin1
    399401      do j=0,nymin1
    400         wwh(i,j,nlev_ec+1)=0.
     402        wwh(i,j,iwmax)=0.
    401403      end do
    402404    end do
    403   endif
     405!  endif
    404406
    405407! For global fields, assign the leftmost data column also to the rightmost
  • src/readwind_gfs.f90

    r92fab65 rdba4221  
    103103
    104104  !HSO
     105  write(*,*)   'Reading: '//path(3)(1:length(3)) &
     106         //trim(wfname(indj))
    105107  call grib_open_file(ifile,path(3)(1:length(3)) &
    106108         //trim(wfname(indj)),'r',iret)
  • src/readwind_nests.f90

    r92fab65 rdba4221  
    7979  ! OPENING OF DATA FILE (GRIB CODE)
    8080  !
    81 
     81    write(*,*)   'Reading: '//path(numpath+2*(l-1)+1) &
     82         (1:length(numpath+2*(l-1)+1))//trim(wfnamen(l,indj))
    82835   call grib_open_file(ifile,path(numpath+2*(l-1)+1) &
    8384         (1:length(numpath+2*(l-1)+1))//trim(wfnamen(l,indj)),'r')
     
    365366  endif
    366367
    367   if(levdiff2.eq.0) then
    368     iwmax=nlev_ec+1
     368!  if(levdiff2.eq.0) then
     369    iwmax=iwmax+1
    369370    do i=0,nxn(l)-1
    370371      do j=0,nyn(l)-1
    371         wwhn(i,j,nlev_ec+1,l)=0.
     372        wwhn(i,j,iwmax,l)=0.
    372373      end do
    373374    end do
    374   endif
     375!  endif
    375376
    376377  do i=0,nxn(l)-1
  • src/writeheader_txt.f90

    r92fab65 rdba4221  
    5252 
    5353  write(unitheader,*) '# ibdate,ibtime, iedate, ietime, flexversion'
    54   write(unitheader,*) ibdate, ibtime, iedate, ietime, trim(flexversion) !  'FLEXPART V9.0'
     54  write(unitheader,*) ibdate, ibtime, iedate, ietime, trim(flexversion)
    5555  !if (ldirect.eq.1) then
    5656  !  write(unitheader,*) ibdate,ibtime,trim(flexversion) !  'FLEXPART V9.0'
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG