Changeset dba4221 in flexpart.git for options/SPECIES/specoverview.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
  • options/SPECIES/specoverview.f90

    r95a45d3 rdba4221  
    1919! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
    2020!**********************************************************************
     21program specoverview
    2122  implicit none
    2223
     
    2728  real :: pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst
    2829  real :: pcrain_aero, pcsnow_aero, pccn_aero, pin_aero
    29   integer :: readerror, unitspecies, specnumber
     30  real :: parea_dow(7), parea_hour(24), ppoint_dow(7), ppoint_hour(24)
     31  integer :: ierr, unitspecies, specnumber
    3032
    31 ! declare namelist
     33  ! declare namelist
    3234  namelist /species_params/ &
    3335       pspecies, pdecay, pweta_gas, pwetb_gas, &
    3436       pcrain_aero, pcsnow_aero, pccn_aero, pin_aero, &
    3537       preldiff, phenry, pf0, pdensity, pdquer, &
    36        pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst
     38       pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst, &
     39       parea_dow, parea_hour, ppoint_dow, ppoint_hour
    3740
    3841  unitspecies=4
    3942
    40   write(*,*) '    Species   |       |   WetDep(gas)   |    DryDep(gas)   |WetDep(below-C)| WetDep(in-C)|'//&
    41              '     DryDepo(particles)  Altern| Radioact.  |     OH Reaction      |'
     43  write(*,*) '    Species   |       |   WetDep(gas)   |    DryDep(gas)   |WetDep(below-C)| WetDep(in-C)|'// &
     44       '     DryDepo(particles)  Altern| Radioact.  |     OH Reaction      |'
    4245
    43   write(*,*) '    Name      |molwght| A          B    | D    H        f0 | Crain   Csnow |  ccn    in  |' //&
    44              '   rho    dquer    dsig    vd  | Halflife[s]|   C**     D[T]  N*** |'
     46  write(*,*) '    Name      |molwght| A          B    | D    H        f0 | Crain   Csnow |  ccn    in  |'// &
     47       '   rho    dquer    dsig    vd  | Halflife[s]|   C**     D[T]  N*** |'
    4548
    46   write(*,*) '--------------|-------|-----------------|------------------|---------------|-------------|'//&
    47              '-------------------------------|------------|----------------------|'
     49  write(*,*) '--------------|-------|-----------------|------------------|---------------|-------------|'// &
     50       '-------------------------------|------------|----------------------|'
    4851
    4952
    50 ! write(*,*) '    Specie    | Radioact.  | WetDep(gas)     |WetDep(below-C)| WetDep(in-C)|     DryDepo(gas)  |'//&
    51 !            '     DryDepo(particles)  Altern|       |     OH Reaction      |'
    52 ! write(*,*) '    Name      | Halflife[s]|  A         B    |  Crain  Csnow | ccn    in   |   D      H    f0  |' //&
    53 !            '   rho    dquer    dsig    vd  |molwght|   C**     D[T]  N*** |'
    54 ! write(*,*) '--------------|------------|-----------------|---------------|-------------|-------------------|'//&
    55 !            '-------------------------------|-------|----------------------|'
     53  do specnumber=1,100
    5654
    57   do specnumber=1,100
    58  
    59   write (aspec,'(i0.3)') specnumber
    60   speciesfn='SPECIES_'//aspec
    61  
    62 ! write(*,*) 'Processing: ',speciesfn
     55     write (aspec,'(i0.3)') specnumber
     56     speciesfn='SPECIES_'//aspec
    6357
    64   pspecies="" ! read failure indicator value
    65   pdecay=-9.9
    66   pweta_gas=-0.9E-09
    67   pwetb_gas=0.0
    68   pcrain_aero=-9.9
    69   pcsnow_aero=-9.9
    70   pccn_aero=-9.9
    71   pin_aero=-9.9
    72   preldiff=-9.9
    73   phenry=0.0
    74   pf0=0.0
    75   pdensity=-0.9E09
    76   pdquer=0.0
    77   pdsigma=0.0
    78   pdryvel=-9.99
    79   pohcconst=-9.9
    80   pohdconst=-9.9
    81   pohnconst=2.0
    82   pweightmolar=-9.9
     58     ! write(*,*) 'Processing: ',speciesfn
    8359
    84 ! Open the SPECIES file and read species names and properties
    85 !************************************************************
    86   open(unitspecies,file=speciesfn,status='old',form='formatted',err=998)
    87   read(unitspecies,species_params,err=998)
    88   close(unitspecies)
    89  
    90   write(*,45) specnumber,' ',pspecies,'|',pweightmolar,'|',pweta_gas,' ',pwetb_gas,'|', &
    91               preldiff,' ',phenry,' ',pf0,'|', &
    92               pcrain_aero,' ',pcsnow_aero,'|',pccn_aero,' ',pin_aero,'|', &
    93               pdensity,pdquer,pdsigma,pdryvel,'|',pdecay,'|',pohcconst,pohdconst,pohnconst,'|'
     60     pspecies="" ! read failure indicator value
     61     pdecay=-9.9
     62     pweta_gas=-0.9E-09
     63     pwetb_gas=0.0
     64     pcrain_aero=-9.9
     65     pcsnow_aero=-9.9
     66     pccn_aero=-9.9
     67     pin_aero=-9.9
     68     preldiff=-9.9
     69     phenry=0.0
     70     pf0=0.0
     71     pdensity=-0.9E09
     72     pdquer=0.0
     73     pdsigma=0.0
     74     pdryvel=-9.99
     75     pohcconst=-9.9
     76     pohdconst=-9.9
     77     pohnconst=2.0
     78     pweightmolar=-9.9
    9479
    95 45 format(i3,a1,a11,a1,f7.1,a1,e8.1,a1,f8.2,a1, &
     80     ! Open the SPECIES file and read species names and properties
     81     !************************************************************
     82     open(unitspecies,file=speciesfn,status='old',form='formatted',iostat=ierr)
     83     if (ierr /= 0) then
     84        ! Report missing files below 40
     85        if (specnumber <= 40) then
     86           write(*,'(i3,2(1x,a))') specnumber, 'no such file:', trim(speciesfn)
     87        end if
     88        cycle
     89     end if
     90     read(unitspecies,species_params)  ! to skip errors add: ,err=998
     91     close(unitspecies)
     92
     93     write(*,45) specnumber,' ',pspecies,'|',pweightmolar,'|',pweta_gas,' ',pwetb_gas,'|', &
     94          preldiff,' ',phenry,' ',pf0,'|', &
     95          pcrain_aero,' ',pcsnow_aero,'|',pccn_aero,' ',pin_aero,'|', &
     96          pdensity,pdquer,pdsigma,pdryvel,'|',pdecay,'|',pohcconst,pohdconst,pohnconst,'|'
     97
     9845   format(i3,a1,a11,a1,f7.1,a1,e8.1,a1,f8.2,a1, &
    9699          f4.1,a1,e8.1,a1,f4.1,a1, &
    97100          f7.1,a1,f7.1,a1,f6.1,a1,f6.1,a1, &
    98101          e8.1,e9.1,f7.1,f7.2,a1,f12.1,a1,e8.1,f7.1,f7.1,a1)
    99102
    100 !  write(*,45) specnumber,' ',pspecies,'|',pdecay,'|',pweta_gas,' ',pwetb_gas,'|',pcrain_aero,' ', &
    101 !            pcsnow_aero,'|',pccn_aero,' ',pin_aero,'|',preldiff,' ',phenry,' ',pf0,'|', &
    102 !             pdensity,pdquer,pdsigma,pdryvel,'|',pweightmolar,'|',pohcconst,pohdconst,pohnconst,'|'
     103998  continue
     104  enddo
    103105
    104 !5 format(i3,a1,a11,a1,f12.1,a1,e8.1,a1,f8.2,a1,f7.1,a1,f7.1,a1,f6.1,a1,f6.1,a1,f5.1,a1,e8.1,a1,f4.1,a1, &
    105 !         e8.1,e9.1,f7.1,f7.2,a1,f7.1,a1,e8.1,f7.1,f7.1,a1)
    106            
    107 998 continue
    108 enddo
     106  write(*,*) '** unit [cm^3/molec/s] (in FLEXPART version 9.2 and below this had unit [cm3/s], note the unit is now changed!)'
     107  write(*,*) '*** no unit'
    109108
    110 write(*,*) '** unit [cm^3/molec/s] (in FLEXPART version 9.2 and below this had unit [cm3/s], note the unit is now changed!)'
    111 write(*,*) '*** no unit'
     109  print*,'rho: density'
    112110
    113  print*,'rho: density'
    114 
    115 end
     111end program specoverview
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG