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

File:
1 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
Note: See TracChangeset for help on using the changeset viewer.