Changeset 4842


Ignore:
Timestamp:
Jan 14, 2021 10:42:28 AM (3 years ago)
Author:
raasch
Message:

reading of namelist file and actions in case of namelist errors revised so that statement labels and goto statements are not required any more, deprecated namelists removed

Location:
palm/trunk
Files:
19 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/bulk_cloud_model_mod.f90

    r4828 r4842  
    2424! -----------------
    2525! $Id$
     26! reading of namelist file and actions in case of namelist errors revised so that statement labels
     27! and goto statements are not required any more
     28!
     29! 4828 2021-01-05 11:21:41Z Giersch
    2630! Enable 3D data output also with 64-bit precision
    2731!
     
    664668!> Parin for &bulk_cloud_parameters for the bulk cloud module
    665669!--------------------------------------------------------------------------------------------------!
    666     SUBROUTINE bcm_parin
    667 
    668 
    669        IMPLICIT NONE
    670 
    671        CHARACTER (LEN=80)  ::  line  !< dummy string that contains the current line of the parameter
    672                                      !< file
    673 
    674        NAMELIST /bulk_cloud_parameters/                                                            &
    675           aerosol_bulk,                                                                            &
    676           bulk_cloud_model,                                                                        &
    677           c_sedimentation,                                                                         &
    678           call_microphysics_at_all_substeps,                                                       &
    679           cloud_scheme,                                                                            &
    680           cloud_water_sedimentation,                                                               &
    681           collision_turbulence,                                                                    &
    682           curvature_solution_effects_bulk,                                                         &
    683           dry_aerosol_radius,                                                                      &
    684           graupel,                                                                                 &
    685           ice_crystal_sedimentation,                                                               &
    686           in_init,                                                                                 &
    687           limiter_sedimentation,                                                                   &
    688           microphysics_ice_phase,                                                                  &
    689           na_init,                                                                                 &
    690           nc_const,                                                                                &
    691           sigma_bulk,                                                                              &
    692           snow,                                                                                    &
    693           start_ice_microphysics,                                                                  &
    694           ventilation_effect
    695 
    696        line = ' '
    697 !
    698 !--    Try to find bulk cloud module namelist
    699        REWIND ( 11 )
    700        line = ' '
    701        DO   WHILE ( INDEX( line, '&bulk_cloud_parameters' ) == 0 )
    702           READ ( 11, '(A)', END=10 )  line
    703        ENDDO
    704        BACKSPACE ( 11 )
    705 !
    706 !--    Read user-defined namelist
    707        READ ( 11, bulk_cloud_parameters )
    708 !
    709 !--    Set flag that indicates that the bulk cloud module is switched on
    710        !bulk_cloud_model = .TRUE.
    711 
    712 10     CONTINUE
    713 
    714 
    715     END SUBROUTINE bcm_parin
     670 SUBROUTINE bcm_parin
     671
     672
     673    IMPLICIT NONE
     674
     675    CHARACTER(LEN=100)  ::  line  !< Dummy string that contains the current line of the parameter
     676                                  !< file
     677
     678    INTEGER(iwp)  ::  io_status   !< Status after reading the namelist file
     679
     680
     681    NAMELIST /bulk_cloud_parameters/                                                               &
     682       aerosol_bulk,                                                                               &
     683       bulk_cloud_model,                                                                           &
     684       c_sedimentation,                                                                            &
     685       call_microphysics_at_all_substeps,                                                          &
     686       cloud_scheme,                                                                               &
     687       cloud_water_sedimentation,                                                                  &
     688       collision_turbulence,                                                                       &
     689       curvature_solution_effects_bulk,                                                            &
     690       dry_aerosol_radius,                                                                         &
     691       graupel,                                                                                    &
     692       ice_crystal_sedimentation,                                                                  &
     693       in_init,                                                                                    &
     694       limiter_sedimentation,                                                                      &
     695       microphysics_ice_phase,                                                                     &
     696       na_init,                                                                                    &
     697       nc_const,                                                                                   &
     698       sigma_bulk,                                                                                 &
     699       snow,                                                                                       &
     700       start_ice_microphysics,                                                                     &
     701       ventilation_effect
     702
     703!
     704!-- Move to the beginning of the namelist file and try to find and read the namelist.
     705    REWIND( 11 )
     706    READ( 11, bulk_cloud_parameters, IOSTAT=io_status )
     707!
     708!-- Action depending on the READ status
     709    IF ( io_status == 0 )  THEN
     710!
     711!--    bulk_cloud_parameters namelist was found and read correctly. Set flag that
     712!--    bulk_cloud_model_mod is switched on.
     713       bulk_cloud_model = .TRUE.
     714
     715    ELSEIF ( io_status > 0 )  THEN
     716!
     717!--    bulk_cloud_parameters namelist was found, but contained errors. Print an error message
     718!--    containing the line that caused the problem.
     719       BACKSPACE( 11 )
     720       READ( 11 , '(A)') line
     721       CALL parin_fail_message( 'bulk_cloud_parameters', line )
     722
     723    ENDIF
     724
     725 END SUBROUTINE bcm_parin
    716726
    717727
  • palm/trunk/SOURCE/dynamics_mod.f90

    r4828 r4842  
    2424! -----------------
    2525! $Id$
     26! reading of namelist file and actions in case of namelist errors revised so that statement labels
     27! and goto statements are not required any more
     28!
     29! 4828 2021-01-05 11:21:41Z Giersch
    2630! Enable 3D data output also with 64-bit precision
    2731!
     
    336340
    337341
    338     CHARACTER (LEN=80)  ::  line  !< dummy string that contains the current line of the parameter file
    339 
    340     NAMELIST /dynamics_parameters/                                                                 &
    341        dynamics_module_enabled
    342 
    343 
    344     line = ' '
    345 !
    346 !-- Try to find module-specific namelist
    347     REWIND ( 11 )
    348     line = ' '
    349     DO   WHILE ( INDEX( line, '&dynamics_parameters' ) == 0 )
    350        READ ( 11, '(A)', END=12 )  line
    351     ENDDO
    352     BACKSPACE ( 11 )
    353 
    354 !-- Set default module switch to true
     342    CHARACTER(LEN=100)  ::  line  !< dummy string that contains the current line of the parameter
     343                                  !< file
     344    INTEGER(iwp)  ::  io_status   !< status after reading the namelist file
     345
     346   
     347    NAMELIST /dynamics_parameters/  dynamics_module_enabled
     348
     349!
     350!-- Set default module switch to true.
    355351    dynamics_module_enabled = .TRUE.
    356352
    357 !-- Read user-defined namelist
    358     READ ( 11, dynamics_parameters, ERR = 10 )
    359 
    360     GOTO 12
    361 
    362 10  BACKSPACE( 11 )
    363     READ( 11 , '(A)') line
    364     CALL parin_fail_message( 'dynamics_parameters', line )
    365 
    366 12  CONTINUE
     353!-- Move to the beginning of the namelist file and try to find and read the namelist.
     354    REWIND( 11 )
     355    READ( 11, dynamics_parameters, IOSTAT=io_status )
     356
     357!
     358!-- Action depending on the READ status
     359    IF ( io_status > 0 )  THEN
     360!
     361!--    dynamics_parameters namelist was found, but contained errors. Print an error message
     362!--    including the line that caused the problem.
     363       BACKSPACE( 11 )
     364       READ( 11 , '(A)') line
     365       CALL parin_fail_message( 'dynamics_parameters', line )
     366
     367    ENDIF
    367368
    368369 END SUBROUTINE dynamics_parin
  • palm/trunk/SOURCE/gust_mod.f90

    r4828 r4842  
    2424! -----------------
    2525! $Id$
     26! reading of namelist file and actions in case of namelist errors revised so that statement labels
     27! and goto statements are not required any more
     28!
     29! 4828 2021-01-05 11:21:41Z Giersch
    2630! Enable 3D data output also with 64-bit precision
    2731!
     
    213217!> Parin for &gust_parameters for gust module
    214218!--------------------------------------------------------------------------------------------------!
    215     SUBROUTINE gust_parin
    216 
    217 
    218        IMPLICIT NONE
    219 
    220        CHARACTER (LEN=80)  ::  line  !< dummy string that contains the current line of the parameter file
    221 
    222        NAMELIST /gust_parameters/                                                                  &
    223           gust_module_enabled
    224 
    225        line = ' '
    226 !
    227 !--    Try to find gust module package
    228        REWIND ( 11 )
    229        line = ' '
    230        DO   WHILE ( INDEX( line, '&gust_parameters' ) == 0 )
    231           READ ( 11, '(A)', END=10 )  line
    232        ENDDO
    233        BACKSPACE ( 11 )
    234 !
    235 !--    Read user-defined namelist
    236        READ ( 11, gust_parameters )
    237 !
    238 !--    Set flag that indicates that the gust module is switched on
     219 SUBROUTINE gust_parin
     220
     221
     222    IMPLICIT NONE
     223
     224    CHARACTER(LEN=100)  ::  line  !< dummy string that contains the current line of the parameter
     225                                  !< file
     226    INTEGER(iwp)  ::  io_status   !< status after reading the namelist file
     227
     228
     229    NAMELIST /gust_parameters/  gust_module_enabled
     230
     231!
     232!-- Move to the beginning of the namelist file and try to find and read the namelist.
     233    REWIND( 11 )
     234    READ( 11, gust_parameters, IOSTAT=io_status )
     235
     236!
     237!-- Action depending on the READ status
     238    IF ( io_status == 0 )  THEN
     239!
     240!--    gust_parameters namelist was found and read correctly. Set flag that indicates that the gust
     241!--    module is switched on.
    239242       gust_module_enabled = .TRUE.
    240243
    241 10     CONTINUE
    242 
    243 
    244     END SUBROUTINE gust_parin
     244    ELSEIF ( io_status > 0 )  THEN
     245!
     246!--    gust_parameters namelist was found, but contained errors. Print an error message including
     247!--    the line that caused the problem.
     248       BACKSPACE( 11 )
     249       READ( 11 , '(A)') line
     250       CALL parin_fail_message( 'gust_parameters', line )
     251
     252    ENDIF
     253
     254 END SUBROUTINE gust_parin
    245255
    246256
  • palm/trunk/SOURCE/indoor_model_mod.f90

    r4828 r4842  
    2525! -----------------
    2626! $Id$
     27! reading of namelist file and actions in case of namelist errors revised so that statement labels
     28! and goto statements are not required any more
     29!
     30! 4828 2021-01-05 11:21:41Z Giersch
    2731! Change parameters for summer_pars and winter_pars (responsible: S. Rissmann)
    2832!
     
    19031907        CASE ( 'im_t_indoor_wall_win' )
    19041908           unit = 'K'
    1905            
     1909
    19061910        CASE ( 'im_t_indoor_wall' )
    19071911           unit = 'K'
     
    21232127
    21242128
    2125     CHARACTER (LEN=80) ::  line  !< string containing current line of file PARIN
     2129    CHARACTER(LEN=100) ::  line  !< string containing current line of file PARIN
     2130
     2131    INTEGER(iwp)  ::  io_status  !< status after reading the namelist file
     2132
    21262133
    21272134    NAMELIST /indoor_parameters/  indoor_during_spinup,                                            &
    21282135                                  initial_indoor_temperature
    21292136
    2130 
    2131 !
    2132 !-- Try to find indoor model package
    2133     REWIND ( 11 )
    2134     line = ' '
    2135     DO  WHILE ( INDEX( line, '&indoor_parameters' ) == 0 )
    2136        READ ( 11, '(A)', END=10 )  line
    2137     ENDDO
    2138     BACKSPACE ( 11 )
    2139 
    2140 !
    2141 !-- Read user-defined namelist
    2142     READ ( 11, indoor_parameters )
    2143 !
    2144 !-- Set flag that indicates that the indoor model is switched on
    2145     indoor_model = .TRUE.
     2137!
     2138!-- Move to the beginning of the namelist file and try to find and read the namelist.
     2139    REWIND( 11 )
     2140    READ( 11, indoor_parameters, IOSTAT=io_status )
     2141
     2142!
     2143!-- Action depending on the READ status
     2144    IF ( io_status == 0 )  THEN
     2145!
     2146!--    indoor_parameters namelist was found and read correctly. Set flag that indicates that the
     2147!--    indoor model is switched on.
     2148       indoor_model = .TRUE.
     2149
     2150    ELSEIF ( io_status > 0 )  THEN
     2151!
     2152!--    indoor_parameters namelist was found, but contained errors. Print an error message including
     2153!--    the line that caused the problem.
     2154       BACKSPACE( 11 )
     2155       READ( 11 , '(A)' ) line
     2156       CALL parin_fail_message( 'indoor_parameters', line )
     2157
     2158    ENDIF
    21462159
    21472160!
     
    21562169!        ENDIF
    21572170
    2158  10 CONTINUE
    2159 
    21602171 END SUBROUTINE im_parin
    21612172
  • palm/trunk/SOURCE/lagrangian_particle_model_mod.f90

    r4828 r4842  
    2424! -----------------
    2525! $Id$
     26! reading of namelist file and actions in case of namelist errors revised so that statement labels
     27! and goto statements are not required any more,
     28! deprecated namelist removed
     29!
     30! 4828 2021-01-05 11:21:41Z Giersch
    2631! output of particle time series added
    2732!
     
    569574 SUBROUTINE lpm_parin
    570575
    571     CHARACTER (LEN=80) ::  line  !<
    572 
    573     NAMELIST /particles_par/                                                                       &
    574        aero_species,                                                                               &
    575        aero_type,                                                                                  &
    576        aero_weight,                                                                                &
    577        alloc_factor,                                                                               &
    578        bc_par_b,                                                                                   &
    579        bc_par_lr,                                                                                  &
    580        bc_par_ns,                                                                                  &
    581        bc_par_t,                                                                                   &
    582        collision_kernel,                                                                           &
    583        curvature_solution_effects,                                                                 &
    584        deallocate_memory,                                                                          &
    585        density_ratio,                                                                              &
    586        dissipation_classes,                                                                        &
    587        dt_dopts,                                                                                   &
    588        dt_min_part,                                                                                &
    589        dt_prel,                                                                                    &
    590        dt_write_particle_data,                                                                     &
    591        end_time_prel,                                                                              &
    592        initial_weighting_factor,                                                                   &
    593        log_sigma,                                                                                  &
    594        max_number_particles_per_gridbox,                                                           &
    595        merging,                                                                                    &
    596        na,                                                                                         &
    597        number_concentration,                                                                       &
    598        number_of_particle_groups,                                                                  &
    599        number_particles_per_gridbox,                                                               &
    600        particles_per_point,                                                                        &
    601        particle_advection_start,                                                                   &
    602        particle_advection_interpolation,                                                           &
    603        particle_maximum_age,                                                                       &
    604        pdx,                                                                                        &
    605        pdy,                                                                                        &
    606        pdz,                                                                                        &
    607        psb,                                                                                        &
    608        psl,                                                                                        &
    609        psn,                                                                                        &
    610        psr,                                                                                        &
    611        pss,                                                                                        &
    612        pst,                                                                                        &
    613        radius,                                                                                     &
    614        radius_classes,                                                                             &
    615        radius_merge,                                                                               &
    616        radius_split,                                                                               &
    617        random_start_position,                                                                      &
    618        read_particles_from_restartfile,                                                            &
    619        rm,                                                                                         &
    620        seed_follows_topography,                                                                    &
    621        splitting,                                                                                  &
    622        splitting_factor,                                                                           &
    623        splitting_factor_max,                                                                       &
    624        splitting_function,                                                                         &
    625        splitting_mode,                                                                             &
    626        step_dealloc,                                                                               &
    627        use_sgs_for_particles,                                                                      &
    628        vertical_particle_advection,                                                                &
    629        weight_factor_merge,                                                                        &
    630        weight_factor_split,                                                                        &
    631        write_particle_statistics
     576    CHARACTER(LEN=100) ::  line  !< string containing current line of file PARIN
     577
     578    INTEGER(iwp) ::  io_status  !< status after reading the namelist file
    632579
    633580    NAMELIST /particle_parameters/                                                                 &
     
    699646
    700647!
    701 !-- Position the namelist-file at the beginning (it was already opened in parin), search for the
    702 !-- namelist-group of the package and position the file at this line. Do the same for each
    703 !-- optionally used package.
    704     line = ' '
    705 
    706 !
    707 !-- Try to find particles package
    708     REWIND ( 11 )
    709     line = ' '
    710     DO   WHILE ( INDEX( line, '&particle_parameters' ) == 0 )
    711        READ ( 11, '(A)', END=12 )  line
    712     ENDDO
    713     BACKSPACE ( 11 )
    714 !
    715 !-- Read user-defined namelist
    716     READ ( 11, particle_parameters, ERR = 10 )
    717 !
    718 !-- Set flag that indicates that particles are switched on
    719     particle_advection = .TRUE.
    720 
    721     GOTO 14
    722 
    723 10  BACKSPACE( 11 )
    724     READ( 11 , '(A)') line
    725     CALL parin_fail_message( 'particle_parameters', line )
    726 !
    727 !-- Try to find particles package (old namelist)
    728 12  REWIND ( 11 )
    729     line = ' '
    730     DO WHILE ( INDEX( line, '&particles_par' ) == 0 )
    731        READ ( 11, '(A)', END=14 )  line
    732     ENDDO
    733     BACKSPACE ( 11 )
    734 !
    735 !-- Read user-defined namelist
    736     READ ( 11, particles_par, ERR = 13, END = 14 )
    737 
    738     message_string = 'namelist particles_par is deprecated and will be ' //                        &
    739                      'removed in near future. Please use namelist ' //                             &
    740                      'particle_parameters instead'
    741     CALL message( 'package_parin', 'PA0487', 0, 1, 0, 6, 0 )
    742 
    743 !
    744 !-- Set flag that indicates that particles are switched on
    745     particle_advection = .TRUE.
    746 
    747     GOTO 14
    748 
    749 13    BACKSPACE( 11 )
    750        READ( 11 , '(A)') line
    751        CALL parin_fail_message( 'particles_par', line )
    752 
    753 14 CONTINUE
     648!-- Move to the beginning of the namelist file and try to find and read the namelist.
     649    REWIND( 11 )
     650    READ( 11, particle_parameters, IOSTAT=io_status )
     651!
     652!-- Action depending on the READ status
     653    IF ( io_status == 0 )  THEN
     654!
     655!--    particle_parameters namelist was found and read correctly. Set flag that indicates that
     656!--    particles are switched on.
     657       particle_advection = .TRUE.
     658
     659    ELSEIF ( io_status > 0 )  THEN
     660!
     661!--    particle_parameters namelist was found, but contained errors. Print an error message
     662!--    including the line that caused the error.
     663       BACKSPACE( 11 )
     664       READ( 11 , '(A)' ) line
     665       CALL parin_fail_message( 'particle_parameters', line )
     666
     667    ENDIF
    754668
    755669 END SUBROUTINE lpm_parin
     670
    756671
    757672!--------------------------------------------------------------------------------------------------!
  • palm/trunk/SOURCE/land_surface_model_mod.f90

    r4828 r4842  
    2424! -----------------
    2525! $Id$
     26! reading of namelist file and actions in case of namelist errors revised so that statement labels
     27! and goto statements are not required any more,
     28! deprecated namelist removed
     29!
     30! 4828 2021-01-05 11:21:41Z Giersch
    2631! Enable 3D data output also with 64-bit precision
    2732!
     
    49955000 SUBROUTINE lsm_parin
    49965001
    4997     USE control_parameters,                                                                        &
    4998         ONLY:  message_string
    4999 
    50005002    IMPLICIT NONE
    50015003
    5002     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    5003 
    5004     NAMELIST /lsm_par/         aero_resist_kray,                                                   &
    5005                                alpha_vangenuchten,                                                 &
    5006                                c_surface,                                                          &
    5007                                canopy_resistance_coefficient,                                      &
    5008                                constant_roughness,                                                 &
    5009                                conserve_water_content,                                             &
    5010                                deep_soil_temperature,                                              &
    5011                                dz_soil,                                                            &
    5012                                f_shortwave_incoming,                                               &
    5013                                field_capacity,                                                     &
    5014                                hydraulic_conductivity,                                             &
    5015                                l_vangenuchten,                                                     &
    5016                                lambda_surface_stable,                                              &
    5017                                lambda_surface_unstable,                                            &
    5018                                leaf_area_index,                                                    &
    5019                                min_canopy_resistance,                                              &
    5020                                min_soil_resistance,                                                &
    5021                                n_vangenuchten,                                                     &
    5022                                pavement_depth_level,                                               &
    5023                                pavement_heat_capacity,                                             &
    5024                                pavement_heat_conduct,                                              &
    5025                                pavement_type,                                                      &
    5026                                residual_moisture,                                                  &
    5027                                root_fraction,                                                      &
    5028                                saturation_moisture,                                                &
    5029                                skip_time_do_lsm,                                                   &
    5030                                soil_moisture,                                                      &
    5031                                soil_temperature,                                                   &
    5032                                soil_type,                                                          &
    5033                                surface_type,                                                       &
    5034                                vegetation_coverage,                                                &
    5035                                vegetation_type,                                                    &
    5036                                water_temperature,                                                  &
    5037                                water_type,                                                         &
    5038                                wilting_point,                                                      &
    5039                                z0_pavement,                                                        &
    5040                                z0_vegetation,                                                      &
    5041                                z0_water,                                                           &
    5042                                z0h_pavement,                                                       &
    5043                                z0h_vegetation,                                                     &
    5044                                z0h_water,                                                          &
    5045                                z0q_pavement,                                                       &
    5046                                z0q_vegetation,                                                     &
    5047                                z0q_water
     5004    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter
     5005                                 !< file
     5006    INTEGER(iwp)  ::  io_status  !< status after reading the nameslist file
     5007
    50485008
    50495009    NAMELIST /land_surface_parameters/  aero_resist_kray,                                          &
     
    50925052                                        z0q_water
    50935053
    5094     line = ' '
    5095 
    5096 !
    5097 !-- Try to find land surface model package
    5098     REWIND ( 11 )
    5099     line = ' '
    5100     DO WHILE ( INDEX( line, '&land_surface_parameters' ) == 0 )
    5101        READ ( 11, '(A)', END=12 )  line
    5102     ENDDO
    5103     BACKSPACE ( 11 )
    5104 
    5105 !
    5106 !-- Read user-defined namelist
    5107     READ ( 11, land_surface_parameters, ERR = 10 )
    5108 
    5109 !
    5110 !-- Set flag that indicates that the land surface model is switched on
    5111     land_surface = .TRUE.
    5112 
    5113     GOTO 14
    5114 
    5115 10  BACKSPACE( 11 )
    5116     READ( 11 , '(A)') line
    5117     CALL parin_fail_message( 'land_surface_parameters', line )
    5118 !
    5119 !-- Try to find old namelist
    5120 12  REWIND ( 11 )
    5121     line = ' '
    5122     DO WHILE ( INDEX( line, '&lsm_par' ) == 0 )
    5123        READ ( 11, '(A)', END=14 )  line
    5124     ENDDO
    5125     BACKSPACE ( 11 )
    5126 
    5127 !
    5128 !-- Read user-defined namelist
    5129     READ ( 11, lsm_par, ERR = 13, END = 14 )
    5130 
    5131     message_string = 'namelist lsm_par is deprecated and will be ' //                              &
    5132                      'removed in near future. Please use namelist ' //                             &
    5133                      'land_surface_parameters instead'
    5134     CALL message( 'lsm_parin', 'PA0487', 0, 1, 0, 6, 0 )
    5135 
    5136 !
    5137 !-- Set flag that indicates that the land surface model is switched on
    5138     land_surface = .TRUE.
    5139 
    5140     GOTO 14
    5141 
    5142 13  BACKSPACE( 11 )
    5143     READ( 11 , '(A)') line
    5144     CALL parin_fail_message( 'lsm_par', line )
    5145 
    5146 
    5147 14  CONTINUE
    5148 
     5054!
     5055!-- Move to the beginning of the namelist file and try to find and read the namelist.
     5056    REWIND( 11 )
     5057    READ( 11, land_surface_parameters, IOSTAT=io_status )
     5058
     5059!
     5060!-- Action depending on the READ status
     5061    IF ( io_status == 0 )  THEN
     5062!
     5063!--    land_surface_parameters namelist was found and read correctly. Set flag that indicates that
     5064!--    the land surface model is switched on.
     5065       land_surface = .TRUE.
     5066
     5067    ELSEIF ( io_status > 0 )  THEN
     5068!
     5069!--    land_surface_parameters namelist was found but contained errors. Print an error message
     5070!--    including the line that caused the problem.
     5071       BACKSPACE( 11 )
     5072       READ( 11 , '(A)') line
     5073       CALL parin_fail_message( 'land_surface_parameters', line )
     5074
     5075    ENDIF
    51495076
    51505077 END SUBROUTINE lsm_parin
  • palm/trunk/SOURCE/multi_agent_system_mod.f90

    r4828 r4842  
    2424! -----------------
    2525! $Id$
     26! reading of namelist file and actions in case of namelist errors revised so that statement labels
     27! and goto statements are not required any more
     28!
     29! 4828 2021-01-05 11:21:41Z Giersch
    2630! file re-formatted to follow the PALM coding standard
    2731!
     
    36553659    IMPLICIT NONE
    36563660
    3657     CHARACTER (LEN=80) ::  line  !<
     3661    CHARACTER(LEN=100) ::  line  !< dummy string for current line in namelist file
     3662
     3663    INTEGER(iwp)  ::  io_status  !< status after reading the namelist file
     3664
    36583665
    36593666    NAMELIST /agent_parameters/  a_rand_target,                                                    &
     
    36993706
    37003707!
    3701 !-- Try to find agent package
     3708!-- Move to the beginning of the namelist file and try to find and read the namelist.
    37023709    REWIND ( 11 )
    3703     line = ' '
    3704     DO WHILE ( INDEX( line, '&agent_parameters' ) == 0 )
    3705        READ ( 11, '(A)', END=20 )  line
    3706     ENDDO
    3707     BACKSPACE ( 11 )
    3708 
    3709 !
    3710 !-- Read user-defined namelist
    3711     READ ( 11, agent_parameters, ERR = 10, END = 20 )
    3712 
    3713 !
    3714 !-- Set flag that indicates that agents are switched on
    3715     agents_active = .TRUE.
    3716     GOTO 20
    3717 
    3718 10    BACKSPACE( 11 )
    3719     READ( 11 , '(A)') line
    3720     CALL parin_fail_message( 'agent_parameters', line )
    3721 
    3722 20    CONTINUE
     3710    READ ( 11, agent_parameters, IOSTAT=io_status )
     3711
     3712!
     3713!-- Action depending on the READ status
     3714    IF ( io_status == 0 )  THEN
     3715!
     3716!--    agent_parameters namelist was found and read correctly. Set flag that indicates that agents
     3717!--    are switched on.
     3718       agents_active = .TRUE.
     3719
     3720    ELSEIF ( io_status > 0 )  THEN
     3721!
     3722!--    agent_parameters namelist was found but contained errors. Print an error message including
     3723!--    the line that caused the problem.
     3724       BACKSPACE( 11 )
     3725       READ( 11 , '(A)') line
     3726       CALL parin_fail_message( 'agent_parameters', line )
     3727
     3728    ENDIF
    37233729
    37243730 END SUBROUTINE mas_parin
  • palm/trunk/SOURCE/nesting_offl_mod.f90

    r4834 r4842  
    2424! -----------------
    2525! $Id$
     26! reading of namelist file and actions in case of namelist errors revised so that statement labels
     27! and goto statements are not required any more
     28!
     29! 4834 2021-01-07 10:28:00Z raasch
    2630! file re-formatted to follow the PALM coding standard
    2731!
     
    24482452 SUBROUTINE nesting_offl_parin
    24492453
    2450     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    2451 
    2452 
    2453     NAMELIST /nesting_offl_parameters/   nesting_offline
    2454 
    2455     line = ' '
    2456 
    2457 !
    2458 !-- Try to find stg package
    2459     REWIND ( 11 )
    2460     line = ' '
    2461     DO WHILE ( INDEX( line, '&nesting_offl_parameters' ) == 0 )
    2462        READ ( 11, '(A)', END=20 )  line
    2463     ENDDO
    2464     BACKSPACE ( 11 )
    2465 
    2466 !
    2467 !-- Read namelist
    2468     READ ( 11, nesting_offl_parameters, ERR = 10, END = 20 )
    2469 
    2470     GOTO 20
    2471 
    2472 10    BACKSPACE( 11 )
    2473     READ( 11 , '(A)') line
    2474     CALL parin_fail_message( 'nesting_offl_parameters', line )
    2475 
    2476 20    CONTINUE
    2477 
     2454    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter file
     2455    INTEGER(iwp) ::  io_status   !< status after reading the namelist file
     2456
     2457
     2458    NAMELIST /nesting_offl_parameters/  nesting_offline
     2459
     2460!
     2461!-- Move to the beginning of the namelist file and try to find and read the namelist.
     2462    REWIND( 11 )
     2463    READ( 11, nesting_offl_parameters, IOSTAT=io_status )
     2464
     2465!
     2466!-- Action depending on the READ status
     2467    IF ( io_status > 0 )  THEN
     2468!
     2469!--    nesting_offl_parameters namelist was found but contained errors. Print an error message
     2470!--    including the line that caused the problem.
     2471       BACKSPACE( 11 )
     2472       READ( 11 , '(A)' ) line
     2473       CALL parin_fail_message( 'nesting_offl_parameters', line )
     2474
     2475    ENDIF
    24782476
    24792477 END SUBROUTINE nesting_offl_parin
     2478
    24802479
    24812480!--------------------------------------------------------------------------------------------------!
     
    25002499
    25012500 END SUBROUTINE nesting_offl_header
     2501
    25022502
    25032503!--------------------------------------------------------------------------------------------------!
  • palm/trunk/SOURCE/ocean_mod.f90

    r4828 r4842  
    2424! -----------------
    2525! $Id$
     26! reading of namelist file and actions in case of namelist errors revised so that statement labels
     27! and goto statements are not required any more
     28!
     29! 4828 2021-01-05 11:21:41Z Giersch
    2630! file re-formatted to follow the PALM coding standard
    2731!
     
    572576    IMPLICIT NONE
    573577
    574     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    575 
    576 
    577     NAMELIST /ocean_parameters/  bc_sa_t, bottom_salinityflux, salinity, sa_surface,               &
    578                                  sa_vertical_gradient, sa_vertical_gradient_level,                 &
    579                                  stokes_waveheight, stokes_wavelength, surface_cooling_spinup_time,&
    580                                  top_salinityflux, wall_salinityflux, wave_breaking
    581 
    582 !
    583 !-- Try to find the namelist
    584     REWIND ( 11 )
    585     line = ' '
    586     DO WHILE ( INDEX( line, '&ocean_parameters' ) == 0 )
    587        READ ( 11, '(A)', END=12 )  line
    588     ENDDO
    589     BACKSPACE ( 11 )
    590 
    591 !
    592 !-- Read namelist
    593     READ ( 11, ocean_parameters, ERR = 10 )
    594 !
    595 !-- Set switch that enables PALM's ocean mode
    596     ocean_mode = .TRUE.
    597 
    598     GOTO 12
    599 
    600  10 BACKSPACE( 11 )
    601     READ( 11 , '(A)') line
    602     CALL parin_fail_message( 'ocean_parameters', line )
    603 
    604  12 CONTINUE
     578    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter
     579                                 !< file
     580    INTEGER(iwp)  ::  io_status  !< status after reading the namelist file
     581
     582
     583    NAMELIST /ocean_parameters/  bc_sa_t,                                                          &
     584                                 bottom_salinityflux,                                              &
     585                                 salinity,                                                         &
     586                                 sa_surface,                                                       &
     587                                 sa_vertical_gradient,                                             &
     588                                 sa_vertical_gradient_level,                                       &
     589                                 stokes_waveheight,                                                &
     590                                 stokes_wavelength,                                                &
     591                                 surface_cooling_spinup_time,                                      &
     592                                 top_salinityflux,                                                 &
     593                                 wall_salinityflux,                                                &
     594                                 wave_breaking
     595
     596!
     597!-- Move to the beginning of the namelist file and try to find and read the namelist called
     598!-- ocean_parameters.
     599    REWIND( 11 )
     600    READ( 11, ocean_parameters, IOSTAT=io_status )
     601
     602!
     603!-- Action depending on the READ status
     604    IF ( io_status == 0 )  THEN
     605!
     606!--    ocean_parameters namelist was found and read correctly. Set switch that enables PALM's ocean
     607!--    mode.
     608       ocean_mode = .TRUE.
     609
     610    ELSEIF ( io_status > 0 )  THEN
     611!
     612!--    ocean_parameters namelist was found but contained errors. Print an error message including
     613!--    the line that caused the problem.
     614       BACKSPACE( 11 )
     615       READ( 11 , '(A)') line
     616       CALL parin_fail_message( 'ocean_parameters', line )
     617
     618    ENDIF
    605619
    606620 END SUBROUTINE ocean_parin
     621
    607622
    608623!--------------------------------------------------------------------------------------------------!
  • palm/trunk/SOURCE/parin.f90

    r4828 r4842  
    2424! -----------------
    2525! $Id$
     26! reading of namelist file and actions in case of namelist errors revised so that statement labels
     27! and goto statements are not required any more,
     28! deprecated namelists removed
     29!
     30! 4828 2021-01-05 11:21:41Z Giersch
    2631! file re-formatted to follow the PALM coding standard
    2732!
     
    162167    IMPLICIT NONE
    163168
    164     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
     169    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter
     170                                 !< file
    165171
    166172    INTEGER(iwp) ::  global_id      !< process id with respect to MPI_COMM_WORLD
    167173    INTEGER(iwp) ::  global_procs   !< # of procs with respect to MPI_COMM_WORLD
    168174    INTEGER(iwp) ::  i              !<
    169     INTEGER(iwp) ::  ioerr          !< error flag for open/read/write
    170 
    171     NAMELIST /inipar/  alpha_surface,                                                              &
    172                        approximation,                                                              &
    173                        bc_e_b,                                                                     &
    174                        bc_lr,                                                                      &
    175                        bc_ns,                                                                      &
    176                        bc_p_b,                                                                     &
    177                        bc_p_t,                                                                     &
    178                        bc_pt_b,                                                                    &
    179                        bc_pt_t,                                                                    &
    180                        bc_q_b,                                                                     &
    181                        bc_q_t,                                                                     &
    182                        bc_s_b,                                                                     &
    183                        bc_s_t,                                                                     &
    184                        bc_uv_b,                                                                    &
    185                        bc_uv_t,                                                                    &
    186                        building_height,                                                            &
    187                        building_length_x,                                                          &
    188                        building_length_y,                                                          &
    189                        building_wall_left,                                                         &
    190                        building_wall_south,                                                        &
    191                        calc_soil_moisture_during_spinup,                                           &
    192                        call_psolver_at_all_substeps,                                               &
    193                        canyon_height,                                                              &
    194                        canyon_wall_left,                                                           &
    195                        canyon_wall_south,                                                          &
    196                        canyon_width_x,                                                             &
    197                        canyon_width_y,                                                             &
    198                        cfl_factor,                                                                 &
    199                        check_realistic_q,                                                          &
    200                        cloud_droplets,                                                             &
    201                        collective_wait,                                                            &
    202                        complex_terrain,                                                            &
    203                        conserve_volume_flow,                                                       &
    204                        conserve_volume_flow_mode,                                                  &
    205                        constant_flux_layer,                                                        &
    206                        coupling_start_time,                                                        &
    207                        cycle_mg,                                                                   &
    208                        damp_level_1d,                                                              &
    209                        data_output_during_spinup,                                                  &
    210                        dissipation_1d,                                                             &
    211                        dp_external,                                                                &
    212                        dp_level_b,                                                                 &
    213                        dp_smooth,                                                                  &
    214                        dpdxy,                                                                      &
    215                        dt,                                                                         &
    216                        dt_pr_1d,                                                                   &
    217                        dt_run_control_1d,                                                          &
    218                        dt_spinup,                                                                  &
    219                        dx,                                                                         &
    220                        dy,                                                                         &
    221                        dz,                                                                         &
    222                        dz_max,                                                                     &
    223                        dz_stretch_factor,                                                          &
    224                        dz_stretch_level,                                                           &
    225                        dz_stretch_level_end,                                                       &
    226                        dz_stretch_level_start,                                                     &
    227                        e_init,                                                                     &
    228                        e_min,                                                                      &
    229                        end_time_1d,                                                                &
    230                        ensemble_member_nr,                                                         &
    231                        fft_method,                                                                 &
    232                        flux_input_mode,                                                            &
    233                        flux_output_mode,                                                           &
    234                        galilei_transformation,                                                     &
    235                        humidity,                                                                   &
    236                        inflow_damping_height,                                                      &
    237                        inflow_damping_width,                                                       &
    238                        inflow_disturbance_begin,                                                   &
    239                        inflow_disturbance_end,                                                     &
    240                        initializing_actions,                                                       &
    241                        km_constant,                                                                &
    242                        large_scale_forcing,                                                        &
    243                        large_scale_subsidence,                                                     &
    244                        latitude,                                                                   &
    245                        longitude,                                                                  &
    246                        loop_optimization,                                                          &
    247                        lsf_exception,                                                              &
    248                        masking_method,                                                             &
    249                        mg_cycles,                                                                  &
    250                        mg_switch_to_pe0_level,                                                     &
    251                        mixing_length_1d,                                                           &
    252                        momentum_advec,                                                             &
    253                        monotonic_limiter_z,                                                        &
    254                        netcdf_precision,                                                           &
    255                        neutral,                                                                    &
    256                        ngsrb,                                                                      &
    257                        nsor,                                                                       &
    258                        nsor_ini,                                                                   &
    259                        nudging,                                                                    &
    260                        nx,                                                                         &
    261                        ny,                                                                         &
    262                        nz,                                                                         &
    263                        ocean_mode,                                                                 &
    264                        omega,                                                                      &
    265                        omega_sor,                                                                  &
    266                        origin_date_time,                                                           &
    267                        outflow_source_plane,                                                       &
    268                        passive_scalar,                                                             &
    269                        prandtl_number,                                                             &
    270                        psolver,                                                                    &
    271                        pt_damping_factor,                                                          &
    272                        pt_damping_width,                                                           &
    273                        pt_reference,                                                               &
    274                        pt_surface,                                                                 &
    275                        pt_surface_heating_rate,                                                    &
    276                        pt_surface_initial_change,                                                  &
    277                        pt_vertical_gradient,                                                       &
    278                        pt_vertical_gradient_level,                                                 &
    279                        q_surface,                                                                  &
    280                        q_surface_initial_change,                                                   &
    281                        q_vertical_gradient,                                                        &
    282                        q_vertical_gradient_level,                                                  &
    283                        random_generator,                                                           &
    284                        random_heatflux,                                                            &
    285                        rans_const_c,                                                               &
    286                        rans_const_sigma,                                                           &
    287                        rayleigh_damping_factor,                                                    &
    288                        rayleigh_damping_height,                                                    &
    289                        recycling_method_for_thermodynamic_quantities,                              &
    290                        recycling_width,                                                            &
    291                        reference_state,                                                            &
    292                        residual_limit,                                                             &
    293                        rotation_angle,                                                             &
    294                        roughness_length,                                                           &
    295                        scalar_advec,                                                               &
    296                        scalar_rayleigh_damping,                                                    &
    297                        spinup_time,                                                                &
    298                        spinup_pt_amplitude,                                                        &
    299                        spinup_pt_mean,                                                             &
    300                        statistic_regions,                                                          &
    301                        subs_vertical_gradient,                                                     &
    302                        subs_vertical_gradient_level,                                               &
    303                        surface_heatflux,                                                           &
    304                        surface_pressure,                                                           &
    305                        surface_scalarflux,                                                         &
    306                        surface_waterflux,                                                          &
    307                        s_surface,                                                                  &
    308                        s_surface_initial_change,                                                   &
    309                        s_vertical_gradient,                                                        &
    310                        s_vertical_gradient_level,                                                  &
    311                        timestep_scheme,                                                            &
    312                        topography,                                                                 &
    313                        topography_grid_convention,                                                 &
    314                        top_heatflux,                                                               &
    315                        top_momentumflux_u,                                                         &
    316                        top_momentumflux_v,                                                         &
    317                        top_scalarflux,                                                             &
    318                        transpose_compute_overlap,                                                  &
    319                        tunnel_height,                                                              &
    320                        tunnel_length,                                                              &
    321                        tunnel_wall_depth,                                                          &
    322                        tunnel_width_x,                                                             &
    323                        tunnel_width_y,                                                             &
    324                        turbulence_closure,                                                         &
    325                        turbulent_inflow,                                                           &
    326                        turbulent_outflow,                                                          &
    327                        u_bulk,                                                                     &
    328                        u_profile,                                                                  &
    329                        ug_surface,                                                                 &
    330                        ug_vertical_gradient,                                                       &
    331                        ug_vertical_gradient_level,                                                 &
    332                        use_cmax,                                                                   &
    333                        use_fixed_date,                                                             &
    334                        use_fixed_time,                                                             &
    335                        use_free_convection_scaling,                                                &
    336                        use_ug_for_galilei_tr,                                                      &
    337                        use_subsidence_tendencies,                                                  &
    338                        use_surface_fluxes,                                                         &
    339                        use_top_fluxes,                                                             &
    340                        use_upstream_for_tke,                                                       &
    341                        uv_heights,                                                                 &
    342                        v_bulk,                                                                     &
    343                        v_profile,                                                                  &
    344                        vdi_checks,                                                                 &
    345                        vg_surface,                                                                 &
    346                        vg_vertical_gradient,                                                       &
    347                        vg_vertical_gradient_level,                                                 &
    348                        wall_adjustment,                                                            &
    349                        wall_heatflux,                                                              &
    350                        wall_humidityflux,                                                          &
    351                        wall_scalarflux,                                                            &
    352                        y_shift,                                                                    &
    353                        zeta_max,                                                                   &
    354                        zeta_min,                                                                   &
    355                        z0h_factor
     175    INTEGER(iwp) ::  io_status      !< status after reading the namelist files
     176
    356177
    357178    NAMELIST /initialization_parameters/  alpha_surface,                                           &
     
    541362                                          z0h_factor
    542363
    543     NAMELIST /d3par/  averaging_interval,                                                          &
    544                       averaging_interval_pr,                                                       &
    545                       cpu_log_barrierwait,                                                         &
    546                       create_disturbances,                                                         &
    547                       cross_profiles,                                                              &
    548                       data_output,                                                                 &
    549                       data_output_2d_on_each_pe,                                                   &
    550                       data_output_masks,                                                           &
    551                       data_output_pr,                                                              &
    552                       debug_output,                                                                &
    553                       debug_output_timestep,                                                       &
    554                       disturbance_amplitude,                                                       &
    555                       disturbance_energy_limit,                                                    &
    556                       disturbance_level_b,                                                         &
    557                       disturbance_level_t,                                                         &
    558                       do2d_at_begin,                                                               &
    559                       do3d_at_begin,                                                               &
    560                       dt,                                                                          &
    561                       dt_averaging_input,                                                          &
    562                       dt_averaging_input_pr,                                                       &
    563                       dt_coupling,                                                                 &
    564                       dt_data_output,                                                              &
    565                       dt_data_output_av,                                                           &
    566                       dt_disturb,                                                                  &
    567                       dt_domask,                                                                   &
    568                       dt_dopr,                                                                     &
    569                       dt_dopr_listing,                                                             &
    570                       dt_dots,                                                                     &
    571                       dt_do2d_xy,                                                                  &
    572                       dt_do2d_xz,                                                                  &
    573                       dt_do2d_yz,                                                                  &
    574                       dt_do3d,                                                                     &
    575                       dt_max,                                                                      &
    576                       dt_restart,                                                                  &
    577                       dt_run_control,                                                              &
    578                       end_time,                                                                    &
    579                       force_print_header,                                                          &
    580                       mask_k_over_surface,                                                         &
    581                       mask_scale_x,                                                                &
    582                       mask_scale_y,                                                                &
    583                       mask_scale_z,                                                                &
    584                       mask_x,                                                                      &
    585                       mask_y,                                                                      &
    586                       mask_z,                                                                      &
    587                       mask_x_loop,                                                                 &
    588                       mask_y_loop,                                                                 &
    589                       mask_z_loop,                                                                 &
    590                       netcdf_data_format,                                                          &
    591                       netcdf_deflate,                                                              &
    592                       normalizing_region,                                                          &
    593                       npex,                                                                        &
    594                       npey,                                                                        &
    595                       nz_do3d,                                                                     &
    596                       profile_columns,                                                             &
    597                       profile_rows,                                                                &
    598                       restart_time,                                                                &
    599                       section_xy,                                                                  &
    600                       section_xz,                                                                  &
    601                       section_yz,                                                                  &
    602                       skip_time_data_output,                                                       &
    603                       skip_time_data_output_av,                                                    &
    604                       skip_time_dopr,                                                              &
    605                       skip_time_do2d_xy,                                                           &
    606                       skip_time_do2d_xz,                                                           &
    607                       skip_time_do2d_yz,                                                           &
    608                       skip_time_do3d,                                                              &
    609                       skip_time_domask,                                                            &
    610                       synchronous_exchange,                                                        &
    611                       termination_time_needed
    612 
    613364    NAMELIST /runtime_parameters/  averaging_interval,                                             &
    614365                                   averaging_interval_pr,                                          &
     
    699450    CALL location_message( 'reading environment parameters from ENVPAR', 'start' )
    700451
    701     OPEN( 90, FILE='ENVPAR', STATUS='OLD', FORM='FORMATTED', IOSTAT=ioerr )
    702 
    703     IF ( ioerr /= 0 )  THEN
     452    OPEN( 90, FILE='ENVPAR', STATUS='OLD', FORM='FORMATTED', IOSTAT=io_status )
     453
     454    IF ( io_status /= 0 )  THEN
    704455       message_string = 'local file ENVPAR not found' //                                           &
    705456                        '&some variables for steering may not be properly set'
    706457       CALL message( 'parin', 'PA0276', 0, 1, 0, 6, 0 )
    707458    ELSE
    708        READ( 90, envpar, IOSTAT=ioerr )
    709        IF ( ioerr < 0 )  THEN
     459       READ( 90, envpar, IOSTAT=io_status )
     460       IF ( io_status < 0 )  THEN
    710461          message_string = 'no envpar-NAMELIST found in local file '  //                           &
    711                            'ENVPAR& or some variables for steering may '  //   &
    712                            'not be properly set'
     462                           'ENVPAR& or some variables for steering may not be properly set'
    713463          CALL message( 'parin', 'PA0278', 0, 1, 0, 6, 0 )
    714        ELSEIF ( ioerr > 0 )  THEN
     464       ELSEIF ( io_status > 0 )  THEN
    715465          message_string = 'errors in local file ENVPAR' //                                        &
    716466                           '&some variables for steering may not be properly set'
     
    730480!
    731481!-- Read the control parameters for initialization.
    732 !-- The namelist "inipar" must be provided in the NAMELIST-file.
    733     READ ( 11, initialization_parameters, ERR=10, END=11 )
    734     GOTO 14
    735 
    736  10 BACKSPACE( 11 )
    737     READ( 11 , '(A)') line
    738     CALL parin_fail_message( 'initialization_parameters', line )
    739 
    740  11 REWIND ( 11 )
    741     READ( 11, inipar, ERR=12, END=13 )
    742 
    743     message_string = 'namelist inipar is deprecated and will be ' //                               &
    744                      'removed in near future. & Please use namelist ' //                           &
    745                      'initialization_parameters instead'
    746     CALL message( 'parin', 'PA0017', 0, 1, 0, 6, 0 )
    747 
    748     GOTO 14
    749 
    750  12 BACKSPACE( 11 )
    751     READ( 11 , '(A)') line
    752     CALL parin_fail_message( 'inipar', line )
    753 
    754  13 message_string = 'no initialization_parameters-namelist found'
    755     CALL message( 'parin', 'PA0272', 1, 2, 0, 6, 0 )
    756 
     482!-- The namelist "initialisation_parameters" must be provided in the NAMELIST-file.
     483    READ( 11, initialization_parameters, IOSTAT=io_status )
     484
     485!
     486!-- Action depending on the READ status
     487    IF ( io_status > 0 )  THEN
     488!
     489!--    initialisation_parameters namelist was found but countained errors. Print an error message
     490!-     including the line that caused the problem.
     491       BACKSPACE( 11 )
     492       READ( 11 , '(A)' ) line
     493       CALL parin_fail_message( 'initialization_parameters', line )
     494
     495    ELSEIF ( io_status < 0 )  THEN
     496!
     497!--    initialisation_parametes namelist was not found. Return a message.
     498       message_string = 'no initialization_parameters-namelist found'
     499       CALL message( 'parin', 'PA0272', 1, 2, 0, 6, 0 )
     500
     501    ENDIF
    757502!
    758503!-- Try to read runtime parameters given by the user for this run (namelist "runtime_parameters").
    759504!-- The namelist "runtime_parmeters" can be omitted. In that case default values are used for the
    760505!-- parameters.
    761  14 line = ' '
    762 
    763506    REWIND( 11 )
    764     line = ' '
    765     DO WHILE ( INDEX( line, '&runtime_parameters' ) == 0 )
    766        READ( 11, '(A)', END=16 )  line
    767     ENDDO
    768     BACKSPACE( 11 )
    769 
    770 !
    771 !-- Read namelist
    772     READ( 11, runtime_parameters, ERR = 15 )
    773     GOTO 18
    774 
    775  15 BACKSPACE( 11 )
    776     READ( 11 , '(A)') line
    777     CALL parin_fail_message( 'runtime_parameters', line )
    778 
    779  16 REWIND( 11 )
    780     line = ' '
    781     DO WHILE ( INDEX( line, '&d3par' ) == 0 )
    782        READ( 11, '(A)', END=18 )  line
    783     ENDDO
    784     BACKSPACE ( 11 )
    785 
    786 !
    787 !-- Read namelist
    788     READ( 11, d3par, ERR = 17, END = 18 )
    789 
    790     message_string = 'namelist d3par is deprecated and will be ' //                                &
    791                      'removed in near future. &Please use namelist ' //                            &
    792                      'runtime_parameters instead'
    793     CALL message( 'parin', 'PA0487', 0, 1, 0, 6, 0 )
    794 
    795     GOTO 18
    796 
    797  17 BACKSPACE( 11 )
    798     READ( 11 , '(A)') line
    799     CALL parin_fail_message( 'd3par', line )
    800 
    801  18 CONTINUE
     507    READ( 11, runtime_parameters, IOSTAT=io_status )
     508
     509    IF ( io_status > 0 )  THEN
     510!
     511!--    Namelist runtime_parameters was found but contained errors. Print an error message including
     512!--    the line that caused the problem.
     513       BACKSPACE( 11 )
     514       READ( 11 , '(A)') line
     515       CALL parin_fail_message( 'runtime_parameters', line )
     516
     517    ENDIF
    802518
    803519!
  • palm/trunk/SOURCE/plant_canopy_model_mod.f90

    r4828 r4842  
    2626! -----------------
    2727! $Id$
     28! reading of namelist file and actions in case of namelist errors revised so that statement labels
     29! and goto statements are not required any more,
     30! deprecaed namelist name removed
     31!
     32! 4828 2021-01-05 11:21:41Z Giersch
    2833! file re-formatted to follow the PALM coding standard
    2934!
     
    15501555!> Parin for &plant_canopy_parameters for plant canopy model
    15511556!--------------------------------------------------------------------------------------------------!
    1552     SUBROUTINE pcm_parin
    1553 
    1554        CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    1555 
    1556        NAMELIST /plant_canopy_parameters/  alpha_lad,                                              &
    1557                                            beta_lad,                                               &
    1558                                            canopy_drag_coeff,                                      &
    1559                                            canopy_mode,                                            &
    1560                                            cthf,                                                   &
    1561                                            lad_surface,                                            &
    1562                                            lad_type_coef,                                          &
    1563                                            lad_vertical_gradient,                                  &
    1564                                            lad_vertical_gradient_level,                            &
    1565                                            lai_beta,                                               &
    1566                                            leaf_scalar_exch_coeff,                                 &
    1567                                            leaf_surface_conc,                                      &
    1568                                            pch_index,                                              &
    1569                                            plant_canopy_transpiration
    1570 
    1571        NAMELIST /canopy_par/               alpha_lad,                                              &
    1572                                            beta_lad,                                               &
    1573                                            canopy_drag_coeff,                                      &
    1574                                            canopy_mode,                                            &
    1575                                            cthf,                                                   &
    1576                                            lad_surface,                                            &
    1577                                            lad_type_coef,                                          &
    1578                                            lad_vertical_gradient,                                  &
    1579                                            lad_vertical_gradient_level,                            &
    1580                                            lai_beta,                                               &
    1581                                            leaf_scalar_exch_coeff,                                 &
    1582                                            leaf_surface_conc,                                      &
    1583                                            pch_index,                                              &
    1584                                            plant_canopy_transpiration
    1585 
    1586        line = ' '
    1587 
    1588 !
    1589 !--    Try to find plant-canopy model package
    1590        REWIND( 11 )
    1591        line = ' '
    1592        DO WHILE ( INDEX( line, '&plant_canopy_parameters' ) == 0 )
    1593           READ( 11, '(A)', END=12 )  line
    1594        ENDDO
     1557 SUBROUTINE pcm_parin
     1558
     1559    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter file
     1560
     1561    INTEGER(iwp) ::  io_status   !< status after reading the namelist file
     1562
     1563
     1564    NAMELIST /plant_canopy_parameters/  alpha_lad,                                                 &
     1565                                        beta_lad,                                                  &
     1566                                        canopy_drag_coeff,                                         &
     1567                                        canopy_mode,                                               &
     1568                                        cthf,                                                      &
     1569                                        lad_surface,                                               &
     1570                                        lad_type_coef,                                             &
     1571                                        lad_vertical_gradient,                                     &
     1572                                        lad_vertical_gradient_level,                               &
     1573                                        lai_beta,                                                  &
     1574                                        leaf_scalar_exch_coeff,                                    &
     1575                                        leaf_surface_conc,                                         &
     1576                                        pch_index,                                                 &
     1577                                        plant_canopy_transpiration
     1578
     1579!
     1580!-- Move to the beginning of the namelist file and try to find and read the user-defined namelist
     1581!-- plant_canopy_parameters.
     1582    REWIND( 11 )
     1583    READ( 11, plant_canopy_parameters, IOSTAT=io_status )
     1584
     1585!
     1586!-- Action depending on the READ status
     1587    IF ( io_status == 0 )  THEN
     1588!
     1589!--    plant_canopy_parameters namelist was found and read correctly. Set flag that indicates that
     1590!--    the plant-canopy model is switched on.
     1591       plant_canopy = .TRUE.
     1592
     1593    ELSEIF ( io_status > 0 )  THEN
     1594!
     1595!--    plant_canopy_parameters namelist was found but contained errors. Print an error message
     1596!--    including the line that caused the problem.
    15951597       BACKSPACE( 11 )
    1596 
    1597 !
    1598 !--    Read user-defined namelist
    1599        READ( 11, plant_canopy_parameters, ERR = 10 )
    1600 
    1601 !
    1602 !--    Set flag that indicates that the plant-canopy model is switched on
    1603        plant_canopy = .TRUE.
    1604 
    1605        GOTO 14
    1606 
    1607  10    BACKSPACE( 11 )
    1608        READ( 11 , '(A)') line
     1598       READ( 11 , '(A)' ) line
    16091599       CALL parin_fail_message( 'plant_canopy_parameters', line )
    1610 !
    1611 !--    Try to find old namelist
    1612  12    REWIND( 11 )
    1613        line = ' '
    1614        DO WHILE ( INDEX( line, '&canopy_par' ) == 0 )
    1615           READ( 11, '(A)', END=14 )  line
    1616        ENDDO
    1617        BACKSPACE( 11 )
    1618 
    1619 !
    1620 !--    Read user-defined namelist
    1621        READ( 11, canopy_par, ERR = 13, END = 14 )
    1622 
    1623        message_string = 'namelist canopy_par is deprecated and will be ' //                        &
    1624                         'removed in near future. Please use namelist ' //                          &
    1625                         'plant_canopy_parameters instead'
    1626        CALL message( 'pcm_parin', 'PA0487', 0, 1, 0, 6, 0 )
    1627 
    1628 !
    1629 !--    Set flag that indicates that the plant-canopy model is switched on
    1630        plant_canopy = .TRUE.
    1631 
    1632        GOTO 14
    1633 
    1634  13    BACKSPACE( 11 )
    1635        READ( 11 , '(A)') line
    1636        CALL parin_fail_message( 'canopy_par', line )
    1637 
    1638  14    CONTINUE
    1639 
    1640     END SUBROUTINE pcm_parin
     1600
     1601    ENDIF
     1602
     1603 END SUBROUTINE pcm_parin
    16411604
    16421605
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r4836 r4842  
    2727! -----------------
    2828! $Id$
    29 ! openmp bugfix: some missing arrays added to reduction clause
     29! reading of namelist file and actions in case of namelist errors revised so that statement labels
     30! and goto statements are not required any more,
     31! deprectaed namelist name removed
     32!
     33! 4836 2021-01-07 13:58:12Z raasch
     34! openmp bugfix: some missing arrays added to reduction clause
    3035!
    3136! 4824 2020-12-12 20:45:23Z moh.hefny
     
    717722                                   0.06_wp, 0.06_wp, 0.06_wp,            & !  1 - ocean
    718723                                   0.19_wp, 0.28_wp, 0.09_wp,            & !  2 - mixed farming, tall grassland
    719                                    0.23_wp, 0.33_wp, 0.11_wp,            & !  3 - tall/medium grassland 
    720                                    0.23_wp, 0.33_wp, 0.11_wp,            & !  4 - evergreen shrubland 
    721                                    0.25_wp, 0.34_wp, 0.14_wp,            & !  5 - short grassland/meadow/shrubland 
    722                                    0.14_wp, 0.22_wp, 0.06_wp,            & !  6 - evergreen needleleaf forest 
    723                                    0.17_wp, 0.27_wp, 0.06_wp,            & !  7 - mixed deciduous forest 
    724                                    0.19_wp, 0.31_wp, 0.06_wp,            & !  8 - deciduous forest 
     724                                   0.23_wp, 0.33_wp, 0.11_wp,            & !  3 - tall/medium grassland
     725                                   0.23_wp, 0.33_wp, 0.11_wp,            & !  4 - evergreen shrubland
     726                                   0.25_wp, 0.34_wp, 0.14_wp,            & !  5 - short grassland/meadow/shrubland
     727                                   0.14_wp, 0.22_wp, 0.06_wp,            & !  6 - evergreen needleleaf forest
     728                                   0.17_wp, 0.27_wp, 0.06_wp,            & !  7 - mixed deciduous forest
     729                                   0.19_wp, 0.31_wp, 0.06_wp,            & !  8 - deciduous forest
    725730                                   0.14_wp, 0.22_wp, 0.06_wp,            & !  9 - tropical evergreen broadleaved forest
    726                                    0.18_wp, 0.28_wp, 0.06_wp,            & ! 10 - medium/tall grassland/woodland 
    727                                    0.43_wp, 0.51_wp, 0.35_wp,            & ! 11 - desert, sandy 
    728                                    0.32_wp, 0.40_wp, 0.24_wp,            & ! 12 - desert, rocky 
    729                                    0.19_wp, 0.27_wp, 0.10_wp,            & ! 13 - tundra 
    730                                    0.77_wp, 0.65_wp, 0.90_wp,            & ! 14 - land ice 
    731                                    0.77_wp, 0.65_wp, 0.90_wp,            & ! 15 - sea ice 
    732                                    0.82_wp, 0.70_wp, 0.95_wp,            & ! 16 - snow 
    733                                    0.08_wp, 0.08_wp, 0.08_wp,            & ! 17 - bare soil 
    734                                    0.17_wp, 0.17_wp, 0.17_wp,            & ! 18 - asphalt/concrete mix 
    735                                    0.17_wp, 0.17_wp, 0.17_wp,            & ! 19 - asphalt (asphalt concrete) 
    736                                    0.30_wp, 0.30_wp, 0.30_wp,            & ! 20 - concrete (Portland concrete) 
    737                                    0.17_wp, 0.17_wp, 0.17_wp,            & ! 21 - sett 
     731                                   0.18_wp, 0.28_wp, 0.06_wp,            & ! 10 - medium/tall grassland/woodland
     732                                   0.43_wp, 0.51_wp, 0.35_wp,            & ! 11 - desert, sandy
     733                                   0.32_wp, 0.40_wp, 0.24_wp,            & ! 12 - desert, rocky
     734                                   0.19_wp, 0.27_wp, 0.10_wp,            & ! 13 - tundra
     735                                   0.77_wp, 0.65_wp, 0.90_wp,            & ! 14 - land ice
     736                                   0.77_wp, 0.65_wp, 0.90_wp,            & ! 15 - sea ice
     737                                   0.82_wp, 0.70_wp, 0.95_wp,            & ! 16 - snow
     738                                   0.08_wp, 0.08_wp, 0.08_wp,            & ! 17 - bare soil
     739                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 18 - asphalt/concrete mix
     740                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 19 - asphalt (asphalt concrete)
     741                                   0.30_wp, 0.30_wp, 0.30_wp,            & ! 20 - concrete (Portland concrete)
     742                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 21 - sett
    738743                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 22 - paving stones
    739                                    0.17_wp, 0.17_wp, 0.17_wp,            & ! 23 - cobblestone 
     744                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 23 - cobblestone
    740745                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 24 - metal
    741746                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 25 - wood
    742747                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 26 - gravel
    743                                    0.17_wp, 0.17_wp, 0.17_wp,            & ! 27 - fine gravel 
    744                                    0.17_wp, 0.17_wp, 0.17_wp,            & ! 28 - pebblestone 
     748                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 27 - fine gravel
     749                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 28 - pebblestone
    745750                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 29 - woodchips
    746751                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 30 - tartan (sports)
    747752                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 31 - artificial turf (sports)
    748                                    0.17_wp, 0.17_wp, 0.17_wp,            & ! 32 - clay (sports) 
     753                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 32 - clay (sports)
    749754                                   0.17_wp, 0.17_wp, 0.17_wp,            & ! 33 - building (dummy)
    750755                                   0.60_wp, 0.60_wp, 0.60_wp,            & ! 34 - building wall type 1 - reflecting facade
     
    41054110 SUBROUTINE radiation_parin
    41064111
    4107 
    41084112    IMPLICIT NONE
    41094113
    4110     CHARACTER(LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    4111 
    4112     NAMELIST /radiation_par/   albedo,                                                             &
    4113                                albedo_lw_dif,                                                      &
    4114                                albedo_lw_dir,                                                      &
    4115                                albedo_sw_dif,                                                      &
    4116                                albedo_sw_dir,                                                      &
    4117                                albedo_type,                                                        &
    4118                                bufsize_alltoall,                                                   &
    4119                                constant_albedo,                                                    &
    4120                                dt_radiation,                                                       &
    4121                                emissivity,                                                         &
    4122                                lw_radiation,                                                       &
    4123                                max_raytracing_dist,                                                &
    4124                                min_irrf_value,                                                     &
    4125                                mrt_geom,                                                           &
    4126                                mrt_geom_params,                                                    &
    4127                                mrt_include_sw,                                                     &
    4128                                mrt_nlevels,                                                        &
    4129                                mrt_skip_roof,                                                      &
    4130                                net_radiation,                                                      &
    4131                                nrefsteps,                                                          &
    4132                                plant_lw_interact,                                                  &
    4133                                rad_angular_discretization,                                         &
    4134                                radiation_interactions_on,                                          &
    4135                                radiation_scheme,                                                   &
    4136                                raytrace_discrete_azims,                                            &
    4137                                raytrace_discrete_elevs,                                            &
    4138                                raytrace_mpi_rma,                                                   &
    4139                                trace_fluxes_above,                                                 &
    4140                                skip_time_do_radiation,                                             &
    4141                                surface_reflections,                                                &
    4142                                svfnorm_report_thresh,                                              &
    4143                                sw_radiation,                                                       &
    4144                                unscheduled_radiation_calls
     4114    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter file
     4115
     4116    INTEGER(iwp) ::  io_status   !< status after reading the namelist file
    41454117
    41464118
     
    41794151                                    unscheduled_radiation_calls
    41804152
    4181     line = ' '
    4182 
    4183 !
    4184 !-- Try to find radiation model namelist
     4153!
     4154!-- Move to the beginning of the namelist file and try to find and read the namelist.
    41854155    REWIND( 11 )
    4186     line = ' '
    4187     DO WHILE ( INDEX( line, '&radiation_parameters' ) == 0 )
    4188        READ( 11, '(A)', END = 12 )  line
    4189     ENDDO
    4190     BACKSPACE( 11 )
    4191 
    4192 !
    4193 !-- Read user-defined namelist
    4194     READ( 11, radiation_parameters, ERR = 10 )
    4195 
    4196 !
    4197 !-- Set flag that indicates that the radiation model is switched on
    4198     radiation = .TRUE.
    4199 
    4200     GOTO 14
    4201 
    4202  10 BACKSPACE( 11 )
    4203     READ( 11 , '(A)') line
    4204     CALL parin_fail_message( 'radiation_parameters', line )
    4205 !
    4206 !-- Try to find old namelist
    4207  12 REWIND( 11 )
    4208     line = ' '
    4209     DO WHILE ( INDEX( line, '&radiation_par' ) == 0 )
    4210        READ( 11, '(A)', END = 14 )  line
    4211     ENDDO
    4212     BACKSPACE( 11 )
    4213 
    4214 !
    4215 !-- Read user-defined namelist
    4216     READ( 11, radiation_par, ERR = 13, END = 14 )
    4217 
    4218     message_string = 'namelist radiation_par is deprecated and will be removed in near future. '// &
    4219                      'Please use namelist radiation_parameters instead'
    4220     CALL message( 'radiation_parin', 'PA0487', 0, 1, 0, 6, 0 )
    4221 
    4222 !
    4223 !-- Set flag that indicates that the radiation model is switched on
    4224     radiation = .TRUE.
    4225 
    4226     IF ( .NOT.  radiation_interactions_on  .AND.  surface_reflections )  THEN
    4227        message_string = 'surface_reflections is allowed only when ' //                             &
    4228                         'radiation_interactions_on is set to TRUE'
    4229        CALL message( 'radiation_parin', 'PA0293',1, 2, 0, 6, 0 )
     4156    READ( 11, radiation_parameters, IOSTAT=io_status )
     4157
     4158!
     4159!-- Action depending on the READ status
     4160    IF ( io_status == 0 )  THEN
     4161!
     4162!--    radiation_parameters namelist was found and read correctly. Set flag that indicates that the
     4163!--    radiation model is switched on.
     4164       radiation = .TRUE.
     4165
     4166    ELSEIF ( io_status > 0 )  THEN
     4167!
     4168!--    radiation_parameters namelist was found but contained errors. Print an error message
     4169!--    including the line that caused the problem.
     4170       BACKSPACE( 11 )
     4171       READ( 11 , '(A)' ) line
     4172       CALL parin_fail_message( 'radiation_parameters', line )
     4173
    42304174    ENDIF
    4231 
    4232     GOTO 14
    4233 
    4234  13 BACKSPACE( 11 )
    4235     READ( 11 , '(A)') line
    4236     CALL parin_fail_message( 'radiation_par', line )
    4237 
    4238  14 CONTINUE
    42394175
    42404176 END SUBROUTINE radiation_parin
  • palm/trunk/SOURCE/salsa_mod.f90

    r4828 r4842  
    33! This file is part of PALM-4U.
    44!
    5 ! PALM-4U is free software: you can redistribute it and/or modify it under the 
    6 ! terms of the GNU General Public License as published by the Free Software 
    7 ! Foundation, either version 3 of the License, or (at your option) any later 
     5! PALM-4U is free software: you can redistribute it and/or modify it under the
     6! terms of the GNU General Public License as published by the Free Software
     7! Foundation, either version 3 of the License, or (at your option) any later
    88! version.
    99!
     
    2626! -----------------
    2727! $Id$
     28! reading of namelist file and actions in case of namelist errors revised so that statement labels
     29! and goto statements are not required any more
     30!
     31! 4828 2021-01-05 11:21:41Z Giersch
    2832! Bugfix in obtaining the correct timestamp in case of restart runs
    2933!
     
    3943! 4671 2020-09-09 20:27:58Z pavelkrc
    4044! Implementation of downward facing USM and LSM surfaces
    41 ! 
     45!
    4246! 4535 2020-05-15 12:07:23Z raasch
    4347! bugfix for restart data format query
    44 ! 
     48!
    4549! 4527 2020-05-11 09:39:55Z monakurppa
    4650! Correct a bug in salsa_wrd_global and salsa_check_data_output,
    4751! and add reglim to be read/written in the restart data
    48 ! 
     52!
    4953! 4525 2020-05-10 17:05:07Z raasch
    5054! added reading/writing of global restart data,
    5155! added reading/writing restart data with MPI-IO,
    5256! variable write_binary_salsa removed
    53 ! 
     57!
    5458! 4512 2020-04-30 12:55:34Z monakurppa
    5559! Fixed a bug in component_index_constructor: index out of bounds if all chemical
    5660! components are used
    57 ! 
     61!
    5862! 4508 2020-04-24 13:32:20Z raasch
    5963! decycling replaced by explicit setting of lateral boundary conditions (Siggi)
    60 ! 
     64!
    6165! 4487 2020-04-03 09:38:20Z raasch
    6266! bugfix for subroutine calls that contain the decycle_salsa switches as arguments
    63 ! 
     67!
    6468! 4481 2020-03-31 18:55:54Z maronga
    6569! Bug fix to the previous commit: the logical switch monotonic_limiter_z missing
    6670! from advec_s_ws in salsa_tendency_ij
    67 ! 
     71!
    6872! 4478 2020-03-27 14:06:23Z monakurppa
    6973! Bug fixes:
    7074! - call salsa_driver in salsa_init also for the ghost points
    7175! - decycle flags missing from advec_s_ws call in salsa_tendency
    72 ! 
     76!
    7377! 4457 2020-03-11 14:20:43Z raasch
    7478! use statement for exchange horiz added
    75 ! 
     79!
    7680! 4442 2020-03-04 19:21:13Z suehring
    77 ! Change order of dimension in surface array %frac to allow for better 
     81! Change order of dimension in surface array %frac to allow for better
    7882! vectorization.
    79 ! 
     83!
    8084! 4441 2020-03-04 19:20:35Z suehring
    8185! Bug fixes and reformatting for the restart data and averaged data output
     
    8690!   chemical components: set to 4d arrays instead of separate arrays
    8791! - add allocation checks for averaged data output arrays
    88 ! 
     92!
    8993! 4416 2020-02-20 17:53:57Z monakurppa
    9094! Time index error in salsa_emission_setup
    91 ! 
     95!
    9296! 4380 2020-01-17 23:39:51Z monakurppa
    9397! - Error in saving the surface fluxes in an array that is applied in the
     
    9599! - Corrections in the header: aerosol bin diameters and lower bin limits not
    96100!   printed correctly
    97 ! 
     101!
    98102! 4364 2020-01-08 02:12:31Z monakurppa
    99103! Set time coordinate in the input data relative to origin_time rather than to
    100104! 00:00:00 UTC
    101 ! 
     105!
    102106! 4360 2020-01-07 11:25:50Z suehring
    103107! Introduction of wall_flags_total_0, which currently sets bits based on static
    104108! topography information used in wall_flags_static_0
    105 ! 
     109!
    106110! 4342 2019-12-16 13:49:14Z Giersch
    107111! cdc replaced by canopy_drag_coeff
    108 ! 
     112!
    109113! 4329 2019-12-10 15:46:36Z motisi
    110114! Renamed wall_flags_0 to wall_flags_static_0
    111 ! 
     115!
    112116! 4315 2019-12-02 09:20:07Z monakurppa
    113117! Add an additional check for the time dimension PIDS_SALSA in
    114118! salsa_emission_setup and correct some error message identifiers.
    115 ! 
     119!
    116120! 4298 2019-11-21 15:59:16Z suehring
    117121! Bugfix, close netcdf input files after reading
    118 ! 
     122!
    119123! 4295 2019-11-14 06:15:31Z monakurppa
    120 ! 
    121 ! 
     124!
     125!
    122126! 4280 2019-10-29 14:34:15Z monakurppa
    123127! Corrected a bug in boundary conditions and fac_dt in offline nesting
    124 ! 
     128!
    125129! 4273 2019-10-24 13:40:54Z monakurppa
    126130! - Rename nest_salsa to nesting_salsa
     
    129133!   chemistry module is applied
    130134! - Set the default value of nesting_salsa and nesting_offline_salsa to .TRUE.
    131 ! 
     135!
    132136! 4272 2019-10-23 15:18:57Z schwenkel
    133137! Further modularization of boundary conditions: moved boundary conditions to
     
    144148! - Reformat salsa emission data with LOD=2: size distribution given for each
    145149!   emission category
    146 ! 
     150!
    147151! 4268 2019-10-17 11:29:38Z schwenkel
    148152! Moving module specific boundary conditions from time_integration to module
    149 ! 
     153!
    150154! 4256 2019-10-07 10:08:52Z monakurppa
    151155! Document previous changes: use global variables nx, ny and nz in salsa_header
    152 ! 
     156!
    153157! 4227 2019-09-10 18:04:34Z gronemeier
    154158! implement new palm_date_time_mod
    155 ! 
     159!
    156160! 4226 2019-09-10 17:03:24Z suehring
    157161! Netcdf input routine for dimension length renamed
    158 ! 
     162!
    159163! 4182 2019-08-22 15:20:23Z scharf
    160164! Corrected "Former revisions" section
    161 ! 
     165!
    162166! 4167 2019-08-16 11:01:48Z suehring
    163 ! Changed behaviour of masked output over surface to follow terrain and ignore 
     167! Changed behaviour of masked output over surface to follow terrain and ignore
    164168! buildings (J.Resler, T.Gronemeier)
    165 ! 
     169!
    166170! 4131 2019-08-02 11:06:18Z monakurppa
    167171! - Add "salsa_" before each salsa output variable
     
    174178! - Add the z-dimension for gaseous emissions to correspond the implementation
    175179!   in the chemistry module
    176 ! 
     180!
    177181! 4118 2019-07-25 16:11:45Z suehring
    178182! - When Dirichlet condition is applied in decycling, the boundary conditions are
     
    189193!   This is done to overcome high concentration peaks due to stationary numerical
    190194!   oscillations caused by horizontal advection discretization.
    191 ! 
     195!
    192196! 4117 2019-07-25 08:54:02Z monakurppa
    193 ! Pass integer flag array as well as boundary flags to WS scalar advection 
     197! Pass integer flag array as well as boundary flags to WS scalar advection
    194198! routine
    195 ! 
     199!
    196200! 4109 2019-07-22 17:00:34Z suehring
    197 ! Slightly revise setting of boundary conditions at horizontal walls, use 
     201! Slightly revise setting of boundary conditions at horizontal walls, use
    198202! data-structure offset index instead of pre-calculate it for each facing
    199 ! 
     203!
    200204! 4079 2019-07-09 18:04:41Z suehring
    201 ! Application of monotonic flux limiter for the vertical scalar advection 
    202 ! up to the topography top (only for the cache-optimized version at the 
     205! Application of monotonic flux limiter for the vertical scalar advection
     206! up to the topography top (only for the cache-optimized version at the
    203207! moment).
    204 ! 
     208!
    205209! 4069 2019-07-01 14:05:51Z Giersch
    206 ! Masked output running index mid has been introduced as a local variable to 
     210! Masked output running index mid has been introduced as a local variable to
    207211! avoid runtime error (Loop variable has been modified) in time_integration
    208 ! 
     212!
    209213! 4058 2019-06-27 15:25:42Z knoop
    210214! Bugfix: to_be_resorted was uninitialized in case of s_H2O in 3d_data_averaging
    211 ! 
     215!
    212216! 4012 2019-05-31 15:19:05Z monakurppa
    213217! Merge salsa branch to trunk. List of changes:
     
    221225! - stuff from salsa_util_mod.f90 moved into salsa_mod.f90
    222226! - calls for closing the netcdf input files added
    223 ! 
     227!
    224228! 3956 2019-05-07 12:32:52Z monakurppa
    225229! - Conceptual bug in depo_surf correct for urban and land surface model
     
    229233!   salsa_exchange_horiz_bounds after calling salsa_driver only when needed
    230234!   (i.e. every dt_salsa).
    231 ! 
     235!
    232236! 3924 2019-04-23 09:33:06Z monakurppa
    233237! Correct a bug introduced by the previous update.
    234 ! 
     238!
    235239! 3899 2019-04-16 14:05:27Z monakurppa
    236240! - remove unnecessary error / location messages
     
    239243!
    240244! 3885 2019-04-11 11:29:34Z kanani
    241 ! Changes related to global restructuring of location messages and introduction 
     245! Changes related to global restructuring of location messages and introduction
    242246! of additional debug messages
    243 ! 
     247!
    244248! 3876 2019-04-08 18:41:49Z knoop
    245249! Introduced salsa_actions module interface
    246 ! 
     250!
    247251! 3871 2019-04-08 14:38:39Z knoop
    248252! Major changes in formatting, performance and data input structure (see branch
     
    255259!   surface_aerosol_flux, aerosol_flux_dpg/sigmag/mass_fracs_a/mass_fracs_b.
    256260! - All emissions are now implemented as surface fluxes! No 3D sources anymore.
    257 ! - Update the emission information by calling salsa_emission_update if 
     261! - Update the emission information by calling salsa_emission_update if
    258262!   skip_time_do_salsa >= time_since_reference_point and
    259263!   next_aero_emission_update <= time_since_reference_point
     
    280284! - Removed tailing white spaces and unused variables
    281285! - Change error message to start by PA instead of SA
    282 ! 
     286!
    283287! 3833 2019-03-28 15:04:04Z forkel
    284 ! added USE chem_gasphase_mod for nvar, nspec and spc_names 
    285 ! 
     288! added USE chem_gasphase_mod for nvar, nspec and spc_names
     289!
    286290! 3787 2019-03-07 08:43:54Z raasch
    287291! unused variables removed
    288 ! 
     292!
    289293! 3780 2019-03-05 11:19:45Z forkel
    290294! unused variable for file index removed from rrd-subroutines parameter list
    291 ! 
     295!
    292296! 3685 2019-01-21 01:02:11Z knoop
    293297! Some interface calls moved to module_interface + cleanup
    294 ! 
     298!
    295299! 3655 2019-01-07 16:51:22Z knoop
    296300! Implementation of the PALM module interface
     
    438442        (/0.0,   0.056, 0.0,   0.056, 0.056, 0.042, 0.056, -99., 0.042,0.014,0.056, -99., -99., -99., 0.056/)
    439443!
    440 !-- Constants for the dry deposition model by Zhang et al. (2001): 
    441 !-- empirical constants "alpha" and "gamma" and characteristic radius "A" for 
     444!-- Constants for the dry deposition model by Zhang et al. (2001):
     445!-- empirical constants "alpha" and "gamma" and characteristic radius "A" for
    442446!-- each land use category (15) and season (5)
    443447    REAL(wp), DIMENSION(1:15), PARAMETER :: alpha_z01 = &
     
    445449    REAL(wp), DIMENSION(1:15), PARAMETER :: gamma_z01 = &
    446450        (/0.56, 0.58, 0.56, 0.56, 0.56, 0.54, 0.54, 0.54, 0.54, 0.54, 0.54, 0.54, 0.50, 0.50, 0.56/)
    447     REAL(wp), DIMENSION(1:15,1:5), PARAMETER :: A_z01 =  RESHAPE( (/& 
     451    REAL(wp), DIMENSION(1:15,1:5), PARAMETER :: A_z01 =  RESHAPE( (/&
    448452         2.0, 5.0, 2.0,  5.0, 5.0, 2.0, 2.0, -99., -99., 10.0, 10.0, -99., -99., -99., 10.0,&  ! SC1
    449453         2.0, 5.0, 2.0,  5.0, 5.0, 2.0, 2.0, -99., -99., 10.0, 10.0, -99., -99., -99., 10.0,&  ! SC2
     
    11131117 CONTAINS
    11141118
    1115 !------------------------------------------------------------------------------!
     1119!-------------------  -----------------------------------------------------------------------------!
    11161120! Description:
    11171121! ------------
    11181122!> Parin for &salsa_par for new modules
    1119 !------------------------------------------------------------------------------!
     1123!---------------------                    ---------------------------------------------------------!
    11201124 SUBROUTINE salsa_parin
    11211125
     
    11251129    IMPLICIT NONE
    11261130
    1127     CHARACTER(LEN=80) ::  line   !< dummy string that contains the current line of parameter file
     1131    CHARACTER(LEN=100) ::  line   !< dummy string that contains the current line of parameter file
    11281132
    11291133    INTEGER(iwp) ::  i                 !< loop index
     1134    INTEGER(iwp) ::  io_status         !< status after reading the namelist file
    11301135    INTEGER(iwp) ::  max_pr_salsa_tmp  !< dummy variable
    11311136
    1132     NAMELIST /salsa_parameters/      aerosol_flux_dpg,                         &
    1133                                      aerosol_flux_mass_fracs_a,                &
    1134                                      aerosol_flux_mass_fracs_b,                &
    1135                                      aerosol_flux_sigmag,                      &
    1136                                      advect_particle_water,                    &
    1137                                      bc_aer_b,                                 &
    1138                                      bc_aer_l,                                 &
    1139                                      bc_aer_n,                                 &
    1140                                      bc_aer_r,                                 &
    1141                                      bc_aer_s,                                 &
    1142                                      bc_aer_t,                                 &
    1143                                      depo_pcm_par,                             &
    1144                                      depo_pcm_type,                            &
    1145                                      depo_surf_par,                            &
    1146                                      dpg,                                      &
    1147                                      dt_salsa,                                 &
    1148                                      emiss_factor_main,                        &
    1149                                      emiss_factor_side,                        &
    1150                                      feedback_to_palm,                         &
    1151                                      h2so4_init,                               &
    1152                                      hno3_init,                                &
    1153                                      listspec,                                 &
    1154                                      main_street_id,                           &
    1155                                      mass_fracs_a,                             &
    1156                                      mass_fracs_b,                             &
    1157                                      max_street_id,                            &
    1158                                      n_lognorm,                                &
    1159                                      nbin,                                     &
    1160                                      nesting_salsa,                            &
    1161                                      nesting_offline_salsa,                    &
    1162                                      nf2a,                                     &
    1163                                      nh3_init,                                 &
    1164                                      nj3,                                      &
    1165                                      nlcnd,                                    &
    1166                                      nlcndgas,                                 &
    1167                                      nlcndh2oae,                               &
    1168                                      nlcoag,                                   &
    1169                                      nldepo,                                   &
    1170                                      nldepo_pcm,                               &
    1171                                      nldepo_surf,                              &
    1172                                      nldistupdate,                             &
    1173                                      nsnucl,                                   &
    1174                                      ocnv_init,                                &
    1175                                      ocsv_init,                                &
    1176                                      reglim,                                   &
    1177                                      salsa,                                    &
    1178                                      salsa_emission_mode,                      &
    1179                                      season_z01,                               &
    1180                                      sigmag,                                   &
    1181                                      side_street_id,                           &
    1182                                      skip_time_do_salsa,                       &
    1183                                      surface_aerosol_flux,                     &
     1137    NAMELIST /salsa_parameters/      aerosol_flux_dpg,                                             &
     1138                                     aerosol_flux_mass_fracs_a,                                    &
     1139                                     aerosol_flux_mass_fracs_b,                                    &
     1140                                     aerosol_flux_sigmag,                                          &
     1141                                     advect_particle_water,                                        &
     1142                                     bc_aer_b,                                                     &
     1143                                     bc_aer_l,                                                     &
     1144                                     bc_aer_n,                                                     &
     1145                                     bc_aer_r,                                                     &
     1146                                     bc_aer_s,                                                     &
     1147                                     bc_aer_t,                                                     &
     1148                                     depo_pcm_par,                                                 &
     1149                                     depo_pcm_type,                                                &
     1150                                     depo_surf_par,                                                &
     1151                                     dpg,                                                          &
     1152                                     dt_salsa,                                                     &
     1153                                     emiss_factor_main,                                            &
     1154                                     emiss_factor_side,                                            &
     1155                                     feedback_to_palm,                                             &
     1156                                     h2so4_init,                                                   &
     1157                                     hno3_init,                                                    &
     1158                                     listspec,                                                     &
     1159                                     main_street_id,                                               &
     1160                                     mass_fracs_a,                                                 &
     1161                                     mass_fracs_b,                                                 &
     1162                                     max_street_id,                                                &
     1163                                     n_lognorm,                                                    &
     1164                                     nbin,                                                         &
     1165                                     nesting_salsa,                                                &
     1166                                     nesting_offline_salsa,                                        &
     1167                                     nf2a,                                                         &
     1168                                     nh3_init,                                                     &
     1169                                     nj3,                                                          &
     1170                                     nlcnd,                                                        &
     1171                                     nlcndgas,                                                     &
     1172                                     nlcndh2oae,                                                   &
     1173                                     nlcoag,                                                       &
     1174                                     nldepo,                                                       &
     1175                                     nldepo_pcm,                                                   &
     1176                                     nldepo_surf,                                                  &
     1177                                     nldistupdate,                                                 &
     1178                                     nsnucl,                                                       &
     1179                                     ocnv_init,                                                    &
     1180                                     ocsv_init,                                                    &
     1181                                     reglim,                                                       &
     1182                                     salsa,                                                        &
     1183                                     salsa_emission_mode,                                          &
     1184                                     season_z01,                                                   &
     1185                                     sigmag,                                                       &
     1186                                     side_street_id,                                               &
     1187                                     skip_time_do_salsa,                                           &
     1188                                     surface_aerosol_flux,                                         &
    11841189                                     van_der_waals_coagc
    11851190
    1186     line = ' '
    1187 !
    1188 !-- Try to find salsa package
    1189     REWIND ( 11 )
    1190     line = ' '
    1191     DO WHILE ( INDEX( line, '&salsa_parameters' ) == 0 )
    1192        READ ( 11, '(A)', END=10 )  line
    1193     ENDDO
    1194     BACKSPACE ( 11 )
    1195 !
    1196 !-- Read user-defined namelist
    1197     READ ( 11, salsa_parameters )
    1198 !
    1199 !-- Enable salsa (salsa switch in modules.f90)
    1200     salsa = .TRUE.
    1201 
    1202  10 CONTINUE
     1191
     1192!
     1193!-- Move to the beginning of the namelist file and try to find and read the namelist.
     1194    REWIND( 11 )
     1195    READ( 11, salsa_parameters, IOSTAT=io_status )
     1196
     1197!
     1198!-- Action depending on the READ status
     1199    IF ( io_status == 0 )  THEN
     1200!
     1201!--    salsa_parameters namelist was found and read correctly. Enable salsa (salsa switch in
     1202!--    modules.f90)
     1203       salsa = .TRUE.
     1204
     1205    ELSEIF ( io_status > 0 )  THEN
     1206!
     1207!--    salsa_parameters namelist was found but contained errors. Print an error message including
     1208!--    the line that caused the problem.
     1209       BACKSPACE( 11 )
     1210       READ( 11 , '(A)' ) line
     1211       CALL parin_fail_message( 'salsa_parameters', line )
     1212
     1213    ENDIF
     1214
    12031215!
    12041216!-- Update the number of output profiles
     
    12121224
    12131225 END SUBROUTINE salsa_parin
     1226
    12141227
    12151228!------------------------------------------------------------------------------!
     
    14451458
    14461459    IMPLICIT NONE
    1447  
     1460
    14481461    INTEGER(iwp), INTENT(IN) ::  io   !< Unit of the output file
    14491462!
     
    17481761!-- (number concentration (#/m3) )
    17491762!
    1750 !-- If chemistry is on, read gas phase concentrations from there. Otherwise, 
     1763!-- If chemistry is on, read gas phase concentrations from there. Otherwise,
    17511764!-- allocate salsa_gas array.
    17521765
     
    18221835       ENDDO
    18231836!
    1824 !--    Vertical surfaces: northward (l=0), southward (l=1), eastward (l=2) and 
     1837!--    Vertical surfaces: northward (l=0), southward (l=1), eastward (l=2) and
    18251838!--    westward (l=3) facing
    18261839       DO  l = 0, 3
     
    19992012! Description:
    20002013! ------------
    2001 !> Initializes particle size distribution grid by calculating size bin limits 
    2002 !> and mid-size for *dry* particles in each bin. Called from salsa_initialize 
     2014!> Initializes particle size distribution grid by calculating size bin limits
     2015!> and mid-size for *dry* particles in each bin. Called from salsa_initialize
    20032016!> (only at the beginning of simulation).
    20042017!> Size distribution described using:
     
    20092022!> based on given subrange size limits and bin number.
    20102023!
    2011 !> Mona changed 06/2017: Use geometric mean diameter to describe the mean 
     2024!> Mona changed 06/2017: Use geometric mean diameter to describe the mean
    20122025!> particle diameter in a size bin, not the arithmeric mean which clearly
    2013 !> overestimates the total particle volume concentration. 
     2026!> overestimates the total particle volume concentration.
    20142027!
    20152028!> Coded by:
     
    20892102!> Initilize altitude-dependent aerosol size distributions and compositions.
    20902103!>
    2091 !> Mona added 06/2017: Correct the number and mass concentrations by normalizing 
     2104!> Mona added 06/2017: Correct the number and mass concentrations by normalizing
    20922105!< by the given total number and mass concentration.
    20932106!>
     
    22682281             CALL get_variable( id_dyn, 'Dmid', pr_dmid )
    22692282!
    2270 !--          Check whether the sectional representation conform to the one 
     2283!--          Check whether the sectional representation conform to the one
    22712284!--          applied in the model
    22722285             IF ( ANY( ABS( ( aero(1:nbins_aerosol)%dmid - pr_dmid ) /                             &
     
    23232336             message_string = 'Error in initialising mass fractions of chemical components. ' //   &
    23242337                              'Check that all chemical components are included in parameter file!'
    2325              CALL message( 'salsa_mod: aerosol_init', 'PA0606', 2, 2, 0, 6, 0 ) 
     2338             CALL message( 'salsa_mod: aerosol_init', 'PA0606', 2, 2, 0, 6, 0 )
    23262339          ENDIF
    23272340!
     
    25502563                   ENDIF
    25512564                   ib = ib+1
    2552                 ENDDO 
     2565                ENDDO
    25532566             ENDIF
    25542567          ENDDO !< k
     
    25932606! Description:
    25942607! ------------
    2595 !> Create a lognormal size distribution and discretise to a sectional 
     2608!> Create a lognormal size distribution and discretise to a sectional
    25962609!> representation.
    25972610!------------------------------------------------------------------------------!
     
    26872700!
    26882701!--          Predetermine flag to mask topography
    2689              flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     2702             flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
    26902703!
    26912704!--          Regime 2a:
     
    27172730                   IF ( prunmode == 1 )  THEN
    27182731                      aerosol_mass(ic)%init(k) = MAX( 0.0_wp, pmf2b(k) ) * ( 1.0_wp - pnf2a(k) ) * &
    2719                                                  pndist(k,ib) * pcore(ib) * prho 
     2732                                                 pndist(k,ib) * pcore(ib) * prho
    27202733                   ENDIF
    27212734                   ib = ib + 1
     
    36303643! Description:
    36313644! ------------
    3632 !> Performs necessary unit and dimension conversion between the host model and 
     3645!> Performs necessary unit and dimension conversion between the host model and
    36333646!> SALSA module, and calls the main SALSA routine.
    36343647!> Partially adobted form the original SALSA boxmodel version.
    36353648!> Now takes masses in as kg/kg from LES!! Converted to m3/m3 for SALSA
    3636 !> 05/2016 Juha: This routine is still pretty much in its original shape. 
     3649!> 05/2016 Juha: This routine is still pretty much in its original shape.
    36373650!>               It's dumb as a mule and twice as ugly, so implementation of
    36383651!>               an improved solution is necessary sooner or later.
     
    37523765!
    37533766!--    Set volume concentrations:
    3754 !--    Sulphate (SO4) or sulphuric acid H2SO4 
     3767!--    Sulphate (SO4) or sulphuric acid H2SO4
    37553768       IF ( index_so4 > 0 )  THEN
    37563769          vc = 1
     
    38203833       IF ( index_no > 0 )  THEN
    38213834          vc = 6
    3822           str = ( index_no-1 ) * nbins_aerosol + 1 
     3835          str = ( index_no-1 ) * nbins_aerosol + 1
    38233836          endi = index_no * nbins_aerosol
    38243837          ic = 1
     
    38593872       aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
    38603873!
    3861 !--    Number concentrations (numc) and particle sizes 
     3874!--    Number concentrations (numc) and particle sizes
    38623875!--    (dwet = wet diameter, core = dry volume)
    38633876       DO  ib = 1, nbins_aerosol
     
    41144127!
    41154128!-- Set surfaces and wall fluxes due to deposition
    4116     IF ( lsdepo  .AND.  lsdepo_surf  .AND.  prunmode == 3 )  THEN 
     4129    IF ( lsdepo  .AND.  lsdepo_surf  .AND.  prunmode == 3 )  THEN
    41174130       IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
    41184131          CALL depo_surf( i, j, surf_def_h(0), vd, schmidt_num, kvis, in_u, .TRUE. )
     
    41894202
    41904203 END SUBROUTINE set_salsa_runtime
    4191  
     4204
    41924205!------------------------------------------------------------------------------!
    41934206! Description:
    41944207! ------------
    4195 !> Calculates the absolute temperature (using hydrostatic pressure), saturation 
    4196 !> vapour pressure and mixing ratio over water, relative humidity and air 
     4208!> Calculates the absolute temperature (using hydrostatic pressure), saturation
     4209!> vapour pressure and mixing ratio over water, relative humidity and air
    41974210!> density needed in the SALSA model.
    4198 !> NOTE, no saturation adjustment takes place -> the resulting water vapour 
     4211!> NOTE, no saturation adjustment takes place -> the resulting water vapour
    41994212!> mixing ratio can be supersaturated, allowing the microphysical calculations
    42004213!> in SALSA.
     
    42544267! Description:
    42554268! ------------
    4256 !> Calculates ambient sizes of particles by equilibrating soluble fraction of 
     4269!> Calculates ambient sizes of particles by equilibrating soluble fraction of
    42574270!> particles with water using the ZSR method (Stokes and Robinson, 1966).
    42584271!> Method:
     
    42604273!> - (ammonium) sulphate (100%)
    42614274!> - sea salt (100 %)
    4262 !> - organic carbon (epsoc * 100%) 
     4275!> - organic carbon (epsoc * 100%)
    42634276!> Exact thermodynamic considerations neglected.
    4264 !> - If particles contain no sea salt, calculation according to sulphate 
     4277!> - If particles contain no sea salt, calculation according to sulphate
    42654278!>   properties
    4266 !> - If contain sea salt but no sulphate, calculation according to sea salt 
     4279!> - If contain sea salt but no sulphate, calculation according to sea salt
    42674280!>   properties
    4268 !> - If contain both sulphate and sea salt -> the molar fraction of these 
     4281!> - If contain both sulphate and sea salt -> the molar fraction of these
    42694282!>   compounds determines which one of them is used as the basis of calculation.
    4270 !> If sulphate and sea salt coexist in a particle, it is assumed that the Cl is 
    4271 !> replaced by sulphate; thus only either sulphate + organics or sea salt + 
     4283!> If sulphate and sea salt coexist in a particle, it is assumed that the Cl is
     4284!> replaced by sulphate; thus only either sulphate + organics or sea salt +
    42724285!> organics is included in the calculation of soluble fraction.
    4273 !> Molality parameterizations taken from Table 1 of Tang: Thermodynamic and 
    4274 !> optical properties of mixed-salt aerosols of atmospheric importance, 
     4286!> Molality parameterizations taken from Table 1 of Tang: Thermodynamic and
     4287!> optical properties of mixed-salt aerosols of atmospheric importance,
    42754288!> J. Geophys. Res., 102 (D2), 1883-1893 (1997)
    42764289!
    42774290!> Coded by:
    4278 !> Hannele Korhonen (FMI) 2005 
     4291!> Hannele Korhonen (FMI) 2005
    42794292!> Harri Kokkola (FMI) 2006
    42804293!> Matti Niskanen(FMI) 2012
     
    42824295!> Modified for the new aerosol datatype, Juha Tonttila (FMI) 2014
    42834296!
    4284 !> fxm: should sea salt form a solid particle when prh is very low (even though 
     4297!> fxm: should sea salt form a solid particle when prh is very low (even though
    42854298!> it could be mixed with e.g. sulphate)?
    42864299!> fxm: crashes if no sulphate or sea salt
     
    43354348          zvpart(6:7) = paero(ib)%volc(6:7) / paero(ib)%numc
    43364349!
    4337 !--       Total volume and wet diameter of one dry particle 
     4350!--       Total volume and wet diameter of one dry particle
    43384351          zcore = SUM( zvpart(1:2) )
    43394352          zdwet = paero(ib)%dwet
     
    43454358             zaw = MAX( 1.0E-3_wp, zrh / zke ) ! To avoid underflow
    43464359!
    4347 !--          Binary molalities (mol/kg): 
     4360!--          Binary molalities (mol/kg):
    43484361!--          Sulphate
    43494362             zbinmol(1) = 1.1065495E+2_wp - 3.6759197E+2_wp * zaw + 5.0462934E+2_wp * zaw**2 -     &
     
    43674380                       zcore / api6 )**0.33333333_wp
    43684381!
    4369 !--          Kelvin effect (Eq. 10.85 in in Seinfeld and Pandis (2006)). Avoid 
     4382!--          Kelvin effect (Eq. 10.85 in in Seinfeld and Pandis (2006)). Avoid
    43704383!--          overflow.
    43714384             zke = EXP( MIN( 50.0_wp, 4.0_wp * surfw0 * amvh2so4 / ( abo * ptemp *  zdwet ) ) )
    43724385
    43734386             counti = counti + 1
    4374              IF ( counti > 1000 )  THEN 
     4387             IF ( counti > 1000 )  THEN
    43754388                message_string = 'Subrange 1: no convergence!'
    43764389                CALL message( 'salsa_mod: equilibration', 'PA0617', 1, 2, 0, 6, 0 )
     
    43784391          ENDDO
    43794392!
    4380 !--       Instead of lwc, use the volume concentration of water from now on 
     4393!--       Instead of lwc, use the volume concentration of water from now on
    43814394!--       (easy to convert...)
    43824395          paero(ib)%volc(8) = zlwc / arhoh2o
     
    44384451                             6.210577919E+1_wp * zaw**2 + 5.510176187E+2_wp * zaw**3 -             &
    44394452                             1.460055286E+3_wp * zaw**4 + 1.894467542E+3_wp * zaw**5 -             &
    4440                              1.220611402E+3_wp * zaw**6 + 3.098597737E+2_wp * zaw**7 
     4453                             1.220611402E+3_wp * zaw**6 + 3.098597737E+2_wp * zaw**7
    44414454!--             Sea salt (natrium chloride)
    44424455                zbinmol(5) = 5.875248E+1_wp - 1.8781997E+2_wp * zaw + 2.7211377E+2_wp * zaw**2 -   &
     
    44574470
    44584471                counti = counti + 1
    4459                 IF ( counti > 1000 )  THEN 
     4472                IF ( counti > 1000 )  THEN
    44604473                   message_string = 'Subrange 2: no convergence!'
    44614474                CALL message( 'salsa_mod: equilibration', 'PA0618', 1, 2, 0, 6, 0 )
     
    44824495!> Description:
    44834496!> ------------
    4484 !> Calculation of the settling velocity vc (m/s) per aerosol size bin and 
     4497!> Calculation of the settling velocity vc (m/s) per aerosol size bin and
    44854498!> deposition on plant canopy (lsdepo_pcm).
    44864499!
     
    47504763!> Calculate the dry deposition on horizontal and vertical surfaces. Implement
    47514764!> as a surface flux.
    4752 !> @todo aerodynamic resistance ignored for now (not important for 
     4765!> @todo aerodynamic resistance ignored for now (not important for
    47534766!        high-resolution simulations)
    47544767!------------------------------------------------------------------------------!
     
    50105023! ------------
    50115024!> Calculates particle loss and change in size distribution due to (Brownian)
    5012 !> coagulation. Only for particles with dwet < 30 micrometres. 
     5025!> coagulation. Only for particles with dwet < 30 micrometres.
    50135026!
    50145027!> Method:
    50155028!> Semi-implicit, non-iterative method: (Jacobson, 1994)
    50165029!> Volume concentrations of the smaller colliding particles added to the bin of
    5017 !> the larger colliding particles. Start from first bin and use the updated 
     5030!> the larger colliding particles. Start from first bin and use the updated
    50185031!> number and volume for calculation of following bins. NB! Our bin numbering
    50195032!> does not follow particle size in subrange 2.
     
    50285041!> Exact coagulation coefficients for each pressure level are scaled according
    50295042!> to current particle wet size (linear scaling).
    5030 !> Bins are organized in terms of the dry size of the condensation nucleus, 
     5043!> Bins are organized in terms of the dry size of the condensation nucleus,
    50315044!> while coagulation kernell is calculated with the actual hydrometeor
    50325045!> size.
     
    50785091!--    CoagSink ~ Dp in continuum subrange --> 'effective' number conc. of coarse particles
    50795092
    5080 !-- 2) Updating coagulation coefficients 
     5093!-- 2) Updating coagulation coefficients
    50815094!
    50825095!-- Aerosol mass (kg). Density of 1500 kg/m3 assumed
     
    52685281    mfp = ( 1.656E-10_wp * temp + 1.828E-8_wp ) * ( p_0 + 1325.0_wp ) / pres
    52695282!
    5270 !-- 2) Slip correction factor for small particles 
     5283!-- 2) Slip correction factor for small particles
    52715284    knud = 2.0_wp * EXP( LOG(mfp) - LOG(diam) )! Knudsen number for air (15.23)
    52725285!
     
    53255338! Description:
    53265339! ------------
    5327 !> Calculates the change in particle volume and gas phase 
     5340!> Calculates the change in particle volume and gas phase
    53285341!> concentrations due to nucleation, condensation and dissolutional growth.
    53295342!
    53305343!> Sulphuric acid and organic vapour: only condensation and no evaporation.
    53315344!
    5332 !> New gas and aerosol phase concentrations calculated according to Jacobson 
     5345!> New gas and aerosol phase concentrations calculated according to Jacobson
    53335346!> (1997): Numerical techniques to solve condensational and dissolutional growth
    53345347!> equations when growth is coupled to reversible reactions, Aerosol Sci. Tech.,
     
    53365349!
    53375350!> Following parameterization has been used:
    5338 !> Molecular diffusion coefficient of condensing vapour (m2/s) 
     5351!> Molecular diffusion coefficient of condensing vapour (m2/s)
    53395352!> (Reid et al. (1987): Properties of gases and liquids, McGraw-Hill, New York.)
    53405353!> D = {1.d-7*sqrt(1/M_air + 1/M_gas)*T^1.75} / &
     
    53435356!> d_air = 19.70  : diffusion volume of air
    53445357!> M_h2so4 = 98.08 : molar mass of h2so4 (g/mol)
    5345 !> d_h2so4 = 51.96  : diffusion volume of h2so4 
     5358!> d_h2so4 = 51.96  : diffusion volume of h2so4
    53465359!
    53475360!> Called from main aerosol model
     
    54475460       zknud(ss:ee) = 2.0_wp * zmfp / paero(ss:ee)%dwet
    54485461!
    5449 !--    Transitional correction factor: aerosol + gas (the semi-empirical Fuchs- Sutugin 
     5462!--    Transitional correction factor: aerosol + gas (the semi-empirical Fuchs- Sutugin
    54505463!--    interpolation function (Fuchs and Sutugin, 1971))
    54515464       zbeta = ( zknud + 1.0_wp ) / ( 0.377_wp * zknud + 1.0_wp + 4.0_wp / ( 3.0_wp * massacc ) *  &
     
    54595472                 * paero(start_subrange_1a:start_subrange_1a+1)%dwet)
    54605473!
    5461 !--    Collision rate (mass-transfer coefficient): gases on aerosols (1/s) (Eq. 16.64 in 
     5474!--    Collision rate (mass-transfer coefficient): gases on aerosols (1/s) (Eq. 16.64 in
    54625475!--    Jacobson (2005))
    54635476       ss = start_subrange_1a
     
    54755488!--    5) Changes in gas-phase concentrations and particle volume
    54765489!
    5477 !--    5.1) Organic vapours 
     5490!--    5.1) Organic vapours
    54785491!
    54795492!--    5.1.1) Non-volatile organic compound: condenses onto all bins
     
    55275540!
    55285541!--       Change in gas concentration (#/m3)
    5529           zdvap3 = pcocsv - zcvap_new3 
     5542          zdvap3 = pcocsv - zcvap_new3
    55305543!
    55315544!--       Updated gas concentration (#/m3)
     
    55905603!
    55915604!-- Condensation of water vapour
    5592     IF ( lscndh2oae )  THEN 
     5605    IF ( lscndh2oae )  THEN
    55935606       CALL gpparth2o( paero, ptemp, ppres, pcs, pcw, ptstep )
    55945607    ENDIF
     
    56005613! ------------
    56015614!> Calculates the particle number and volume increase, and gas-phase
    5602 !> concentration decrease due to nucleation subsequent growth to detectable size 
     5615!> concentration decrease due to nucleation subsequent growth to detectable size
    56035616!> of 3 nm.
    56045617!
     
    56595672    REAL(wp) ::  zdelta_vap   !< change of H2SO4 and organic vapour concentration (#/m3)
    56605673    REAL(wp) ::  zdfvap       !< air diffusion coefficient (m2/s)
    5661     REAL(wp) ::  zdmean       !< mean diameter of existing particles (m) 
     5674    REAL(wp) ::  zdmean       !< mean diameter of existing particles (m)
    56625675    REAL(wp) ::  zeta         !< constant: proportional to ratio of CS/GR (m)
    56635676                              !< (condensation sink / growth rate)
     
    56745687    REAL(wp) ::  zlambda      !< parameter for adjusting the growth rate due to self-coagulation
    56755688    REAL(wp) ::  zm_c         !< particle mass (kg) for c = critical (1nm)
    5676     REAL(wp) ::  zm_para      !< Parameter m for calculating the coagulation sink (Eq. 5&6 in 
     5689    REAL(wp) ::  zm_para      !< Parameter m for calculating the coagulation sink (Eq. 5&6 in
    56775690                              !< Lehtinen et al. 2007)
    56785691    REAL(wp) ::  zm_x         !< particle mass (kg) for x = 3nm
     
    56845697    REAL(wp) ::  znsa         !< number of H2SO4 molecules in critical cluster
    56855698
    5686     REAL(wp), INTENT(in) ::  pc_nh3   !< ammonia concentration (#/m3) 
     5699    REAL(wp), INTENT(in) ::  pc_nh3   !< ammonia concentration (#/m3)
    56875700    REAL(wp), INTENT(in) ::  pc_ocnv  !< conc. of non-volatile OC (#/m3)
    56885701    REAL(wp), INTENT(in) ::  pc_sa    !< sulphuric acid conc. (#/m3)
     
    58125825          znsa    = 1.0_wp
    58135826!
    5814 !--    Heteromolecular nucleation, J~[H2SO4]*[ORG] 
     5827!--    Heteromolecular nucleation, J~[H2SO4]*[ORG]
    58155828!--    (See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242.)
    58165829       CASE(7)
     
    58645877!
    58655878!-- 2.1) Check that there is enough H2SO4 and organic vapour to produce the nucleation
    5866     IF ( nsnucl <= 4 )  THEN 
     5879    IF ( nsnucl <= 4 )  THEN
    58675880!
    58685881!--    If the chosen nucleation scheme is 1-4, nucleation occurs only due to H2SO4. All of the total
     
    58815894          pxocnv = 0.0_wp
    58825895       ELSE
    5883           pxsa   = pc_sa * znsa / ( pc_sa * znsa + pc_ocnv * znoc ) 
     5896          pxsa   = pc_sa * znsa / ( pc_sa * znsa + pc_ocnv * znoc )
    58845897          pxocnv = pc_ocnv * znoc / ( pc_sa * znsa + pc_ocnv * znoc )
    58855898       ENDIF
     
    60096022                   ( 3.0_wp * z_r_c2 * zgamma_f_2 ) - z_r_c2
    60106023       zomega_2x = ( ( z_r_x2 + zgamma_f_2 )**3 - ( z_r_x2**2 + zgamma_f_2 )**1.5_wp ) /           &
    6011                    ( 3.0_wp * z_r_x2 * zgamma_f_2 ) - z_r_x2 
     6024                   ( 3.0_wp * z_r_x2 * zgamma_f_2 ) - z_r_x2
    60126025!
    60136026!--    The distance (m) at which the two fluxes are matched (condensation and coagulation sinks)
     
    60256038       zcoags_x = MAX( 1.0E-20_wp, SUM( z_k_x2 * paero(:)%numc ) )
    60266039!
    6027 !--    Parameter m for calculating the coagulation sink onto background particles (Eq. 5&6 in 
     6040!--    Parameter m for calculating the coagulation sink onto background particles (Eq. 5&6 in
    60286041!--    Lehtinen et al. 2007)
    60296042       zm_para = LOG( zcoags_x / zcoags_c ) / LOG( reglim(1) / zdcrit )
     
    60416054       ELSEIF ( nj3 == 3 )  THEN  ! Anttila et al. (2010): coagulation sink and self-coag.
    60426055!
    6043 !--       If air is polluted, the self-coagulation becomes important. Self-coagulation of small 
     6056!--       If air is polluted, the self-coagulation becomes important. Self-coagulation of small
    60446057!--       particles < 3 nm.
    60456058!
     
    61986211!
    61996212!-- Nucleation rate in #/(cm3 s)
    6200     pnuc_rate = EXP( pnuc_rate ) 
     6213    pnuc_rate = EXP( pnuc_rate )
    62016214!
    62026215!-- Check the validity of parameterization
    6203     IF ( pnuc_rate < 1.0E-7_wp )  THEN 
     6216    IF ( pnuc_rate < 1.0E-7_wp )  THEN
    62046217       pnuc_rate = 0.0_wp
    62056218       pd_crit   = 1.0E-9_wp
     
    62526265!
    62536266!-- 6) Organic compounds not involved when binary nucleation is assumed
    6254     pn_crit_ocnv = 0.0_wp   ! number of organic molecules 
     6267    pn_crit_ocnv = 0.0_wp   ! number of organic molecules
    62556268    pk_sa        = 1.0_wp   ! if = 1, H2SO4 involved in nucleation
    62566269    pk_ocnv      = 0.0_wp   ! if = 1, organic compounds involved
     
    62996312
    63006313 END SUBROUTINE binnucl
    6301  
     6314
    63026315!------------------------------------------------------------------------------!
    63036316! Description:
     
    63536366    zlogsa  = LOG( pc_sa )
    63546367!
    6355 !-- 2) Nucleation rate (Eq. 7 in Napari et al., 2002: Parameterization of 
     6368!-- 2) Nucleation rate (Eq. 7 in Napari et al., 2002: Parameterization of
    63566369!--    ternary nucleation of sulfuric acid - ammonia - water.
    63576370    zlnj = - 84.7551114741543_wp + 0.3117595133628944_wp * prh +                                   &
     
    64616474! Description:
    64626475! ------------
    6463 !> Function z_n_nuc_tayl is connected to the calculation of self-coagualtion of 
     6476!> Function z_n_nuc_tayl is connected to the calculation of self-coagualtion of
    64646477!> small particles. It calculates number of the particles in the size range
    6465 !> [zdcrit,dx] using Taylor-expansion (please note that the expansion is not 
     6478!> [zdcrit,dx] using Taylor-expansion (please note that the expansion is not
    64666479!> valid for certain rational numbers, e.g. -4/3 and -3/2)
    64676480!------------------------------------------------------------------------------!
     
    65066519! Description:
    65076520! ------------
    6508 !> Calculates the condensation of water vapour on aerosol particles. Follows the 
     6521!> Calculates the condensation of water vapour on aerosol particles. Follows the
    65096522!> analytical predictor method by Jacobson (2005).
    6510 !> For equations, see Jacobson (2005), Fundamentals of atmospheric modelling 
     6523!> For equations, see Jacobson (2005), Fundamentals of atmospheric modelling
    65116524!> (2nd edition).
    65126525!------------------------------------------------------------------------------!
     
    66906703! Description:
    66916704! ------------
    6692 !> Calculates the activity coefficient of liquid water 
     6705!> Calculates the activity coefficient of liquid water
    66936706!------------------------------------------------------------------------------!
    66946707 REAL(wp) FUNCTION acth2o( ppart, pcw )
     
    67236736! Description:
    67246737! ------------
    6725 !> Calculates the dissolutional growth of particles (i.e. gas transfers to a 
    6726 !> particle surface and dissolves in liquid water on the surface). Treated here 
    6727 !> as a non-equilibrium (time-dependent) process. Gases: HNO3 and NH3 
     6738!> Calculates the dissolutional growth of particles (i.e. gas transfers to a
     6739!> particle surface and dissolves in liquid water on the surface). Treated here
     6740!> as a non-equilibrium (time-dependent) process. Gases: HNO3 and NH3
    67286741!> (Chapter 17.14 in Jacobson, 2005).
    67296742!
    6730 !> Called from subroutine condensation. 
     6743!> Called from subroutine condensation.
    67316744!> Coded by:
    67326745!> Harri Kokkola (FMI)
    6733 !------------------------------------------------------------------------------! 
     6746!------------------------------------------------------------------------------!
    67346747 SUBROUTINE gpparthno3( ppres, ptemp, paero, pghno3, pgnh3, pcw, pcs, pbeta, ptstep )
    67356748
     
    72707283                                         !< 1: HNO3, 2: HCL, 3: NH4+/H+ (NH3), 4: HHSO4**2/H2SO4,
    72717284                                         !< 5: H2SO4**3/HHSO4**2, 6: NH4HSO2, 7: HHSO4
    7272     REAL(wp), DIMENSION(:) ::  ions      !< ion molarities (mol/m3): 1: H+, 2: NH4+, 3: Na+, 
     7285    REAL(wp), DIMENSION(:) ::  ions      !< ion molarities (mol/m3): 1: H+, 2: NH4+, 3: Na+,
    72737286                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
    7274     REAL(wp), DIMENSION(7) ::  ions_mol  !< ion molalities (mol/kg): 1: H+, 2: NH4+, 3: Na+, 
     7287    REAL(wp), DIMENSION(7) ::  ions_mol  !< ion molalities (mol/kg): 1: H+, 2: NH4+, 3: Na+,
    72757288                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
    7276     REAL(wp), DIMENSION(:) ::  mols_out  !< ion molality output (mol/kg): 1: H+, 2: NH4+, 3: Na+, 
     7289    REAL(wp), DIMENSION(:) ::  mols_out  !< ion molality output (mol/kg): 1: H+, 2: NH4+, 3: Na+,
    72777290                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
    72787291!
     
    75607573                      sodium_nitrate_eq_frac * nano3_h2so4 + sodium_chloride_eq_frac * nacl_h2so4
    75617574
    7562        gamma_h2so4 = EXP( ln_h2so4_act )    ! molal activity coefficient 
     7575       gamma_h2so4 = EXP( ln_h2so4_act )    ! molal activity coefficient
    75637576!
    75647577!--    Export activity coefficients
     
    75897602       ENDIF
    75907603!
    7591 !--    Calculate the new hydrogen ion, bisulphate ion and sulphate ion 
     7604!--    Calculate the new hydrogen ion, bisulphate ion and sulphate ion
    75927605!--    concentration
    75937606       h_real    = ions(1)
     
    76157628!-- 4) ACTIVITY COEFFICIENTS -for vapour pressures of HNO3,HCL and NH3
    76167629!
    7617 !-- This section evaluates activity coefficients and vapour pressures using the water content 
     7630!-- This section evaluates activity coefficients and vapour pressures using the water content
    76187631!-- calculated above) for each inorganic condensing species: a - HNO3, b - NH3, c - HCL.
    7619 !-- The following procedure is used: Zaveri et al (2005) found that one could express the variation 
     7632!-- The following procedure is used: Zaveri et al (2005) found that one could express the variation
    76207633!-- of activity coefficients linearly in log-space if equivalent mole fractions were used.
    76217634!-- So, by a taylor series expansion LOG( activity coefficient ) =
     
    79277940!> Update the particle size distribution. Put particles into corrects bins.
    79287941!>
    7929 !> Moving-centre method assumed, i.e. particles are allowed to grow to their 
    7930 !> exact size as long as they are not crossing the fixed diameter bin limits. 
    7931 !> If the particles in a size bin cross the lower or upper diameter limit, they 
     7942!> Moving-centre method assumed, i.e. particles are allowed to grow to their
     7943!> exact size as long as they are not crossing the fixed diameter bin limits.
     7944!> If the particles in a size bin cross the lower or upper diameter limit, they
    79327945!> are all moved to the adjacent diameter bin and their volume is averaged with
    7933 !> the particles in the new bin, which then get a new diameter. 
    7934 !
    7935 !> Moving-centre method minimises numerical diffusion. 
     7946!> the particles in the new bin, which then get a new diameter.
     7947!
     7948!> Moving-centre method minimises numerical diffusion.
    79367949!------------------------------------------------------------------------------!
    79377950 SUBROUTINE distr_update( paero )
     
    79968009!
    79978010!--          If size bin has not grown, cycle.
    7998 !--          Changed by Mona: compare to the arithmetic mean volume, as done originally. Now 
    7999 !--          particle volume is derived from the geometric mean diameter, not arithmetic (see 
     8011!--          Changed by Mona: compare to the arithmetic mean volume, as done originally. Now
     8012!--          particle volume is derived from the geometric mean diameter, not arithmetic (see
    80008013!--          SUBROUTINE set_sizebins).
    80018014             IF ( zvpart <= api6 * ( ( aero(ib)%vhilim + aero(ib)%vlolim ) / ( 2.0_wp * api6 ) ) ) &
     
    95379550    REAL(wp), DIMENSION(:), INTENT(out) ::  mconc  !< total dry or wet mass concentration
    95389551
    9539 !-- Number of components 
     9552!-- Number of components
    95409553    IF ( itype == 'dry' )  THEN
    9541        iend = prtcl%ncomp - 1 
     9554       iend = prtcl%ncomp - 1
    95429555    ELSE IF ( itype == 'wet' )  THEN
    95439556       iend = prtcl%ncomp
     
    1002710040                   message_string = 'end_time of the simulation exceeds the time dimension in ' // &
    1002810041                                    'the salsa input file.'
    10029                    CALL message( 'salsa_emission_setup', 'PA0692', 1, 2, 0, 6, 0 ) 
     10042                   CALL message( 'salsa_emission_setup', 'PA0692', 1, 2, 0, 6, 0 )
    1003010043                ENDIF
    1003110044!
     
    1009310106                inn = def_modes%cat_input_to_model(in)
    1009410107!
    10095 !--             Calculate the number concentration (1/m3) of a log-normal size distribution 
     10108!--             Calculate the number concentration (1/m3) of a log-normal size distribution
    1009610109!--             following Jacobson (2005): Eq 13.25.
    1009710110                def_modes%ntot_table = 6.0_wp * def_modes%pm_frac_table(:,inn) / ( pi *            &
     
    1064310656                                          MAX( time_since_reference_point, 0.0_wp ) ), DIM = 1 ) - 1
    1064410657!
    10645 !--    Allocate the data input array always before reading in the data and deallocate after (NOTE 
     10658!--    Allocate the data input array always before reading in the data and deallocate after (NOTE
    1064610659!--    that "preprocessed" input data array is applied now here)
    1064710660       ALLOCATE( dum_var_5d(1,1,nys:nyn,nxl:nxr,1:chem_emission_att%n_emiss_species) )
     
    1176211775!
    1176311776!--                         Diameter in micrometres
    11764                             mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp 
     11777                            mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp
    1176511778!
    1176611779!--                         Deposition factor: alveolar
     
    1211212125                   DO  k = nzb_do, nzt_do
    1211312126                      local_pf(i,j,k) = MERGE( nbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
    12114                                                BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12127                                               BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1211512128                   ENDDO
    1211612129                ENDDO
     
    1214612159                   DO  k = nzb_do, nzt_do
    1214712160                      local_pf(i,j,k) = MERGE( mbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
    12148                                                BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12161                                               BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1214912162                   ENDDO
    1215012163                ENDDO
     
    1222512238                      DO  k = nzb_do, nzt_do
    1222612239                         local_pf(i,j,k) = MERGE( ldsa_av(k,j,i), REAL( fill_value, KIND = wp ),   &
    12227                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12240                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1222812241                      ENDDO
    1222912242                   ENDDO
     
    1225612269                      DO  k = nzb_do, nzt_do
    1225712270                         local_pf(i,j,k) = MERGE( nufp_av(k,j,i), REAL( fill_value, KIND = wp ),   &
    12258                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12271                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1225912272                      ENDDO
    1226012273                   ENDDO
     
    1228512298                      DO  k = nzb_do, nzt_do
    1228612299                         local_pf(i,j,k) = MERGE( ntot_av(k,j,i), REAL( fill_value, KIND = wp ),   &
    12287                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12300                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1228812301                      ENDDO
    1228912302                   ENDDO
     
    1230512318                         ENDDO
    1230612319                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
    12307                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12320                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1230812321                      ENDDO
    1230912322                   ENDDO
     
    1231812331                      DO  k = nzb_do, nzt_do
    1231912332                         local_pf(i,j,k) = MERGE( pm01_av(k,j,i), REAL( fill_value, KIND = wp ),   &
    12320                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12333                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1232112334                      ENDDO
    1232212335                   ENDDO
     
    1233812351                         ENDDO
    1233912352                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
    12340                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12353                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1234112354                      ENDDO
    1234212355                   ENDDO
     
    1235112364                      DO  k = nzb_do, nzt_do
    1235212365                         local_pf(i,j,k) = MERGE( pm25_av(k,j,i), REAL( fill_value, KIND = wp ),   &
    12353                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12366                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1235412367                      ENDDO
    1235512368                   ENDDO
     
    1237112384                         ENDDO
    1237212385                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
    12373                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12386                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1237412387                      ENDDO
    1237512388                   ENDDO
     
    1240212415                            ENDDO
    1240312416                            local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),      &
    12404                                                      BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12417                                                     BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1240512418                         ENDDO
    1240612419                      ENDDO
     
    1243412447                         ENDDO
    1243512448                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
    12436                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12449                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1243712450                      ENDDO
    1243812451                   ENDDO
     
    1258512598                   ENDDO
    1258612599                ENDDO
    12587              ELSE 
     12600             ELSE
    1258812601                DO  i = 1, mask_size_l(mid,1)
    1258912602                   DO  j = 1, mask_size_l(mid,2)
     
    1266612679                      ENDDO
    1266712680                   ENDDO
    12668                 ELSE 
     12681                ELSE
    1266912682                   DO  i = 1, mask_size_l(mid,1)
    1267012683                      DO  j = 1, mask_size_l(mid,2)
     
    1275512768                      ENDDO
    1275612769                   ENDDO
    12757                 ENDDO 
     12770                ENDDO
    1275812771                IF ( .NOT. mask_surface(mid) )  THEN
    1275912772                   DO  i = 1, mask_size_l(mid,1)
     
    1276412777                      ENDDO
    1276512778                   ENDDO
    12766                 ELSE 
     12779                ELSE
    1276712780                   DO  i = 1, mask_size_l(mid,1)
    1276812781                      DO  j = 1, mask_size_l(mid,2)
     
    1280712820                      ENDDO
    1280812821                   ENDDO
    12809                 ENDDO 
     12822                ENDDO
    1281012823                IF ( .NOT. mask_surface(mid) )  THEN
    1281112824                   DO  i = 1, mask_size_l(mid,1)
     
    1281612829                      ENDDO
    1281712830                   ENDDO
    12818                 ELSE 
     12831                ELSE
    1281912832                   DO  i = 1, mask_size_l(mid,1)
    1282012833                      DO  j = 1, mask_size_l(mid,2)
     
    1286812881                      ENDDO
    1286912882                   ENDDO
    12870                 ELSE 
     12883                ELSE
    1287112884                   DO  i = 1, mask_size_l(mid,1)
    1287212885                      DO  j = 1, mask_size_l(mid,2)
     
    1291112924                      ENDDO
    1291212925                   ENDDO
    12913                 ENDDO 
     12926                ENDDO
    1291412927                IF ( .NOT. mask_surface(mid) )  THEN
    1291512928                   DO  i = 1, mask_size_l(mid,1)
     
    1292012933                      ENDDO
    1292112934                   ENDDO
    12922                 ELSE 
     12935                ELSE
    1292312936                   DO  i = 1, mask_size_l(mid,1)
    1292412937                      DO  j = 1, mask_size_l(mid,2)
     
    1309813111! Description:
    1309913112! ------------
    13100 !> Creates index tables for different (aerosol) components 
     13113!> Creates index tables for different (aerosol) components
    1310113114!------------------------------------------------------------------------------!
    1310213115 SUBROUTINE component_index_constructor( self, ncomp, nlist, listcomp )
     
    1358313596          message_string = 'end_time of the simulation exceeds the time dimension in the dynamic'//&
    1358413597                           ' input file.'
    13585           CALL message( 'salsa_nesting_offl_init', 'PA0690', 1, 2, 0, 6, 0 ) 
     13598          CALL message( 'salsa_nesting_offl_init', 'PA0690', 1, 2, 0, 6, 0 )
    1358613599       ENDIF
    1358713600
     
    1374713760          CALL message( 'salsa_mod: salsa_nesting_offl_input', 'PA0693', 2, 2, 0, 6, 0 )
    1374813761       ENDIF
    13749        
     13762
    1375013763       CALL close_input_file( salsa_nest_offl%id_dynamic )
    1375113764#endif
  • palm/trunk/SOURCE/spectra_mod.f90

    r4828 r4842  
    2525! -----------------
    2626! $Id$
     27! reading of namelist file and actions in case of namelist errors revised so that statement labels
     28! and goto statements are not required any more,
     29! deprecated namelist removed
     30!
     31! 4828 2021-01-05 11:21:41Z Giersch
    2732! support for MPI Fortran77 interface (mpif.h) removed
    2833!
     
    146151
    147152    USE control_parameters,                                                                        &
    148         ONLY:  dt_data_output,                                                                     &
    149                message_string
     153        ONLY:  dt_data_output
    150154
    151155    IMPLICIT NONE
    152156
    153     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    154 
    155     NAMELIST /spectra_par/  averaging_interval_sp,                                                 &
    156                             comp_spectra_level,                                                    &
    157                             data_output_sp,                                                        &
    158                             dt_dosp,                                                               &
    159                             skip_time_dosp,                                                        &
    160                             spectra_direction
     157    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter file
     158
     159    INTEGER(iwp) ::  io_status   !< status after reading the namelist file
     160
    161161
    162162    NAMELIST /spectra_parameters/                                                                  &
     
    168168                            spectra_direction
    169169!
    170 !-- Position the namelist-file at the beginning (it was already opened in parin), search for the
    171 !-- namelist-group of the package and position the file at this line.
    172     line = ' '
    173 
    174 !
    175 !-- Try to find the spectra package
    176     REWIND ( 11 )
    177     line = ' '
    178     DO WHILE ( INDEX( line, '&spectra_parameters' ) == 0 )
    179        READ ( 11, '(A)', END=12 )  line
    180     ENDDO
    181     BACKSPACE ( 11 )
    182 
    183 !
    184 !-- Read namelist
    185     READ ( 11, spectra_parameters, ERR = 10 )
    186 
    187 !
    188 !-- Default setting of dt_dosp here (instead of check_parameters), because its current value is
    189 !-- needed in init_pegrid
    190     IF ( dt_dosp == 9999999.9_wp )  dt_dosp = dt_data_output
    191 
    192 !
    193 !-- Set general switch that spectra shall be calculated
    194     calculate_spectra = .TRUE.
    195 
    196     GOTO 14
    197 
    198  10 BACKSPACE( 11 )
    199     READ( 11 , '(A)') line
    200     CALL parin_fail_message( 'spectra_parameters', line )
    201 !
    202 !-- Try to find the old namelist
    203  12 REWIND ( 11 )
    204     line = ' '
    205     DO WHILE ( INDEX( line, '&spectra_par' ) == 0 )
    206        READ ( 11, '(A)', END=14 )  line
    207     ENDDO
    208     BACKSPACE ( 11 )
    209 
    210 !
    211 !-- Read namelist
    212     READ ( 11, spectra_par, ERR = 13, END = 14 )
    213 
    214 
    215     message_string = 'namelist spectra_par is deprecated and will be removed in near future.' //   &
    216                      ' Please use namelist spectra_parameters instead'
    217     CALL message( 'spectra_parin', 'PA0487', 0, 1, 0, 6, 0 )
    218 !
    219 !-- Default setting of dt_dosp here (instead of check_parameters), because its current value is
    220 !-- needed in init_pegrid
    221     IF ( dt_dosp == 9999999.9_wp )  dt_dosp = dt_data_output
    222 
    223 !
    224 !-- Set general switch that spectra shall be calculated
    225     calculate_spectra = .TRUE.
    226 
    227     GOTO 14
    228 
    229  13 BACKSPACE( 11 )
    230     READ( 11 , '(A)') line
    231     CALL parin_fail_message( 'spectra_par', line )
    232 
    233 
    234  14 CONTINUE
     170!-- Position the namelist-file at the beginning (it was already opened in parin), and try to read
     171!-- the namelist.
     172    REWIND( 11 )
     173    READ( 11, spectra_parameters, IOSTAT=io_status )
     174
     175!
     176!-- Action depending on the READ status
     177    IF ( io_status == 0 )  THEN
     178!
     179!--    spectra_parameters namelist was found and read correctly.
     180!--    Default setting of dt_dosp here (instead of check_parameters), because its current value is
     181!--    needed in init_pegrid.
     182       IF ( dt_dosp == 9999999.9_wp )  dt_dosp = dt_data_output
     183!
     184!--    Set general switch that spectra shall be calculated.
     185       calculate_spectra = .TRUE.
     186
     187    ELSEIF ( io_status > 0 )  THEN
     188!
     189!--    spectra_parameters namelist was found but contained errors. Print an error message including
     190!--    the line that caused the problem.
     191       BACKSPACE( 11 )
     192       READ( 11 , '(A)' ) line
     193       CALL parin_fail_message( 'spectra_parameters', line )
     194
     195    ENDIF
    235196
    236197 END SUBROUTINE spectra_parin
  • palm/trunk/SOURCE/surface_data_output_mod.f90

    r4828 r4842  
    2525! -----------------
    2626! $Id$
     27! reading of namelist file and actions in case of namelist errors revised so that statement labels
     28! and goto statements are not required any more
     29!
     30! 4828 2021-01-05 11:21:41Z Giersch
    2731! Bugfix: correct the down-ward surf_lsm index in the routine surface_data_output_collect_2d
    2832!
     
    42054209    IMPLICIT NONE
    42064210
    4207     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    4208 
    4209 
    4210     NAMELIST /surface_data_output_parameters/ averaging_interval_surf, data_output_surf,           &
    4211                                               dt_dosurf, dt_dosurf_av, skip_time_dosurf,           &
    4212                                               skip_time_dosurf_av, to_netcdf, to_vtk
    4213 
    4214     line = ' '
    4215 
    4216 !
    4217 !-- Try to find the namelist
    4218     REWIND ( 11 )
    4219     line = ' '
    4220     DO WHILE ( INDEX( line, '&surface_data_output_parameters' ) == 0 )
    4221        READ ( 11, '(A)', END=14 )  line
    4222     ENDDO
    4223     BACKSPACE ( 11 )
    4224 
    4225 !
    4226 !-- Read namelist
    4227     READ ( 11, surface_data_output_parameters, ERR = 10 )
    4228 !
    4229 !-- Set flag that indicates that surface data output is switched on
    4230     surface_output = .TRUE.
    4231     GOTO 14
    4232 
    4233  10 BACKSPACE( 11 )
    4234     READ( 11 , '(A)') line
    4235     CALL parin_fail_message( 'surface_data_output_parameters', line )
    4236 
    4237  14 CONTINUE
    4238 
     4211    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter file
     4212
     4213    INTEGER(iwp) ::  io_status   !< status after reading the namelist file
     4214
     4215
     4216    NAMELIST /surface_data_output_parameters/  averaging_interval_surf,                            &
     4217                                               data_output_surf,                                   &
     4218                                               dt_dosurf,                                          &
     4219                                               dt_dosurf_av,                                       &
     4220                                               skip_time_dosurf,                                   &
     4221                                               skip_time_dosurf_av,                                &
     4222                                               to_netcdf,                                          &
     4223                                               to_vtk
     4224
     4225!
     4226!-- Move to the beginning of the namelist file and try to find and read the namelist.
     4227    REWIND( 11 )
     4228    READ( 11, surface_data_output_parameters, IOSTAT=io_status )
     4229!
     4230!-- Action depending on the READ status
     4231    IF ( io_status == 0 )  THEN
     4232!
     4233!--    surface_data_output_parameters namelist was found and read correctly. Set flag that indicates
     4234!--    that surface data output is switched on.
     4235       surface_output = .TRUE.
     4236
     4237    ELSEIF ( io_status > 0 )  THEN
     4238!
     4239!--    surface_data_output_parameters namelist was found but contained errors. Print an error
     4240!--    message including the line that caused the problem.
     4241       BACKSPACE( 11 )
     4242       READ( 11 , '(A)') line
     4243       CALL parin_fail_message( 'surface_data_output_parameters', line )
     4244
     4245    ENDIF
    42394246
    42404247 END SUBROUTINE surface_data_output_parin
  • palm/trunk/SOURCE/synthetic_turbulence_generator_mod.f90

    r4828 r4842  
    2525! -----------------
    2626! $Id$
     27! reading of namelist file and actions in case of namelist errors revised so that statement labels
     28! and goto statements are not required any more
     29!
     30! 4828 2021-01-05 11:21:41Z Giersch
    2731! Implementation of downward facing USM and LSM surfaces
    2832!
    2933! 4647 2020-08-24 16:36:18Z suehring
    30 ! Change default value of synthetic turbulence adjustment as well as compute_velocity_seeds_local 
    31 ! By default, the random-seed computation is now distributed among several cores. Especially for 
     34! Change default value of synthetic turbulence adjustment as well as compute_velocity_seeds_local
     35! By default, the random-seed computation is now distributed among several cores. Especially for
    3236! large length scales this is significantly faster.
    3337!
    3438! 4640 2020-08-11 16:28:32Z suehring
    35 ! - to avoid that the correction term in r11/r22 computation becomes unrealistically high, limit 
     39! - to avoid that the correction term in r11/r22 computation becomes unrealistically high, limit
    3640!   Obukhov length (term is not valid for near neutral conditions)
    3741! - to avoid unrealistically large perturbations, change computation of r21 so that this resembles
     
    4448! Bugfix in initialization from ASCII file - x-length scales at the bottom boundary were not
    4549! initialized properly
    46 ! 
     50!
    4751! 4566 2020-06-16 10:11:51Z suehring
    4852! - revise parametrization for reynolds-stress components, turbulent length- and time scales
     
    5054! - change default value of time interval to adjust turbulence parametrization
    5155! - bugfix in computation of amplitude-tensor (vertical flux of horizontal momentum)
    52 ! 
     56!
    5357! 4562 2020-06-12 08:38:47Z raasch
    5458! Parts of r4559 re-formatted
    55 ! 
     59!
    5660! 4559 2020-06-11 08:51:48Z raasch
    5761! File re-formatted to follow the PALM coding standard
     
    784788    ENDIF
    785789!
    786 !-- Assign initial profiles. Note, this is only required if turbulent inflow from the left is 
     790!-- Assign initial profiles. Note, this is only required if turbulent inflow from the left is
    787791!-- desired, not in case of any of the nesting (offline or self nesting) approaches.
    788     IF ( .NOT. nesting_offline  .AND.  .NOT.  child_domain )  THEN 
     792    IF ( .NOT. nesting_offline  .AND.  .NOT.  child_domain )  THEN
    789793       u_init = mean_inflow_profiles(:,1)
    790794       v_init = mean_inflow_profiles(:,2)
     
    12091213 SUBROUTINE stg_parin
    12101214
    1211     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    1212 
     1215    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter file
     1216
     1217    INTEGER(iwp) ::  io_status   !< status after reading the namelist file
    12131218
    12141219    NAMELIST /stg_par/  dt_stg_adjust,                                                             &
     
    12171222                        compute_velocity_seeds_local
    12181223
    1219     line = ' '
    1220 !
    1221 !-- Try to find stg package
    1222     REWIND ( 11 )
    1223     line = ' '
    1224     DO WHILE ( INDEX( line, '&stg_par' ) == 0 )
    1225        READ ( 11, '(A)', END = 20 )  line
    1226     ENDDO
    1227     BACKSPACE ( 11 )
    1228 
    1229 !
    1230 !-- Read namelist
    1231     READ ( 11, stg_par, ERR = 10, END = 20 )
    1232 
    1233 !
    1234 !-- Set flag that indicates that the synthetic turbulence generator is switched on
    1235     syn_turb_gen = .TRUE.
    1236     GOTO 20
    1237 
    1238  10 BACKSPACE( 11 )
    1239     READ( 11 , '(A)') line
    1240     CALL parin_fail_message( 'stg_par', line )
    1241 
    1242  20 CONTINUE
     1224
     1225!
     1226!-- Move to the beginning of the namelist file and try to find and read the namelist.
     1227    REWIND( 11 )
     1228    READ( 11, stg_par, IOSTAT=io_status )
     1229
     1230!
     1231!-- Action depending on the READ status
     1232    IF ( io_status == 0 )  THEN
     1233!
     1234!--    stg_par namelist was found and read correctly. Set flag that indicates that the synthetic
     1235!--    turbulence generator is switched on.
     1236       syn_turb_gen = .TRUE.
     1237
     1238    ELSEIF ( io_status > 0 )  THEN
     1239!
     1240!--    stg_par namelist was found but contained errors. Print an error message including the line
     1241!--    that caused the problem.
     1242       BACKSPACE( 11 )
     1243       READ( 11 , '(A)') line
     1244       CALL parin_fail_message( 'stg_par', line )
     1245
     1246    ENDIF
    12431247
    12441248 END SUBROUTINE stg_parin
     
    18071811       ENDDO
    18081812    ENDDO
    1809    
     1813
    18101814#if defined( __parallel )
    18111815!
     
    19371941    REAL(wp), DIMENSION(-mergp_x:mergp_x,nzb:nzt+1) :: b_x     !< filter function in x-direction
    19381942    REAL(wp), DIMENSION(-mergp_z:mergp_z,nzb:nzt+1) :: b_z     !< filter function in z-direction
    1939    
     1943
    19401944    REAL(wp), DIMENSION(nzb_y_stg:nzt_y_stg+1,nxl:nxr) :: f_n_l   !<  local velocity seed
    19411945    REAL(wp), DIMENSION(nzb:nzt+1,nxl:nxr)             :: f_n     !<  velocity seed
     
    19821986       ENDDO
    19831987    ENDDO
    1984    
     1988
    19851989#if defined( __parallel )
    19861990!
     
    20822086! Description:
    20832087! ------------
    2084 !> Parametrization of the Reynolds-stress componentes, turbulent length- and time scales. The 
     2088!> Parametrization of the Reynolds-stress componentes, turbulent length- and time scales. The
    20852089!> parametrization follows Brost et al. (1982) with modifications described in Rotach et al. (1996),
    20862090!> which is applied in state-of-the-art dispserion modelling.
     
    21652169!
    21662170!--    u'w' and v'w'. After calculation of the longitudinal and crosswind component
    2167 !--    these are projected along the x- and y-direction. Note, it is assumed that 
     2171!--    these are projected along the x- and y-direction. Note, it is assumed that
    21682172!--    the flux within the boundary points opposite to the vertical gradient.
    21692173       rlon2 = scale_us**2 * ( zzi - 1.0_wp )
     
    22982302    DO  k = nzb+1, nzt+1
    22992303       IF ( r11(k) > 10E-6_wp )  THEN
    2300           a11(k) = SQRT( r11(k) ) 
     2304          a11(k) = SQRT( r11(k) )
    23012305          a21(k) = r21(k) / a11(k)
    23022306          a31(k) = r31(k) / a11(k)
     
    23082312    ENDDO
    23092313    DO  k = nzb+1, nzt+1
    2310        a22(k) = r22(k) - a21(k)**2 
     2314       a22(k) = r22(k) - a21(k)**2
    23112315       IF ( a22(k) > 10E-6_wp )  THEN
    23122316          a22(k) = SQRT( a22(k) )
    23132317          a32(k) = ( r32(k) - a21(k) * a31(k) ) / a22(k)
    2314        ELSE 
     2318       ELSE
    23152319          a22(k) = 10E-8_wp
    23162320          a32(k) = 10E-8_wp
     
    23552359    CALL calc_scaling_variables
    23562360!
    2357 !-- Parametrize Reynolds-stress tensor. Parametrization follows Brost et al. (1982) with 
     2361!-- Parametrize Reynolds-stress tensor. Parametrization follows Brost et al. (1982) with
    23582362!-- modifications described in Rotach et al. (1996) and is based on boundary-layer depth, friction
    2359 !-- velocity and velocity scale. 
     2363!-- velocity and velocity scale.
    23602364    CALL parametrize_turbulence
    23612365!
    2362 !-- Calculate coefficient matrix from Reynolds stress tensor 
     2366!-- Calculate coefficient matrix from Reynolds stress tensor
    23632367!-- (Lund rotation)
    23642368    CALL calc_coeff_matrix
  • palm/trunk/SOURCE/urban_surface_mod.f90

    r4831 r4842  
    2727! -----------------
    2828! $Id$
     29! reading of namelist file and actions in case of namelist errors revised so that statement labels
     30! and goto statements are not required any more
     31!
     32! 4831 2021-01-06 17:55:14Z suehring
    2933! Bugfix in checking output variables with suffix indicating the surface facing
    30 ! 
     34!
    3135! 4828 2021-01-05 11:21:41Z Giersch
    3236! Deactivated A/C cooling capacity for office buildings built before year 2000.
     
    4347! - bugfix in openmp directive
    4448! - make t_green_h and t_green_v public (required in indoor model)
    45 ! 
     49!
    4650! 4747 2020-10-16 09:19:57Z pavelkrc
    4751! Fix window absorptivity calculation (correctly account for 2-sided reflection)
    48 ! 
     52!
    4953! 4738 2020-10-14 08:05:07Z maronga
    5054! Updating building data base (on behalf of Sascha Rissmann)
     
    111115! 4602 2020-07-14 14:49:45Z suehring
    112116! Add missing initialization of albedo type with values given from static input file
    113 ! 
     117!
    114118! 4581 2020-06-29 08:49:58Z suehring
    115119! Missing initialization in case of cyclic_fill runs
    116 ! 
     120!
    117121! 4535 2020-05-15 12:07:23Z raasch
    118122! bugfix for restart data format query
    119 ! 
     123!
    120124! 4517 2020-05-03 14:29:30Z raasch
    121125! added restart with MPI-IO for reading local arrays
    122 ! 
     126!
    123127! 4510 2020-04-29 14:19:18Z raasch
    124128! Further re-formatting to follow the PALM coding standard
     
    318322!> -------------
    319323!> @todo Revise sorting of building_pars
    320 !> @todo Revise initialization when building_pars / building_surface_pars are provided - 
     324!> @todo Revise initialization when building_pars / building_surface_pars are provided -
    321325!>       intialization is not consistent to building_pars
    322326!> @todo Revise flux conversion in energy-balance solver
     
    58135817    IMPLICIT NONE
    58145818
    5815     CHARACTER(LEN=80)  ::  line  !< string containing current line of file PARIN
    5816 
    5817     NAMELIST /urban_surface_par/                                                                   &
    5818                         building_type,                                                             &
    5819                         roof_category,                                                             &
    5820                         roof_inner_temperature,                                                    &
    5821                         roughness_concrete,                                                        &
    5822                         soil_inner_temperature,                                                    &
    5823                         urban_surface,                                                             &
    5824                         usm_wall_mod,                                                              &
    5825                         wall_category,                                                             &
    5826                         wall_inner_temperature,                                                    &
    5827                         window_inner_temperature
    5828 
     5819    CHARACTER(LEN=100)  ::  line  !< string containing current line of file PARIN
     5820
     5821    INTEGER(iwp) ::  io_status    !< status after reading the namelist file
    58295822
    58305823    NAMELIST /urban_surface_parameters/                                                            &
     
    58435836
    58445837!
    5845 !-- Try to find urban surface model package
    5846     REWIND ( 11 )
    5847     line = ' '
    5848     DO WHILE ( INDEX( line, '&urban_surface_parameters' ) == 0 )
    5849        READ ( 11, '(A)', END = 12 )  line
    5850     ENDDO
    5851     BACKSPACE ( 11 )
    5852 
    5853 !
    5854 !-- Read user-defined namelist
    5855     READ ( 11, urban_surface_parameters, ERR = 10 )
    5856 
    5857 !
    5858 !-- Set flag that indicates that the urban surface model is switched on
    5859     urban_surface = .TRUE.
    5860 
    5861     GOTO 14
    5862 
    5863  10 BACKSPACE( 11 )
    5864     READ( 11 , '(A)') line
    5865     CALL parin_fail_message( 'urban_surface_parameters', line )
    5866 !
    5867 !-- Try to find old namelist
    5868  12 REWIND ( 11 )
    5869     line = ' '
    5870     DO WHILE ( INDEX( line, '&urban_surface_par' ) == 0 )
    5871        READ ( 11, '(A)', END = 14 )  line
    5872     ENDDO
    5873     BACKSPACE ( 11 )
    5874 
    5875 !
    5876 !-- Read user-defined namelist
    5877     READ ( 11, urban_surface_par, ERR = 13, END = 14 )
    5878 
    5879     message_string = 'namelist urban_surface_par is deprecated and will be removed in near ' //    &
    5880                      'future. Please use namelist urban_surface_parameters instead'
    5881     CALL message( 'usm_parin', 'PA0487', 0, 1, 0, 6, 0 )
    5882 
    5883 !
    5884 !-- Set flag that indicates that the urban surface model is switched on
    5885     urban_surface = .TRUE.
    5886 
    5887     GOTO 14
    5888 
    5889  13 BACKSPACE( 11 )
    5890     READ( 11 , '(A)') line
    5891     CALL parin_fail_message( 'urban_surface_par', line )
    5892 
    5893 
    5894  14 CONTINUE
    5895 
     5838!-- Move to the beginning of the namelist file and try to find and read the namelist.
     5839    REWIND( 11 )
     5840    READ( 11, urban_surface_parameters, IOSTAT=io_status )
     5841
     5842!
     5843!-- Action depending on the READ status
     5844    IF ( io_status == 0 )  THEN
     5845!
     5846!--    urban_surface_parameters namelist was found and read correctly. Set flag that indicates that
     5847!--    the urban surface model is switched on.
     5848       urban_surface = .TRUE.
     5849
     5850    ELSEIF ( io_status > 0 )  THEN
     5851!
     5852!--    urban_surface_parameters namelist was found but contained errors. Print an error message
     5853!--    including the line that caused the problem.
     5854       BACKSPACE( 11 )
     5855       READ( 11 , '(A)' ) line
     5856       CALL parin_fail_message( 'urban_surface_parameters', line )
     5857
     5858    ENDIF
    58965859
    58975860 END SUBROUTINE usm_parin
     
    75847547       1512000.0_wp,   &  !< parameter 8   - [J/(m3*K)] heat capacity 3rd wall layer above ground floor level
    75857548       0.93_wp,        &  !< parameter 9   - [W/(m*K)] thermal conductivity 1st wall layer (outside) above ground floor level
    7586        0.81_wp,        &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level       
     7549       0.81_wp,        &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level
    75877550       0.81_wp,        &  !< parameter 11  - [W/(m*K)] thermal conductivity 3rd wall layer above ground floor level
    75887551       299.15_wp,      &  !< parameter 12  - [K] indoor target summer temperature
    7589        293.15_wp,      &  !< parameter 13  - [K] indoor target winter temperature 
     7552       293.15_wp,      &  !< parameter 13  - [K] indoor target winter temperature
    75907553       0.93_wp,        &  !< parameter 14  - [-] wall emissivity above ground floor level
    75917554       0.86_wp,        &  !< parameter 15  - [-] green emissivity above ground floor level
     
    77267689                        /)
    77277690
    7728     building_pars(:,2) = (/                                                                        &                       
     7691    building_pars(:,2) = (/                                                                        &
    77297692       0.75_wp,        &  !< parameter 0   - [-] wall fraction above ground floor level
    77307693       0.25_wp,        &  !< parameter 1   - [-] window fraction above ground floor level
     
    77377700       2112000.0_wp,   &  !< parameter 8   - [J/(m3*K)] heat capacity 3rd wall layer above ground floor level
    77387701       0.93_wp,        &  !< parameter 9   - [W/(m*K)] thermal conductivity 1st wall layer (outside) above ground floor level
    7739        0.046_wp,       &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level       
     7702       0.046_wp,       &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level
    77407703       2.1_wp,         &  !< parameter 11  - [W/(m*K)] thermal conductivity 3rd wall layer above ground floor level
    77417704       299.15_wp,      &  !< parameter 12  - [K] indoor target summer temperature
     
    78797842                        /)
    78807843
    7881     building_pars(:,3) = (/                                                                        &                       
     7844    building_pars(:,3) = (/                                                                        &
    78827845       0.71_wp,        &  !< parameter 0   - [-] wall fraction above ground floor level
    78837846       0.29_wp,        &  !< parameter 1   - [-] window fraction above ground floor level
     
    78907853       1344000.0_wp,   &  !< parameter 8   - [J/(m3*K)] heat capacity 3rd wall layer above ground floor level
    78917854       0.93_wp,        &  !< parameter 9   - [W/(m*K)] thermal conductivity 1st wall layer (outside) above ground floor level
    7892        0.035_wp,       &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level       
     7855       0.035_wp,       &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level
    78937856       0.68_wp,        &  !< parameter 11  - [W/(m*K)] thermal conductivity 3rd wall layer above ground floor level
    78947857       299.15_wp,      &  !< parameter 12  - [K] indoor target summer temperature
     
    80097972       4.5_wp,         &  !< parameter 127 - [m2/m2] ratio internal surface/floor area
    80107973       40.0_wp,        &  !< parameter 128 - [W] maximal heating capacity
    8011        0.0_wp,         &  !< parameter 129 - [W] maximal cooling capacity 
     7974       0.0_wp,         &  !< parameter 129 - [W] maximal cooling capacity
    80127975       0.0_wp,         &  !< parameter 130 - [W/m2] additional internal heat gains dependent on occupancy of the room
    80137976       4.2_wp,         &  !< parameter 131 - [W/m2] basic internal heat gains without occupancy of the room
     
    80438006       1512000.0_wp,   &  !< parameter 8   - [J/(m3*K)] heat capacity 3rd wall layer above ground floor level
    80448007       0.93_wp,        &  !< parameter 9   - [W/(m*K)] thermal conductivity 1st wall layer (outside) above ground floor level
    8045        0.81_wp,        &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level       
     8008       0.81_wp,        &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level
    80468009       0.81_wp,        &  !< parameter 11  - [W/(m*K)] thermal conductivity 3rd wall layer above ground floor level
    80478010       299.15_wp,      &  !< parameter 12  - [K] indoor target summer temperature
     
    81568119       2.9_wp,         &  !< parameter 121 - [W/(m2*K)] u-value windows
    81578120       1.0_wp,         &  !< parameter 122 - [1/h] basic airflow without occupancy of the room for - summer 1.0_wp, winter 0.2
    8158        1.0_wp,         &  !< parameter 123 - [1/h] additional airflow dependent on occupancy of the room for - summer 1.0_wp, winter 0.8 
     8121       1.0_wp,         &  !< parameter 123 - [1/h] additional airflow dependent on occupancy of the room for - summer 1.0_wp, winter 0.8
    81598122       0.0_wp,         &  !< parameter 124 - [-] heat recovery efficiency
    81608123       3.0_wp,         &  !< parameter 125 - [m2/m2] dynamic parameter specific effective surface
     
    81968159       2112000.0_wp,   &  !< parameter 8   - [J/(m3*K)] heat capacity 3rd wall layer above ground floor level
    81978160       0.93_wp,        &  !< parameter 9   - [W/(m*K)] thermal conductivity 1st wall layer (outside) above ground floor level
    8198        2.1_wp,         &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level       
     8161       2.1_wp,         &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level
    81998162       0.046_wp,       &  !< parameter 11  - [W/(m*K)] thermal conductivity 3rd wall layer above ground floor level
    82008163       299.15_wp,      &  !< parameter 12  - [K] indoor target summer temperature
     
    83088271       0.7_wp,         &  !< parameter 120 - [-] g-value windows
    83098272       1.7_wp,         &  !< parameter 121 - [W/(m2*K)] u-value windows
    8310        1.0_wp,         &  !< parameter 122 - [1/h] basic airflow without occupancy of the room for - summer 1.0_wp, winter 0.2 
     8273       1.0_wp,         &  !< parameter 122 - [1/h] basic airflow without occupancy of the room for - summer 1.0_wp, winter 0.2
    83118274       1.0_wp,         &  !< parameter 123 - [1/h] additional airflow dependent on occupancy of the room for - summer 1.0_wp, winter 0.8
    83128275       0.0_wp,         &  !< parameter 124 - [-] heat recovery efficiency
     
    83498312       1344000.0_wp,   &  !< parameter 8   - [J/(m3*K)] heat capacity 3rd wall layer above ground floor level
    83508313       0.93_wp,        &  !< parameter 9   - [W/(m*K)] thermal conductivity 1st wall layer (outside) above ground floor level
    8351        0.035_wp,       &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level       
     8314       0.035_wp,       &  !< parameter 10  - [W/(m*K)] thermal conductivity 2nd wall layer above ground floor level
    83528315       0.68_wp,        &  !< parameter 11  - [W/(m*K)] thermal conductivity 3rd wall layer above ground floor level
    83538316       299.15_wp,      &  !< parameter 12  - [K] indoor target summer temperature
     
    86308593      1848000.0_wp,    &  !< parameter 136 - [J/(m3*K)] heat capacity 4th wall layer (downside) above ground floor level
    86318594      1.0_wp,          &  !< parameter 137 - [W/(m*K)] thermal conductivity 4th wall layer (downside) above ground floor level
    8632       1848000.0_wp,    &  !< parameter 138 - [J/(m3*K)] heat capacity 4th wall layer (downside) ground floor level 
     8595      1848000.0_wp,    &  !< parameter 138 - [J/(m3*K)] heat capacity 4th wall layer (downside) ground floor level
    86338596      1.0_wp,          &  !< parameter 139 - [W/(m*K)] thermal conductivity 4th wall layer (downside) ground floor level
    86348597      1848000.0_wp,    &  !< parameter 140 - [J/(m3*K)] heat capacity 4th wall layer (downside) ground plate
  • palm/trunk/SOURCE/virtual_flight_mod.f90

    r4828 r4842  
    2020! Current revisions:
    2121! -----------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! reading of namelist file and actions in case of namelist errors revised so that statement labels
     28! and goto statements are not required any more
     29!
     30! 4828 2021-01-05 11:21:41Z Giersch
    2731! Bugfix, use time_since_reference_point instead of simulated_time
    28 ! 
     32!
    2933! 4535 2020-05-15 12:07:23Z raasch
    3034! bugfix for restart data format query
    31 ! 
     35!
    3236! 4522 2020-05-06 14:17:05Z suehring
    3337! Modularize user_init_flight in order to provide an explicit interface.
    34 ! 
     38!
    3539! 4497 2020-04-15 10:20:51Z raasch
    3640! file re-formatted to follow the PALM coding standard
     
    3943! 4495 2020-04-13 20:11:20Z raasch
    4044! restart data handling with MPI-IO added
    41 ! 
     45!
    4246! 4360 2020-01-07 11:25:50Z suehring
    4347! Corrected "Former revisions" section
     
    226230 SUBROUTINE flight_parin
    227231
    228     USE control_parameters,                                                                        &
    229         ONLY:  message_string
    230 
    231232    IMPLICIT NONE
    232233
    233     CHARACTER(LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    234 
    235     NAMELIST /flight_par/ flight_angle,                                                            &
    236                           flight_begin,                                                            &
    237                           flight_end,                                                              &
    238                           flight_level,                                                            &
    239                           leg_mode,                                                                &
    240                           max_elev_change,                                                         &
    241                           rate_of_climb,                                                           &
    242                           speed_agl,                                                               &
    243                           x_end,                                                                   &
    244                           x_start,                                                                 &
    245                           y_end,                                                                   &
    246                           y_start
     234    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter file
     235
     236    INTEGER(iwp) ::  io_status   !< status after reading the namelist file
    247237
    248238
     
    259249                                         y_end,                                                    &
    260250                                         y_start
    261 !
    262 !-- Try to find the namelist flight_par
    263     REWIND ( 11 )
    264     line = ' '
    265     DO  WHILE ( INDEX( line, '&virtual_flight_parameters' ) == 0 )
    266        READ ( 11, '(A)', END = 12 )  line
    267     ENDDO
    268     BACKSPACE ( 11 )
    269 
    270 !
    271 !-- Read namelist
    272     READ ( 11, virtual_flight_parameters, ERR = 10 )
    273 !
    274 !-- Set switch so that virtual flights shall be carried out
    275     virtual_flight = .TRUE.
    276 
    277     GOTO 14
    278 
    279  10    BACKSPACE( 11 )
    280        READ( 11 , '(A)') line
     251
     252!
     253!-- Move to the beginning of the namelist file and try to find and read the namelist.
     254    REWIND( 11 )
     255    READ( 11, virtual_flight_parameters, IOSTAT=io_status )
     256
     257!
     258!-- Action depending on the READ status
     259    IF ( io_status == 0 )  THEN
     260!
     261!--    virtual_flight_parameters namelist was found and read correctly. Set switch that virtual
     262!--    flights are carried out.
     263       virtual_flight = .TRUE.
     264
     265    ELSEIF ( io_status > 0 )  THEN
     266!
     267!--    virtual_flight_parameters namelist was found, but contained errors. Print an error message
     268!--    including the line that caused the problem.
     269       BACKSPACE( 11 )
     270       READ( 11 , '(A)' ) line
    281271       CALL parin_fail_message( 'virtual_flight_parameters', line )
    282 !
    283 !--    Try to find the old namelist
    284  12    REWIND ( 11 )
    285        line = ' '
    286        DO  WHILE ( INDEX( line, '&flight_par' ) == 0 )
    287           READ ( 11, '(A)', END = 14 )  line
    288        ENDDO
    289        BACKSPACE ( 11 )
    290 
    291 !
    292 !-- Read namelist
    293     READ ( 11, flight_par, ERR = 13, END = 14 )
    294 
    295     message_string = 'namelist flight_par is deprecated and will be ' //                           &
    296                      'removed in near future.& Please use namelist ' //                            &
    297                      'virtual_flight_parameters instead'
    298     CALL message( 'flight_parin', 'PA0487', 0, 1, 0, 6, 0 )
    299 !
    300 !-- Set switch so that virtual flights shall be carried out
    301     virtual_flight = .TRUE.
    302 
    303     GOTO 14
    304 
    305  13    BACKSPACE( 11 )
    306        READ( 11 , '(A)') line
    307        CALL parin_fail_message( 'flight_par', line )
    308 
    309  14    CONTINUE
     272
     273    ENDIF
    310274
    311275 END SUBROUTINE flight_parin
     276
    312277
    313278!--------------------------------------------------------------------------------------------------!
  • palm/trunk/TESTS/cases/topo_from_ASCII_file/INPUT/topo_from_ASCII_file_p3d

    r4462 r4842  
    1  &inipar nx = 39, ny = 39, nz = 40,
     1 &initialization_parameters
     2         nx = 39, ny = 39, nz = 40,
    23         dx = 2.0, dy = 2.0, dz = 2.0,
    34
     
    2021         topography_grid_convention = 'cell_center',  / ! default
    2122
    22  &d3par  end_time                  =    900.0,
     23 &runtime_parameters
     24         end_time                  =    900.0,
    2325         termination_time_needed   =    900.0,
    2426
Note: See TracChangeset for help on using the changeset viewer.