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