Changeset 2932


Ignore:
Timestamp:
Mar 26, 2018 9:39:22 AM (6 years ago)
Author:
maronga
Message:

renamed all Fortran NAMELISTS

Location:
palm/trunk/SOURCE
Files:
20 edited

Legend:

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

    r2918 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed particles_par to particle_parameters
     28!
     29! 2918 2018-03-21 15:52:14Z gronemeier
    2730! Add check for 1D model
    2831!
     
    32513254             IF (  .NOT.  particle_advection )  THEN
    32523255                message_string = 'output of "' // TRIM( var ) // '" requir' // &
    3253                    'es a "particles_par"-NAMELIST in the parameter file (PARIN)'
     3256                   'es a "particle_parameters"-NAMELIST in the parameter file (PARIN)'
    32543257                CALL message( 'check_parameters', 'PA0104', 1, 2, 0, 6, 0 )
    32553258             ENDIF
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r2894 r2932  
    2727! -----------------
    2828! $Id$
     29! renamed chemistry_par to chemistry_parameters
     30!
     31! 2894 2018-03-15 09:17:58Z Giersch
    2932! Calculations of the index range of the subdomain on file which overlaps with
    3033! the current subdomain are already done in read_restart_data_mod,
     
    600603!
    601604!-- Set initial concentration of profiles prescribed by parameters cs_profile
    602 !-- and cs_heights in the namelist &chemistry_par
     605!-- and cs_heights in the namelist &chemistry_parameters
    603606!-- (todo (FK): chem_init_profiles not ready yet, has some bugs)
    604607!     CALL chem_init_profiles
     
    780783! Description:
    781784! ------------
    782 !> Subroutine defining parin for &chemistry_par for chemistry model
     785!> Subroutine defining parin for &chemistry_parameters for chemistry model
    783786!------------------------------------------------------------------------------!
    784787   SUBROUTINE chem_parin
     
    797800      REAL(wp), DIMENSION(nmaxfixsteps) ::   my_steps   !< List of fixed timesteps   my_step(1) = 0.0 automatic stepping
    798801
    799       NAMELIST /chemistry_par/   bc_cs_b,                                &
    800                                  bc_cs_t,                                &
    801                                  call_chem_at_all_substeps,              &
    802                                  chem_debug0,                            &
    803                                  chem_debug1,                            &
    804                                  chem_debug2,                            &
    805                                  chem_gasphase_on,                       &
    806                                  cs_heights,                             &
    807                                  cs_name,                                &
    808                                  cs_profile,                             &
    809                                  cs_profile_name,                        &
    810                                  cs_surface,                             &
    811                                  emiss_factor_main,                      &
    812                                  emiss_factor_side,                      &                     
    813                                  icntrl,                                 &
    814                                  main_street_id,                         &
    815                                  max_street_id,                          &
    816                                  my_steps,                               &
    817                                  rcntrl,                                 &
    818                                  side_street_id,                         &
    819                                  photolysis_scheme,                      &
    820                                  wall_csflux,                            &
    821                                  cs_vertical_gradient,                   &
    822                                  top_csflux,                             &
    823                                  surface_csflux,                         &
    824                                  surface_csflux_name,                    &
    825                                  cs_surface_initial_change,              &
    826                                  cs_vertical_gradient_level
     802      NAMELIST /chemistry_parameters/   bc_cs_b,                          &
     803                                        bc_cs_t,                          &
     804                                        call_chem_at_all_substeps,        &
     805                                        chem_debug0,                      &
     806                                        chem_debug1,                      &
     807                                        chem_debug2,                      &
     808                                        chem_gasphase_on,                 &
     809                                        cs_heights,                       &
     810                                        cs_name,                          &
     811                                        cs_profile,                       &
     812                                        cs_profile_name,                  &
     813                                        cs_surface,                       &
     814                                        emiss_factor_main,                &
     815                                        emiss_factor_side,                &                     
     816                                        icntrl,                           &
     817                                        main_street_id,                   &
     818                                        max_street_id,                    &
     819                                        my_steps,                         &
     820                                        rcntrl,                           &
     821                                        side_street_id,                   &
     822                                        photolysis_scheme,                &
     823                                        wall_csflux,                      &
     824                                        cs_vertical_gradient,             &
     825                                        top_csflux,                       &
     826                                        surface_csflux,                   &
     827                                        surface_csflux_name,              &
     828                                        cs_surface_initial_change,        &
     829                                        cs_vertical_gradient_level
    827830                             
    828831!-- analogue to chem_names(nspj) we could invent chem_surfaceflux(nspj) and chem_topflux(nspj)
    829832!-- so this way we could prescribe a specific flux value for each species
    830 !>  chemistry_par for initial profiles
     833!>  chemistry_parameters for initial profiles
    831834!>  cs_names = 'O3', 'NO2', 'NO', ...   to set initial profiles)
    832835!>  cs_heights(1,:) = 0.0, 100.0, 500.0, 2000.0, .... (height levels where concs will be prescribed for O3)
     
    839842!--   Read chem namelist   
    840843!--   (todo: initialize these parameters in declaration part, do this for
    841 !--          all chemistry_par namelist parameters)
     844!--          all chemistry_parameters namelist parameters)
    842845      icntrl    = 0
    843846      rcntrl    = 0.0_wp
     
    851854      REWIND ( 11 )
    852855      line = ' '
    853       DO   WHILE ( INDEX( line, '&chemistry_par' ) == 0 )
     856      DO   WHILE ( INDEX( line, '&chemistry_parameters' ) == 0 )
    854857         READ ( 11, '(A)', END=10 )  line
    855858      ENDDO
     
    857860!
    858861!--   Read chemistry namelist
    859       READ ( 11, chemistry_par )                         
     862      READ ( 11, chemistry_parameters )                         
    860863!
    861864!--   Enable chemistry model
     
    17731776!
    17741777! !
    1775 ! !-- Writing out input parameters that are not part of chemistry_par namelist
    1776 ! !-- (namelist parameters are anyway read in again in case of restart)
     1778! !-- Writing out input parameters that are not part of chemistry_parameters
     1779! !-- namelist (namelist parameters are anyway read in again in case of restart)
    17771780!     DO lsp = 1, nvar
    17781781!        CALL wrd_write_string( 'conc_pr_init_'//chem_species(lsp)%name )
  • palm/trunk/SOURCE/cpulog_mod.f90

    r2718 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed d3par to runtime_parameters
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    116119!> ao far.
    117120!>
    118 !> d3par-parameter cpu_log_barrierwait can be used to set an MPI barrier at the
    119 !> beginning of the measurement (modus 'start' or 'continue'), to avoid that
    120 !> idle times (due to MPI calls in the code segment, which are
     121!> runtime_parameters-parameter cpu_log_barrierwait can be used to set an MPI
     122!> barrier at the beginning of the measurement (modus 'start' or 'continue'),
     123!> to avoid that idle times (due to MPI calls in the code segment, which are
    121124!> waiting for other processes to be finished) affect the measurements.
    122125!> If barriers shall not be used at all, a fourth, optional parameter has to be
  • palm/trunk/SOURCE/data_output_profiles.f90

    r2718 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed d3par to runtime_parameters
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    140143       ELSE
    141144!
    142 !--       This case may happen if dt_dopr is changed in the d3par-list of
    143 !--       a restart run
     145!--       This case may happen if dt_dopr is changed in the
     146!--       runtime_parameters-list of a restart run
    144147          RETURN
    145148       ENDIF
  • palm/trunk/SOURCE/gust_mod.f90

    r2912 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed gust_par to gust_parameters
     28!
     29!
    2730! Initial interface definition
    2831!
    2932!
    30 !
    3133! Description:
    3234! ------------
     
    156158! Description:
    157159! ------------
    158 !> Parin for &gust_par for gust module
     160!> Parin for &gust_parameters for gust module
    159161!------------------------------------------------------------------------------!
    160162    SUBROUTINE gust_parin
     
    165167       CHARACTER (LEN=80)  ::  line  !< dummy string that contains the current line of the parameter file
    166168
    167        NAMELIST /gust_par/  &
     169       NAMELIST /gust_parameters/  &
    168170          gust_module_enabled
    169171
     
    173175       REWIND ( 11 )
    174176       line = ' '
    175        DO   WHILE ( INDEX( line, '&gust_par' ) == 0 )
     177       DO   WHILE ( INDEX( line, '&gust_parameters' ) == 0 )
    176178          READ ( 11, '(A)', END=10 )  line
    177179       ENDDO
     
    179181!
    180182!--    Read user-defined namelist
    181        READ ( 11, gust_par )
     183       READ ( 11, gust_parameters )
    182184!
    183185!--    Set flag that indicates that the gust module is switched on
  • palm/trunk/SOURCE/land_surface_model_mod.f90

    r2921 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed lsm_par to land_surface_parameters. Bugfix in message calls
     28!
     29! 2921 2018-03-22 15:05:23Z Giersch
    2730! The activation of spinup has been moved to parin
    2831!
     
    10631066             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    10641067                      'res land_surface = .TRUE.'
    1065              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1068             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    10661069          ENDIF
    10671070          unit = 'm3/m3'
     
    10711074             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    10721075                      'res land_surface = .TRUE.'
    1073              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1076             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    10741077          ENDIF
    10751078          unit = 'K'   
     
    10811084                              TRIM( var ) // '" & only 2d-horizontal ' //      &
    10821085                              'cross sections are allowed for this value'
    1083              CALL message( 'check_parameters', 'PA0111', 1, 2, 0, 6, 0 )
     1086             CALL message( 'lsm_check_data_output', 'PA0111', 1, 2, 0, 6, 0 )
    10841087          ENDIF
    10851088          IF ( TRIM( var ) == 'lai*'  .AND.  .NOT.  land_surface )  THEN
    10861089             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    10871090                              'res land_surface = .TRUE.'
    1088              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1091             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    10891092          ENDIF
    10901093          IF ( TRIM( var ) == 'c_liq*'  .AND.  .NOT.  land_surface )  THEN
    10911094             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    10921095                              'res land_surface = .TRUE.'
    1093              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1096             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    10941097          ENDIF
    10951098          IF ( TRIM( var ) == 'c_soil*'  .AND.  .NOT.  land_surface )  THEN
    10961099             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    10971100                              'res land_surface = .TRUE.'
    1098              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1101             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    10991102          ENDIF
    11001103          IF ( TRIM( var ) == 'c_veg*'  .AND.  .NOT. land_surface )  THEN
    11011104             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    11021105                              'res land_surface = .TRUE.'
    1103              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1106             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    11041107          ENDIF
    11051108          IF ( TRIM( var ) == 'm_liq*'  .AND.  .NOT.  land_surface )  THEN
    11061109             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    11071110                              'res land_surface = .TRUE.'
    1108              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1111             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    11091112          ENDIF
    11101113          IF ( TRIM( var ) == 'qsws_liq*'  .AND.  .NOT. land_surface )         &
     
    11121115             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    11131116                              'res land_surface = .TRUE.'
    1114              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1117             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    11151118          ENDIF
    11161119          IF ( TRIM( var ) == 'qsws_soil*'  .AND.  .NOT.  land_surface )       &
     
    11181121             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    11191122                              'res land_surface = .TRUE.'
    1120              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1123             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    11211124          ENDIF
    11221125          IF ( TRIM( var ) == 'qsws_veg*'  .AND.  .NOT. land_surface )         &
     
    11241127             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    11251128                              'res land_surface = .TRUE.'
    1126              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1129             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    11271130          ENDIF
    11281131          IF ( TRIM( var ) == 'r_s*'  .AND.  .NOT.  land_surface )             &
     
    11301133             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    11311134                              'res land_surface = .TRUE.'
    1132              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     1135             CALL message( 'lsm_check_data_output', 'PA0404', 1, 2, 0, 6, 0 )
    11331136          ENDIF
    11341137
     
    11851188                              TRIM( data_output_pr(var_count) ) // ' is' //    &
    11861189                              'not implemented for land_surface = .FALSE.'
    1187              CALL message( 'check_parameters', 'PA0402', 1, 2, 0, 6, 0 )
     1190             CALL message( 'lsm_check_data_output_pr', 'PA0402', 1, 2, 0, 6, 0 )
    11881191          ELSE
    11891192             dopr_index(var_count) = 89
     
    12031206                              TRIM( data_output_pr(var_count) ) // ' is' //    &
    12041207                              ' not implemented for land_surface = .FALSE.'
    1205              CALL message( 'check_parameters', 'PA0402', 1, 2, 0, 6, 0 )
     1208             CALL message( 'lsm_check_data_output_pr', 'PA0402', 1, 2, 0, 6, 0 )
    12061209          ELSE
    12071210             dopr_index(var_count) = 91
     
    12511254       message_string = 'unknown surface type surface_type = "' //             &
    12521255                        TRIM( surface_type ) // '"'
    1253        CALL message( 'check_parameters', 'PA0019', 1, 2, 0, 6, 0 )
     1256       CALL message( 'lsm_check_parameters', 'PA0019', 1, 2, 0, 6, 0 )
    12541257    ENDIF
    12551258
     
    12621265                        'bc_pt_b = "dirichlet" and '//                         &
    12631266                        'bc_q_b  = "dirichlet"'
    1264        CALL message( 'check_parameters', 'PA0399', 1, 2, 0, 6, 0 )
     1267       CALL message( 'lsm_check_parameters', 'PA0399', 1, 2, 0, 6, 0 )
    12651268    ENDIF
    12661269
     
    12681271       message_string = 'lsm requires '//                                      &
    12691272                        'constant_flux_layer = .T.'
    1270        CALL message( 'check_parameters', 'PA0400', 1, 2, 0, 6, 0 )
     1273       CALL message( 'lsm_check_parameters', 'PA0400', 1, 2, 0, 6, 0 )
    12711274    ENDIF
    12721275
     
    12781281                              'requires setting of min_canopy_resistance'//    &
    12791282                              '/= 9999999.9'
    1280              CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
     1283             CALL message( 'lsm_check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    12811284          ENDIF
    12821285
     
    12851288                              'requires setting of leaf_area_index'//          &
    12861289                              '/= 9999999.9'
    1287              CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
     1290             CALL message( 'lsm_check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    12881291          ENDIF
    12891292
     
    12921295                              'requires setting of vegetation_coverage'//      &
    12931296                              '/= 9999999.9'
    1294                 CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
     1297                CALL message( 'lsm_check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    12951298          ENDIF
    12961299
     
    12991302                              'requires setting of'//                          &
    13001303                              'canopy_resistance_coefficient /= 9999999.9'
    1301              CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
     1304             CALL message( 'lsm_check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    13021305          ENDIF
    13031306
     
    13061309                              'requires setting of lambda_surface_stable'//    &
    13071310                              '/= 9999999.9'
    1308              CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
     1311             CALL message( 'lsm_check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    13091312          ENDIF
    13101313
     
    13131316                              'requires setting of lambda_surface_unstable'//  &
    13141317                              '/= 9999999.9'
    1315              CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
     1318             CALL message( 'lsm_check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    13161319          ENDIF
    13171320
     
    13201323                              'requires setting of f_shortwave_incoming'//     &
    13211324                              '/= 9999999.9'
    1322              CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
     1325             CALL message( 'lsm_check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    13231326          ENDIF
    13241327
     
    13271330                              'requires setting of z0_vegetation'//            &
    13281331                              '/= 9999999.9'
    1329              CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
     1332             CALL message( 'lsm_check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    13301333          ENDIF
    13311334
     
    13341337                              'requires setting of z0h_vegetation'//           &
    13351338                              '/= 9999999.9'
    1336              CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
     1339             CALL message( 'lsm_check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    13371340          ENDIF
    13381341       ENDIF
     
    13431346             message_string = 'vegetation_type = 1 (bare soil)'//              &
    13441347                              ' requires vegetation_coverage = 0'
    1345              CALL message( 'check_parameters', 'PA0471', 1, 2, 0, 6, 0 )
     1348             CALL message( 'lsm_check_parameters', 'PA0471', 1, 2, 0, 6, 0 )
    13461349          ENDIF
    13471350       ENDIF
     
    13551358                                     ' is not allowed in combination with ',   &
    13561359                                     'most_method = ', most_method
    1357           CALL message( 'check_parameters', 'PA0417', 1, 2, 0, 6, 0 )
     1360          CALL message( 'lsm_check_parameters', 'PA0417', 1, 2, 0, 6, 0 )
    13581361       ENDIF
    13591362
     
    13641367                              'requires setting of z0_water'//                 &
    13651368                              '/= 9999999.9'
    1366              CALL message( 'check_parameters', 'PA0415', 1, 2, 0, 6, 0 )
     1369             CALL message( 'lsm_check_parameters', 'PA0415', 1, 2, 0, 6, 0 )
    13671370          ENDIF
    13681371
     
    13711374                              'requires setting of z0h_water'//                &
    13721375                              '/= 9999999.9'
    1373              CALL message( 'check_parameters', 'PA0392', 1, 2, 0, 6, 0 )
     1376             CALL message( 'lsm_check_parameters', 'PA0392', 1, 2, 0, 6, 0 )
    13741377          ENDIF
    13751378         
     
    13781381                              'requires setting of water_temperature'//        &
    13791382                              '/= 9999999.9'
    1380              CALL message( 'check_parameters', 'PA0379', 1, 2, 0, 6, 0 )
     1383             CALL message( 'lsm_check_parameters', 'PA0379', 1, 2, 0, 6, 0 )
    13811384          ENDIF       
    13821385         
     
    13901393          message_string = 'non-default setting of dz_soil '//                  &
    13911394                           'does not allow to use pavement_type /= 0)'
    1392              CALL message( 'check_parameters', 'PA0341', 1, 2, 0, 6, 0 )
     1395             CALL message( 'lsm_check_parameters', 'PA0341', 1, 2, 0, 6, 0 )
    13931396          ENDIF
    13941397
     
    13991402                              'requires setting of z0_pavement'//              &
    14001403                              '/= 9999999.9'
    1401              CALL message( 'check_parameters', 'PA0352', 1, 2, 0, 6, 0 )
     1404             CALL message( 'lsm_check_parameters', 'PA0352', 1, 2, 0, 6, 0 )
    14021405          ENDIF
    14031406
     
    14061409                              'requires setting of z0h_pavement'//             &
    14071410                              '/= 9999999.9'
    1408              CALL message( 'check_parameters', 'PA0353', 1, 2, 0, 6, 0 )
     1411             CALL message( 'lsm_check_parameters', 'PA0353', 1, 2, 0, 6, 0 )
    14091412          ENDIF
    14101413         
     
    14131416                              'requires setting of pavement_heat_conduct'//    &
    14141417                              '/= 9999999.9'
    1415              CALL message( 'check_parameters', 'PA0342', 1, 2, 0, 6, 0 )
     1418             CALL message( 'lsm_check_parameters', 'PA0342', 1, 2, 0, 6, 0 )
    14161419          ENDIF
    14171420         
     
    14201423                              'requires setting of pavement_heat_capacity'//   &
    14211424                              '/= 9999999.9'
    1422              CALL message( 'check_parameters', 'PA0139', 1, 2, 0, 6, 0 )
     1425             CALL message( 'lsm_check_parameters', 'PA0139', 1, 2, 0, 6, 0 )
    14231426          ENDIF
    14241427
     
    14271430                              'requires setting of pavement_depth_level'//     &
    14281431                              '/= 0'
    1429              CALL message( 'check_parameters', 'PA0474', 1, 2, 0, 6, 0 )
     1432             CALL message( 'lsm_check_parameters', 'PA0474', 1, 2, 0, 6, 0 )
    14301433          ENDIF
    14311434
     
    14401443                                     'combination with most_method = ',        &
    14411444                                     TRIM( most_method )
    1442           CALL message( 'check_parameters', 'PA0999', 2, 2, 0, 6, 0 )
     1445          CALL message( 'lsm_check_parameters', 'PA0999', 2, 2, 0, 6, 0 )
    14431446       ENDIF
    14441447!
     
    14491452          message_string = 'pavement-surfaces are not allowed in ' //           &
    14501453                           'combination with a non-default setting of dz_soil'
    1451           CALL message( 'check_parameters', 'PA0999', 2, 2, 0, 6, 0 )
     1454          CALL message( 'lsm_check_parameters', 'PA0999', 2, 2, 0, 6, 0 )
    14521455       ENDIF
    14531456    ENDIF
     
    14581461    THEN
    14591462       message_string = 'surface_type = netcdf requires static input file.'
    1460        CALL message( 'check_parameters', 'PA0465', 1, 2, 0, 6, 0 )
     1463       CALL message( 'lsm_check_parameters', 'PA0465', 1, 2, 0, 6, 0 )
    14611464    ENDIF
    14621465
     
    14671470                           'requires setting of alpha_vangenuchten'//          &
    14681471                           '/= 9999999.9'
    1469           CALL message( 'check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
     1472          CALL message( 'lsm_check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
    14701473       ENDIF
    14711474
     
    14741477                           'requires setting of l_vangenuchten'//              &
    14751478                           '/= 9999999.9'
    1476           CALL message( 'check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
     1479          CALL message( 'lsm_check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
    14771480       ENDIF
    14781481
     
    14811484                           'requires setting of n_vangenuchten'//              &
    14821485                           '/= 9999999.9'
    1483           CALL message( 'check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
     1486          CALL message( 'lsm_check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
    14841487       ENDIF
    14851488
     
    14881491                           'requires setting of hydraulic_conductivity'//      &
    14891492                           '/= 9999999.9'
    1490           CALL message( 'check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
     1493          CALL message( 'lsm_check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
    14911494       ENDIF
    14921495
     
    14951498                           'requires setting of saturation_moisture'//         &
    14961499                           '/= 9999999.9'
    1497           CALL message( 'check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
     1500          CALL message( 'lsm_check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
    14981501       ENDIF
    14991502
     
    15021505                           'requires setting of field_capacity'//              &
    15031506                           '/= 9999999.9'
    1504           CALL message( 'check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
     1507          CALL message( 'lsm_check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
    15051508       ENDIF
    15061509
     
    15091512                           'requires setting of wilting_point'//               &
    15101513                           '/= 9999999.9'
    1511           CALL message( 'check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
     1514          CALL message( 'lsm_check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
    15121515       ENDIF
    15131516
     
    15161519                           'requires setting of residual_moisture'//           &
    15171520                           '/= 9999999.9'
    1518           CALL message( 'check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
     1521          CALL message( 'lsm_check_parameters', 'PA0403', 1, 2, 0, 6, 0 )
    15191522       ENDIF
    15201523
     
    15481551                                  ' in soil_temperature (', COUNT(             &
    15491552                                   soil_temperature /= 9999999.9_wp ), ')'
    1550           CALL message( 'check_parameters', 'PA0471', 1, 2, 0, 6, 0 )
     1553          CALL message( 'lsm_check_parameters', 'PA0471', 1, 2, 0, 6, 0 )
    15511554    ENDIF
    15521555
     
    15541557          message_string = 'deep_soil_temperature is not set but must be'//    &
    15551558                           '/= 9999999.9'
    1556           CALL message( 'check_parameters', 'PA0472', 1, 2, 0, 6, 0 )
     1559          CALL message( 'lsm_check_parameters', 'PA0472', 1, 2, 0, 6, 0 )
    15571560    ENDIF
    15581561
     
    15641567                           'requires setting of root_fraction'//               &
    15651568                           '/= 9999999.9 and SUM(root_fraction) = 1'
    1566           CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
     1569          CALL message( 'lsm_check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    15671570       ENDIF
    15681571    ENDIF   
     
    15761579          message_string = 'soil_moisture must not exceed its saturation' //    &
    15771580                            ' value'
    1578           CALL message( 'check_parameters', 'PA0458', 1, 2, 0, 6, 0 )
     1581          CALL message( 'lsm_check_parameters', 'PA0458', 1, 2, 0, 6, 0 )
    15791582       ENDIF
    15801583    ENDDO
     
    45384541    SUBROUTINE lsm_parin
    45394542
     4543       USE control_parameters,                                                 &
     4544           ONLY:  message_string
    45404545
    45414546       IMPLICIT NONE
     
    45694574                                  z0h_water, z0q_water, z0_pavement,           &
    45704575                                  z0h_pavement, z0q_pavement
    4571        
     4576
     4577       NAMELIST /land_surface_parameters/                                      &
     4578                                  alpha_vangenuchten, c_surface,               &
     4579                                  canopy_resistance_coefficient,               &
     4580                                  constant_roughness,                          &
     4581                                  conserve_water_content,                      &
     4582                                  deep_soil_temperature,                       &
     4583                                  dz_soil,                                     &
     4584                                  f_shortwave_incoming, field_capacity,        &
     4585                                  aero_resist_kray, hydraulic_conductivity,    &
     4586                                  lambda_surface_stable,                       &
     4587                                  lambda_surface_unstable, leaf_area_index,    &
     4588                                  l_vangenuchten, min_canopy_resistance,       &
     4589                                  min_soil_resistance, n_vangenuchten,         &
     4590                                  pavement_depth_level,                        &
     4591                                  pavement_heat_capacity,                      &
     4592                                  pavement_heat_conduct, pavement_type,        &
     4593                                  residual_moisture, root_fraction,            &
     4594                                  saturation_moisture, skip_time_do_lsm,       &
     4595                                  soil_moisture, soil_temperature,             &
     4596                                  soil_type,                                   &
     4597                                  surface_type,                                &
     4598                                  vegetation_coverage, vegetation_type,        &
     4599                                  water_temperature, water_type,               &
     4600                                  wilting_point, z0_vegetation,                &
     4601                                  z0h_vegetation, z0q_vegetation, z0_water,    &
     4602                                  z0h_water, z0q_water, z0_pavement,           &
     4603                                  z0h_pavement, z0q_pavement
     4604                                 
    45724605       line = ' '
    4573        
     4606 
    45744607!
    45754608!--    Try to find land surface model package
    45764609       REWIND ( 11 )
    45774610       line = ' '
    4578        DO   WHILE ( INDEX( line, '&lsm_par' ) == 0 )
     4611       DO   WHILE ( INDEX( line, '&land_surface_parameters' ) == 0 )
    45794612          READ ( 11, '(A)', END=10 )  line
    45804613       ENDDO
     
    45834616!
    45844617!--    Read user-defined namelist
    4585        READ ( 11, lsm_par )
     4618       READ ( 11, land_surface_parameters )
    45864619
    45874620!
    45884621!--    Set flag that indicates that the land surface model is switched on
    45894622       land_surface = .TRUE.
    4590 
    4591 
    4592  10    CONTINUE
     4623       
     4624       GOTO 12
     4625!
     4626!--    Try to find old namelist
     4627 10    REWIND ( 11 )
     4628       line = ' '
     4629       DO   WHILE ( INDEX( line, '&lsm_par' ) == 0 )
     4630          READ ( 11, '(A)', END=12 )  line
     4631       ENDDO
     4632       BACKSPACE ( 11 )
     4633
     4634!
     4635!--    Read user-defined namelist
     4636       READ ( 11, lsm_par )
     4637
     4638       message_string = 'namelist lsm_par is deprecated and will be ' // &
     4639                     'removed in near future. Please &use namelist ' //  &
     4640                     'land_surface_parameters instead'
     4641       CALL message( 'lsm_parin', 'PA0487', 0, 1, 0, 6, 0 )
     4642       
     4643!
     4644!--    Set flag that indicates that the land surface model is switched on
     4645       land_surface = .TRUE.
     4646
     4647
     4648 12    CONTINUE
    45934649       
    45944650
  • palm/trunk/SOURCE/lpm_splitting.f90

    r2718 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed particles_par to particle_parameters
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    167170!--             a critical radius  (radius_split) a critical weighting factor
    168171!--             (weight_factor_split) and a splitting factor (splitting_factor)
    169 !--             must  be prescribed (see particles_par). Super droplets which
    170 !--             have a larger radius and larger weighting factor are split into
    171 !--             'splitting_factor' super droplets. Therefore, the weighting
     172!--             must  be prescribed (see particle_parameters). Super droplets
     173!--             which have a larger radius and larger weighting factor are split
     174!--             into 'splitting_factor' super droplets. Therefore, the weighting
    172175!--             factor of  the super droplet and all created clones is reduced
    173176!--             by the factor of 'splitting_factor'.
  • palm/trunk/SOURCE/message.f90

    r2718 r2932  
    2020! Current revisions:
    2121! -----------------
    22 ! 
     22!
    2323!
    2424! Former revisions:
  • palm/trunk/SOURCE/netcdf_interface_mod.f90

    r2817 r2932  
    2525! -----------------
    2626! $Id$
     27! Renamed inipar to initialization_parameters.
     28!
     29! 2817 2018-02-19 16:32:21Z knoop
    2730! Preliminary gust module interface implemented
    2831!
     
    682685
    683686             CASE DEFAULT
    684                 WRITE ( message_string, * ) 'unknown variable in inipar ',    &
    685                                   'assignment: netcdf_precision(', i, ')="',  &
     687                WRITE ( message_string, * ) 'unknown variable in ' //          &
     688                                  'initialization_parameters ',                &
     689                                  'assignment: netcdf_precision(', i, ')="',   &
    686690                                            TRIM( netcdf_precision(i) ),'"'
    687691                CALL message( 'netcdf_define_header', 'PA0243', 1, 2, 0, 6, 0 )
  • palm/trunk/SOURCE/package_parin.f90

    r2718 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed particles_par to particle_parameters
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    157160
    158161    USE control_parameters,                                                    &
    159         ONLY:  dt_data_output, dt_dopts, dt_dvrp, particle_maximum_age,        &
    160                threshold
     162        ONLY:  dt_data_output, dt_dopts, dt_dvrp, message_string,              &
     163               particle_maximum_age, threshold
    161164
    162165    USE dvrp_variables,                                                        &
     
    249252                                  write_particle_statistics
    250253
     254                                 
     255    NAMELIST /particle_parameters/                                             &
     256                                  aero_species, aero_type, aero_weight,        &
     257                                  alloc_factor, bc_par_b, bc_par_lr,           &
     258                                  bc_par_ns, bc_par_t,                         &
     259                                  collision_kernel, curvature_solution_effects,&
     260                                  deallocate_memory, density_ratio,            &
     261                                  dissipation_classes, dt_dopts,               &
     262                                  dt_min_part, dt_prel,                        &
     263                                  dt_write_particle_data,                      &
     264                                  end_time_prel, initial_weighting_factor,     &
     265                                  log_sigma,                                   &
     266                                  max_number_particles_per_gridbox, merging,   &
     267                                  min_nr_particle,                             &
     268                                  na, number_concentration,                    &
     269                                  number_of_particle_groups,                   &
     270                                  number_particles_per_gridbox,                &
     271                                  particles_per_point,                         &
     272                                  particle_advection_start,                    &
     273                                  particle_maximum_age, pdx, pdy, pdz, psb,    &
     274                                  psl, psn, psr, pss, pst, radius,             &
     275                                  radius_classes, radius_merge, radius_split,  &
     276                                  random_start_position,                       &
     277                                  read_particles_from_restartfile, rm,         &
     278                                  seed_follows_topography,                     &
     279                                  splitting, splitting_factor,                 &
     280                                  splitting_factor_max, splitting_function,    &
     281                                  splitting_mode, step_dealloc,                &
     282                                  use_sgs_for_particles,                       &
     283                                  vertical_particle_advection,                 &
     284                                  weight_factor_merge, weight_factor_split,    &
     285                                  write_particle_statistics
    251286!
    252287!-- Position the namelist-file at the beginning (it was already opened in
     
    275310    REWIND ( 11 )
    276311    line = ' '
    277     DO   WHILE ( INDEX( line, '&particles_par' ) == 0 )
     312    DO   WHILE ( INDEX( line, '&particle_parameters' ) == 0 )
    278313       READ ( 11, '(A)', END=30 )  line
    279314    ENDDO
     
    282317!
    283318!-- Read user-defined namelist
    284     READ ( 11, particles_par )
     319    READ ( 11, particle_parameters )
    285320
    286321!
    287322!-- Set flag that indicates that particles are switched on
    288323    particle_advection = .TRUE.
    289 
    290  30 CONTINUE
     324   
     325    GOTO 31
     326
     327!
     328!-- Try to find particles package (old namelist)
     32930  REWIND ( 11 )
     330    line = ' '
     331    DO   WHILE ( INDEX( line, '&particles_par' ) == 0 )
     332       READ ( 11, '(A)', END=31 )  line
     333    ENDDO
     334    BACKSPACE ( 11 )
     335
     336!
     337!-- Read user-defined namelist
     338    READ ( 11, particles_par )
     339   
     340   
     341    message_string = 'namelist particles_par is deprecated and will be ' //    &
     342                     'removed in near future. Please &use namelist ' //        &
     343                     'particle_parameters instead'
     344    CALL message( 'package_parin', 'PA0487', 0, 1, 0, 6, 0 )
     345
     346!
     347!-- Set flag that indicates that particles are switched on
     348    particle_advection = .TRUE.
     349
     350 31 CONTINUE
    291351
    292352 END SUBROUTINE package_parin
  • palm/trunk/SOURCE/parin.f90

    r2921 r2932  
    2525! -----------------
    2626! $Id$
     27! inipar renamed to initialization_parameters.
     28! d3par renamed to runtime_parameters.
     29!
     30! 2921 2018-03-22 15:05:23Z Giersch
    2731! Activation of spinup has been moved from lsm/usm_parin to parin itself
    2832!
     
    523527             wall_salinityflux, wall_scalarflux, y_shift, zeta_max, zeta_min,  &
    524528             z0h_factor
    525      
     529
     530    NAMELIST /initialization_parameters/  aerosol_bulk, alpha_surface,         &
     531             approximation, bc_e_b,                                            &
     532             bc_lr, bc_ns, bc_p_b, bc_p_t, bc_pt_b, bc_pt_t, bc_q_b,           &
     533             bc_q_t,bc_s_b, bc_s_t, bc_sa_t, bc_uv_b, bc_uv_t,                 &
     534             bottom_salinityflux, building_height, building_length_x,          &
     535             building_length_y, building_wall_left, building_wall_south,       &
     536             calc_soil_moisture_during_spinup,                                 &
     537             call_psolver_at_all_substeps, call_microphysics_at_all_substeps,  &
     538             canyon_height,                                                    &
     539             canyon_width_x, canyon_width_y, canyon_wall_left,                 &
     540             canyon_wall_south, c_sedimentation, cfl_factor, cloud_droplets,   &
     541             cloud_physics, cloud_scheme, cloud_top_radiation,                 &
     542             cloud_water_sedimentation,                                        &
     543             collective_wait, collision_turbulence, complex_terrain,           &
     544             conserve_volume_flow,                                             &
     545             conserve_volume_flow_mode, constant_flux_layer,                   &
     546             coupling_start_time, curvature_solution_effects_bulk,             &
     547             cycle_mg, damp_level_1d,                                          &
     548             data_output_during_spinup,                                        &
     549             day_of_year_init,                                                 &
     550             dissipation_1d,                                                   &
     551             dp_external, dp_level_b, dp_smooth, dpdxy, dry_aerosol_radius,    &
     552             dt, dt_pr_1d, dt_run_control_1d, dt_spinup, dx, dy, dz, dz_max,   &
     553             dz_stretch_factor, dz_stretch_level, end_time_1d,                 &
     554             ensemble_member_nr, e_init, e_min, fft_method,                    &
     555             flux_input_mode, flux_output_mode, forcing,                       &
     556             galilei_transformation, humidity,                                 &
     557             inflow_damping_height, inflow_damping_width,                      &
     558             inflow_disturbance_begin, inflow_disturbance_end,                 &
     559             initializing_actions, km_constant,                                &
     560             large_scale_forcing, large_scale_subsidence, latitude,            &
     561             limiter_sedimentation, longitude,                                 &
     562             loop_optimization, lsf_exception, masking_method, mg_cycles,      &
     563             mg_switch_to_pe0_level, mixing_length_1d, momentum_advec,         &
     564             most_method, na_init, nc_const, netcdf_precision, neutral, ngsrb, &
     565             nsor, nsor_ini, nudging, nx, ny, nz, ocean, omega, omega_sor,     &
     566             outflow_source_plane, passive_scalar,                             &
     567             prandtl_number, precipitation, psolver, pt_damping_factor,        &
     568             pt_damping_width, pt_reference, pt_surface,                       &
     569             pt_surface_initial_change, pt_vertical_gradient,                  &
     570             pt_vertical_gradient_level, q_surface, q_surface_initial_change,  &
     571             q_vertical_gradient, q_vertical_gradient_level,                   &
     572             random_generator, random_heatflux, rans_mode,                     &
     573             rayleigh_damping_factor, rayleigh_damping_height,                 &
     574             recycling_width, recycling_yshift,                                &
     575             reference_state, residual_limit,                                  &
     576             roughness_length, sa_surface,                                     &
     577             sa_vertical_gradient, sa_vertical_gradient_level, scalar_advec,   &
     578             scalar_rayleigh_damping, sigma_bulk,                              &
     579             spinup_time, spinup_pt_amplitude, spinup_pt_mean,                 &
     580             statistic_regions, subs_vertical_gradient,                        &
     581             subs_vertical_gradient_level, surface_heatflux, surface_pressure, &
     582             surface_scalarflux, surface_waterflux,                            &
     583             s_surface, s_surface_initial_change, s_vertical_gradient,         &
     584             s_vertical_gradient_level, time_utc_init, timestep_scheme,        &
     585             topography, topography_grid_convention, top_heatflux,             &
     586             top_momentumflux_u, top_momentumflux_v, top_salinityflux,         &
     587             top_scalarflux, transpose_compute_overlap,                        &
     588             tunnel_height, tunnel_length, tunnel_width_x, tunnel_width_y,     &
     589             tunnel_wall_depth, turbulence_closure,                            &
     590             turbulent_inflow, turbulent_outflow,                              &
     591             use_subsidence_tendencies, ug_surface, ug_vertical_gradient,      &
     592             ug_vertical_gradient_level, use_surface_fluxes, use_cmax,         &
     593             use_top_fluxes, use_ug_for_galilei_tr, use_upstream_for_tke,      &
     594             uv_heights, u_bulk, u_profile, vg_surface, vg_vertical_gradient,  &
     595             vg_vertical_gradient_level, v_bulk, v_profile, ventilation_effect,&
     596             wall_adjustment, wall_heatflux, wall_humidityflux,                &
     597             wall_salinityflux, wall_scalarflux, y_shift, zeta_max, zeta_min,  &
     598             z0h_factor
     599             
    526600    NAMELIST /d3par/  averaging_interval, averaging_interval_pr,               &
    527601             cpu_log_barrierwait, create_disturbances,                         &
     
    545619             termination_time_needed, vnest_start_time, z_max_do2d
    546620
     621    NAMELIST /runtime_parameters/  averaging_interval, averaging_interval_pr,  &
     622             cpu_log_barrierwait, create_disturbances,                         &
     623             cross_profiles, data_output, data_output_masks,                   &
     624             data_output_pr, data_output_2d_on_each_pe, disturbance_amplitude, &
     625             disturbance_energy_limit, disturbance_level_b,                    &
     626             disturbance_level_t, do2d_at_begin, do3d_at_begin,                &
     627             dt, dt_averaging_input, dt_averaging_input_pr,                    &
     628             dt_coupling, dt_data_output, dt_data_output_av, dt_disturb,       &
     629             dt_domask, dt_dopr, dt_dopr_listing, dt_dots, dt_do2d_xy,         &
     630             dt_do2d_xz, dt_do2d_yz, dt_do3d, dt_max, dt_restart,              &
     631             dt_run_control,end_time, force_print_header, mask_scale_x,        &
     632             mask_scale_y, mask_scale_z, mask_x, mask_y, mask_z, mask_x_loop,  &
     633             mask_y_loop, mask_z_loop, netcdf_data_format, netcdf_deflate,     &
     634             normalizing_region, npex, npey, nz_do3d,                          &
     635             precipitation_amount_interval, profile_columns, profile_rows,     &
     636             restart_time, section_xy, section_xz, section_yz,                 &
     637             skip_time_data_output, skip_time_data_output_av, skip_time_dopr,  &
     638             skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,          &
     639             skip_time_do3d, skip_time_domask, synchronous_exchange,           &
     640             termination_time_needed, vnest_start_time, z_max_do2d
    547641
    548642    NAMELIST /envpar/  batch_job, host, local_dvrserver_running,               &
     
    617711!--       Read the control parameters for initialization.
    618712!--       The namelist "inipar" must be provided in the NAMELIST-file.
    619           READ ( 11, inipar, ERR=10, END=11 )
     713          READ ( 11, initialization_parameters, ERR=10, END=11 )
    620714
    621715          GOTO 12
    622716
    623  10       message_string = 'errors in \$inipar &or no \$inipar-namelist ' //   &
     717 10       message_string = 'errors in initialization_parameters &or no ' //    &
     718                           'initialization_parameters-namelist ' //            &
    624719                           'found (CRAY-machines only)'
    625720          CALL message( 'parin', 'PA0271', 1, 2, 0, 6, 0 )
    626721
    627  11       message_string = 'no \$inipar-namelist found'
     722 11       REWIND ( 11 )
     723          READ ( 11, inipar, ERR=13, END=14 )
     724 
     725          message_string = 'namelist inipar is deprecated and will be ' //     &
     726                          'removed in near future. Please &use namelist ' //   &
     727                          'initialization_parameters instead'
     728          CALL message( 'parin', 'PA0272', 0, 1, 0, 6, 0 )
     729 
     730          GOTO 12
     731 
     732 13       message_string = 'errors in inipar &or no inipar-namelist ' //       &
     733                           'found (CRAY-machines only)'
     734          CALL message( 'parin', 'PA0271', 1, 2, 0, 6, 0 )
     735         
     736 14       message_string = 'no initialization_parameters-namelist found'
    628737          CALL message( 'parin', 'PA0272', 1, 2, 0, 6, 0 )
    629738
    630739!
    631740!--       Try to read runtime parameters given by the user for this run
    632 !--       (namelist "d3par"). The namelist "d3par" can be omitted. In that case
    633 !--       default values are used for the parameters.
     741!--       (namelist "runtime_parameters"). The namelist "runtime_parmeters"   
     742!--       can be omitted. In that case default values are used for the         
     743!--       parameters.
    634744 12       line = ' '
    635745
    636746          REWIND ( 11 )
    637747          line = ' '
    638           DO   WHILE ( INDEX( line, '&d3par' ) == 0 )
     748          DO   WHILE ( INDEX( line, '&runtime_parameters' ) == 0 )
    639749             READ ( 11, '(A)', END=20 )  line
    640750          ENDDO
     
    643753!
    644754!--       Read namelist
     755          READ ( 11, runtime_parameters )
     756
     757          GOTO 21
     758         
     759 20       REWIND ( 11 )
     760          line = ' '
     761          DO   WHILE ( INDEX( line, '&d3par' ) == 0 )
     762             READ ( 11, '(A)', END=21 )  line
     763          ENDDO
     764          BACKSPACE ( 11 )
     765 
     766 !
     767!--       Read namelist
    645768          READ ( 11, d3par )
    646 
    647  20       CONTINUE
     769 
     770          message_string = 'namelist d3par is deprecated and will be ' //      &
     771                          'removed in near future. Please &use namelist ' //   &
     772                          'runtime_parameters instead'
     773          CALL message( 'parin', 'PA0487', 0, 1, 0, 6, 0 )
     774         
     775 21       CONTINUE
    648776
    649777!
  • palm/trunk/SOURCE/plant_canopy_model_mod.f90

    r2920 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed canopy_par to plant_canopy_parameters
     28!
     29! 2920 2018-03-22 11:22:01Z kanani
    2730! Move usm_lad_rma and prototype_lad to radiation_model (moh.hefny)
    2831!
     
    945948! Description:
    946949! ------------
    947 !> Parin for &canopy_par for plant canopy model
     950!> Parin for &plant_canopy_parameters for plant canopy model
    948951!------------------------------------------------------------------------------!
    949952    SUBROUTINE pcm_parin
    950953
    951954       USE control_parameters,                                                 &
    952            ONLY:  plant_canopy
     955           ONLY:  message_string, plant_canopy
    953956
    954957       IMPLICIT NONE
     
    956959       CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    957960       
     961       NAMELIST /plant_canopy_parameters/                                      &
     962                                  alpha_lad, beta_lad, canopy_drag_coeff,      &
     963                                  canopy_mode, cthf,                           &
     964                                  lad_surface,                                 &
     965                                  lad_vertical_gradient,                       &
     966                                  lad_vertical_gradient_level,                 &
     967                                  lai_beta,                                    &
     968                                  leaf_scalar_exch_coeff,                      &
     969                                  leaf_surface_conc, pch_index
     970
    958971       NAMELIST /canopy_par/      alpha_lad, beta_lad, canopy_drag_coeff,      &
    959972                                  canopy_mode, cthf,                           &
     
    964977                                  leaf_scalar_exch_coeff,                      &
    965978                                  leaf_surface_conc, pch_index
    966        
     979                                  
    967980       line = ' '
    968981       
     
    971984       REWIND ( 11 )
    972985       line = ' '
    973        DO   WHILE ( INDEX( line, '&canopy_par' ) == 0 )
     986       DO   WHILE ( INDEX( line, '&plant_canopy_parameters' ) == 0 )
    974987          READ ( 11, '(A)', END=10 )  line
    975988       ENDDO
     
    978991!
    979992!--    Read user-defined namelist
    980        READ ( 11, canopy_par )
     993       READ ( 11, plant_canopy_parameters )
    981994
    982995!
    983996!--    Set flag that indicates that the radiation model is switched on
    984997       plant_canopy = .TRUE.
    985 
    986  10    CONTINUE
     998       
     999       GOTO 12
     1000!
     1001!--    Try to find old namelist
     1002 10    REWIND ( 11 )
     1003       line = ' '
     1004       DO   WHILE ( INDEX( line, '&canopy_par' ) == 0 )
     1005          READ ( 11, '(A)', END=12 )  line
     1006       ENDDO
     1007       BACKSPACE ( 11 )
     1008
     1009!
     1010!--    Read user-defined namelist
     1011       READ ( 11, canopy_par )
     1012
     1013       message_string = 'namelist canopy_par is deprecated and will be ' // &
     1014                     'removed in near future. Please &use namelist ' //     &
     1015                     'plant_canopy_parameters instead'
     1016       CALL message( 'pcm_parin', 'PA0487', 0, 1, 0, 6, 0 )
     1017       
     1018!
     1019!--    Set flag that indicates that the radiation model is switched on
     1020       plant_canopy = .TRUE.
     1021
     1022 12    CONTINUE
    9871023       
    9881024
  • palm/trunk/SOURCE/pmc_handle_communicator_mod.f90

    r2841 r2932  
    2525! -----------------
    2626! $Id$
     27! nestpar renamed to nesting_parameters
     28!
     29! 2841 2018-02-27 15:02:57Z knoop
    2730! Bugfix: wrong placement of include 'mpif.h' corrected
    2831!
     
    146149
    147150    INTEGER, PARAMETER, PUBLIC ::  pmc_error_npes        = 1  !< illegal number of processes
    148     INTEGER, PARAMETER, PUBLIC ::  pmc_namelist_error    = 2  !< error(s) in nestpar namelist
     151    INTEGER, PARAMETER, PUBLIC ::  pmc_namelist_error    = 2  !< error(s) in nesting_parameters namelist
    149152    INTEGER, PARAMETER, PUBLIC ::  pmc_no_namelist_found = 3  !< no couple layout namelist found
    150153
     
    152155    INTEGER ::  m_my_cpl_id   !< coupler id of this model
    153156    INTEGER ::  m_parent_id   !< coupler id of parent of this model
    154     INTEGER ::  m_ncpl        !< number of couplers given in nestpar namelist
     157    INTEGER ::  m_ncpl        !< number of couplers given in nesting_parameters namelist
    155158
    156159    TYPE(pmc_layout), PUBLIC, DIMENSION(pmc_max_models) ::  m_couplers  !< information of all couplers
     
    268271!--    comm2d have not yet been assigned at this point.
    269272       IF ( m_world_rank == 0 )  THEN
    270           message_string = 'errors in \$nestpar'
     273          message_string = 'errors in \$nesting_parameters'
    271274          CALL message( 'pmc_init_model', 'PA0223', 3, 2, 0, 6, 0 )
    272275       ENDIF
     
    484487    TYPE(pmc_layout), DIMENSION(pmc_max_models) ::  domain_layouts
    485488
    486     NAMELIST /nestpar/  domain_layouts, nesting_datatransfer_mode, nesting_mode
    487 
     489    NAMELIST /nesting_parameters/  domain_layouts, nesting_datatransfer_mode,  &
     490                                   nesting_mode
     491   
    488492!
    489493!-- Initialize some coupling variables
     
    495499!-- Open the NAMELIST-file and read the nesting layout
    496500    CALL check_open( 11 )
    497     READ ( 11, nestpar, IOSTAT=istat )
     501    READ ( 11, nesting_parameters, IOSTAT=istat )
    498502!
    499503!-- Set filepointer to the beginning of the file. Otherwise process 0 will later
     
    503507    IF ( istat < 0 )  THEN
    504508!
    505 !--    No nestpar-NAMELIST found
     509!--    No nesting_parameters-NAMELIST found
    506510       pmc_status = pmc_no_namelist_found
    507511       RETURN
    508512    ELSEIF ( istat > 0 )  THEN
    509513!
    510 !--    Errors in reading nestpar-NAMELIST
     514!--    Errors in reading nesting_parameters-NAMELIST
    511515       pmc_status = pmc_namelist_error
    512516       RETURN
     
    519523    m_couplers = domain_layouts
    520524!
    521 !-- Get the number of nested models given in the nestpar-NAMELIST
     525!-- Get the number of nested models given in the nesting_parameters-NAMELIST
    522526    DO  i = 1, pmc_max_models
    523527!
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r2930 r2932  
    2828! -----------------
    2929! $Id$
     30! renamed radiation_par to radiation_parameters
     31!
     32! 2930 2018-03-23 16:30:46Z suehring
    3033! Remove default surfaces from radiation model, does not make much sense to
    3134! apply radiation model without energy-balance solvers; Further, add check for
     
    25712574! Description:
    25722575! ------------
    2573 !> Parin for &radiation_par for radiation model
     2576!> Parin for &radiation_parameters for radiation model
    25742577!------------------------------------------------------------------------------!
    25752578    SUBROUTINE radiation_parin
     
    25922595                                  average_radiation,                           &
    25932596                                  surf_reflections, svfnorm_report_thresh
    2594        
     2597   
     2598       NAMELIST /radiation_parameters/   albedo, albedo_type, albedo_lw_dir,   &
     2599                                  albedo_lw_dif, albedo_sw_dir, albedo_sw_dif, &
     2600                                  constant_albedo, dt_radiation, emissivity,   &
     2601                                  lw_radiation, net_radiation,                 &
     2602                                  radiation_scheme, skip_time_do_radiation,    &
     2603                                  sw_radiation, unscheduled_radiation_calls,   &
     2604                                  split_diffusion_radiation,                   &
     2605                                  max_raytracing_dist, min_irrf_value,         &
     2606                                  nrefsteps, mrt_factors, rma_lad_raytrace,    &
     2607                                  dist_max_svf,                                &
     2608                                  average_radiation,                           &
     2609                                  surf_reflections, svfnorm_report_thresh
     2610   
    25952611       line = ' '
    25962612       
    25972613!
    2598 !--    Try to find radiation model package
     2614!--    Try to find radiation model namelist
    25992615       REWIND ( 11 )
    26002616       line = ' '
    2601        DO   WHILE ( INDEX( line, '&radiation_par' ) == 0 )
     2617       DO   WHILE ( INDEX( line, '&radiation_parameters' ) == 0 )
    26022618          READ ( 11, '(A)', END=10 )  line
    26032619       ENDDO
     
    26062622!
    26072623!--    Read user-defined namelist
    2608        READ ( 11, radiation_par )
     2624       READ ( 11, radiation_parameters )
    26092625
    26102626!
    26112627!--    Set flag that indicates that the radiation model is switched on
    26122628       radiation = .TRUE.
     2629       
     2630       GOTO 12
     2631!
     2632!--    Try to find old namelist
     2633 10    REWIND ( 11 )
     2634       line = ' '
     2635       DO   WHILE ( INDEX( line, '&radiation_par' ) == 0 )
     2636          READ ( 11, '(A)', END=12 )  line
     2637       ENDDO
     2638       BACKSPACE ( 11 )
     2639
     2640!
     2641!--    Read user-defined namelist
     2642       READ ( 11, radiation_par )
     2643       
     2644       message_string = 'namelist radiation_par is deprecated and will be ' // &
     2645                     'removed in near future. Please &use namelist ' //        &
     2646                     'radiation_parameters instead'
     2647       CALL message( 'radiation_parin', 'PA0487', 0, 1, 0, 6, 0 )
     2648
     2649       
     2650!
     2651!--    Set flag that indicates that the radiation model is switched on
     2652       radiation = .TRUE.
     2653
     2654 12    CONTINUE
     2655       
     2656
    26132657
    26142658!--    Set radiation_interactions flag according to urban_ and land_surface flag
    2615        IF ( urban_surface  .OR.  land_surface ) radiation_interactions = .TRUE.
    2616 
    2617  10    CONTINUE
     2659       IF ( urban_surface  .OR.  land_surface )  radiation_interactions = .TRUE.
    26182660       
    2619 
    26202661    END SUBROUTINE radiation_parin
    26212662
     
    54515492               CASE DEFAULT
    54525493                  WRITE(message_string, *) 'ERROR: the surface type ',td , ' is not supported for calculating SVF'
    5453                   CALL message( 'radiation_calc_svf', 'PA0XXX', 1, 2, 0, 6, 0 )
     5494                  CALL message( 'radiation_calc_svf', 'PA0488', 1, 2, 0, 6, 0 )
    54545495            END SELECT
    54555496
  • palm/trunk/SOURCE/spectra_mod.f90

    r2841 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed spectra_par to spectra_parameters
     28!
     29! 2841 2018-02-27 15:02:57Z knoop
    2730! Bugfix: wrong placement of include 'mpif.h' corrected
    2831!
     
    195198
    196199       USE control_parameters,                                                 &
    197            ONLY:  dt_data_output
     200           ONLY:  dt_data_output, message_string
    198201
    199202       IMPLICIT NONE
     
    206209                               spectra_direction
    207210
    208 
     211       NAMELIST /spectra_parameters/                                           &
     212                               averaging_interval_sp, comp_spectra_level,      &
     213                               data_output_sp, dt_dosp, skip_time_dosp,        &
     214                               spectra_direction
    209215!
    210216!--    Position the namelist-file at the beginning (it was already opened in
     
    217223       REWIND ( 11 )
    218224       line = ' '
    219        DO   WHILE ( INDEX( line, '&spectra_par' ) == 0 )
     225       DO   WHILE ( INDEX( line, '&spectra_parameters' ) == 0 )
    220226          READ ( 11, '(A)', END=10 )  line
    221227       ENDDO
     
    224230!
    225231!--    Read namelist
    226        READ ( 11, spectra_par )
     232       READ ( 11, spectra_parameters )
    227233
    228234!
     
    235241       calculate_spectra = .TRUE.
    236242
    237  10    CONTINUE
     243       GOTO 12
     244!
     245!--    Try to find the old namelist
     246 10    REWIND ( 11 )
     247       line = ' '
     248       DO   WHILE ( INDEX( line, '&spectra_par' ) == 0 )
     249          READ ( 11, '(A)', END=12 )  line
     250       ENDDO
     251       BACKSPACE ( 11 )
     252
     253!
     254!--    Read namelist
     255       READ ( 11, spectra_par )
     256
     257       
     258       message_string = 'namelist spectra_par is deprecated and will be ' // &
     259                     'removed in near future. Please &use namelist ' //      &
     260                     'spectra_parameters instead'
     261       CALL message( 'spectra_parin', 'PA0487', 0, 1, 0, 6, 0 )
     262!
     263!--    Default setting of dt_dosp here (instead of check_parameters), because
     264!--    its current value is needed in init_pegrid
     265       IF ( dt_dosp == 9999999.9_wp )  dt_dosp = dt_data_output
     266
     267!
     268!--    Set general switch that spectra shall be calculated
     269       calculate_spectra = .TRUE.
     270       
     271       
     272 12    CONTINUE
    238273
    239274    END SUBROUTINE spectra_parin
  • palm/trunk/SOURCE/urban_surface_mod.f90

    r2921 r2932  
    2828! -----------------
    2929! $Id$
     30! renamed urban_surface_par to urban_surface_parameters
     31!
     32! 2921 2018-03-22 15:05:23Z Giersch
    3033! The activation of spinup has been moved to parin
    3134!
     
    51645167                           window_inner_temperature
    51655168
     5169       NAMELIST /urban_surface_parameters/                                     &
     5170                           building_type,                                      &
     5171                           land_category,                                      &
     5172                           naheatlayers,                                       &
     5173                           pedestrian_category,                                &
     5174                           roughness_concrete,                                 &
     5175                           read_wall_temp_3d,                                  &
     5176                           roof_category,                                      &
     5177                           urban_surface,                                      &
     5178                           usm_anthropogenic_heat,                             &
     5179                           usm_material_model,                                 &
     5180                           wall_category,                                      &
     5181                           indoor_model,                                       &
     5182                           wall_inner_temperature,                             &
     5183                           roof_inner_temperature,                             &
     5184                           soil_inner_temperature,                             &
     5185                           window_inner_temperature
    51665186!
    51675187!--    Try to find urban surface model package
    51685188       REWIND ( 11 )
    51695189       line = ' '
    5170        DO   WHILE ( INDEX( line, '&urban_surface_par' ) == 0 )
     5190       DO   WHILE ( INDEX( line, '&urban_surface_parameters' ) == 0 )
    51715191          READ ( 11, '(A)', END=10 )  line
    51725192       ENDDO
     
    51755195!
    51765196!--    Read user-defined namelist
    5177        READ ( 11, urban_surface_par )
     5197       READ ( 11, urban_surface_parameters )
    51785198!
    51795199!--    Set flag that indicates that the land surface model is switched on
    51805200       urban_surface = .TRUE.
    51815201
    5182 
    5183  10    CONTINUE
     5202       GOTO 12
     5203!
     5204!--    Try to find old namelist
     5205 10    REWIND ( 11 )
     5206       line = ' '
     5207       DO   WHILE ( INDEX( line, '&urban_surface_par' ) == 0 )
     5208          READ ( 11, '(A)', END=12 )  line
     5209       ENDDO
     5210       BACKSPACE ( 11 )
     5211
     5212!
     5213!--    Read user-defined namelist
     5214       READ ( 11, urban_surface_par )
     5215
     5216       message_string = 'namelist urban_surface_par is deprecated and will be ' // &
     5217                     'removed in near future. Please &use namelist ' //            &
     5218                     'urban_surface_parameters instead'
     5219       CALL message( 'usm_parin', 'PA0487', 0, 1, 0, 6, 0 )
     5220!
     5221!--    Set flag that indicates that the land surface model is switched on
     5222       urban_surface = .TRUE.
     5223
     5224 12    CONTINUE
    51845225
    51855226
  • palm/trunk/SOURCE/user_parin.f90

    r2718 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed userpar to user_parameters
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    9699    IMPLICIT NONE
    97100
    98     CHARACTER (LEN=80) ::  zeile   !<
     101    CHARACTER (LEN=80) ::  line   !<
    99102
    100103    INTEGER(iwp) ::  i                 !<
     
    104107
    105108    NAMELIST /userpar/  data_output_pr_user, data_output_user, region,         &
     109                        data_output_masks_user
     110                       
     111                       
     112    NAMELIST /user_parameters/  data_output_pr_user, data_output_user, region, &
    106113                        data_output_masks_user
    107114
     
    119126    REWIND ( 11 )
    120127
    121     zeile = ' '
    122     DO   WHILE ( INDEX( zeile, '&userpar' ) == 0 )
    123        READ ( 11, '(A)', END=100 )  zeile
     128    line = ' '
     129    DO   WHILE ( INDEX( line, '&user_parameters' ) == 0 )
     130       READ ( 11, '(A)', END=10 )  line
    124131    ENDDO
    125132    BACKSPACE ( 11 )
     
    128135!-- Read user-defined namelist
    129136    READ ( 11, userpar )
     137
    130138    user_defined_namelist_found = .TRUE.
     139
     140    GOTO 12
     141   
     142   
     14310  REWIND ( 11 )
     144
     145    line = ' '
     146    DO   WHILE ( INDEX( line, '&userpar' ) == 0 )
     147       READ ( 11, '(A)', END=12 )  line
     148    ENDDO
     149    BACKSPACE ( 11 )
     150
     151!
     152!-- Read user-defined namelist
     153    READ ( 11, userpar )
     154   
     155   
     156    message_string = 'namelist userpar is deprecated and will be ' //          &
     157                     'removed in near future. Please &use namelist ' //        &
     158                     'user_parameters instead'
     159    CALL message( 'user_parin', 'PA0487', 0, 1, 0, 6, 0 )
     160       
     161    user_defined_namelist_found = .TRUE.
     162   
     163   
     164 12 CONTINUE
    131165
    132166!
    133167!-- Determine the number of user-defined profiles and append them to the
    134168!-- standard data output (data_output_pr)
    135     max_pr_user_tmp = 0
    136     IF ( data_output_pr_user(1) /= ' ' )  THEN
    137        i = 1
    138        DO  WHILE ( data_output_pr(i) /= ' '  .AND.  i <= 100 )
    139           i = i + 1
    140        ENDDO
    141        j = 1
    142        DO  WHILE ( data_output_pr_user(j) /= ' '  .AND.  j <= 100 )
    143           data_output_pr(i) = data_output_pr_user(j)
    144           max_pr_user_tmp   = max_pr_user_tmp + 1
    145           i = i + 1
    146           j = j + 1
    147        ENDDO
    148     ENDIF
    149 
    150 !
    151 !-- In case of a restart run, the number of user-defined profiles on the
    152 !-- restart file (already stored in max_pr_user) has to match the one given
    153 !-- for the current run
    154     IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
    155        IF ( max_pr_user /= max_pr_user_tmp )  THEN
    156           WRITE( message_string, * ) 'the number of user-defined profiles ',   &
     169    IF ( user_defined_namelist_found )  THEN
     170       max_pr_user_tmp = 0
     171       IF ( data_output_pr_user(1) /= ' ' )  THEN
     172          i = 1
     173          DO  WHILE ( data_output_pr(i) /= ' '  .AND.  i <= 100 )
     174             i = i + 1
     175          ENDDO
     176          j = 1
     177          DO  WHILE ( data_output_pr_user(j) /= ' '  .AND.  j <= 100 )
     178             data_output_pr(i) = data_output_pr_user(j)
     179             max_pr_user_tmp   = max_pr_user_tmp + 1
     180             i = i + 1
     181             j = j + 1
     182          ENDDO
     183      ENDIF
     184
     185
     186!
     187!--    In case of a restart run, the number of user-defined profiles on the
     188!--    restart file (already stored in max_pr_user) has to match the one given
     189!--    for the current run
     190       IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
     191          IF ( max_pr_user /= max_pr_user_tmp )  THEN
     192             WRITE( message_string, * ) 'the number of user-defined profiles ',&
    157193                     'given in &data_output_pr (', max_pr_user_tmp, ') doe',   &
    158194                     'snot match the one ',                                    &
    159195                     '&found in the restart file (', max_pr_user,              &
    160196                                     ')'
    161           CALL message( 'user_parin', 'UI0009', 1, 2, 0, 6, 0 )
     197             CALL message( 'user_parin', 'UI0009', 1, 2, 0, 6, 0 )
     198          ENDIF
     199       ELSE
     200          max_pr_user = max_pr_user_tmp
    162201       ENDIF
    163     ELSE
    164        max_pr_user = max_pr_user_tmp
     202
    165203    ENDIF
    166 
    167 100 RETURN
     204 
     205    RETURN
    168206
    169207 END SUBROUTINE user_parin
  • palm/trunk/SOURCE/uv_exposure_model_mod.f90

    r2894 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed uvexposure_par to biometeorology_parameters
     28!
     29! 2894 2018-03-15 09:17:58Z Giersch
    2730! Routine for skipping global restart data has been removed, uvem_last_actions
    2831! has been renamed to uvem_wrd_global and uvem_read_restart_data has been
     
    425428    CHARACTER (LEN=80) ::  line  !< dummy string for current line in parameter file
    426429   
    427     NAMELIST /uvexposure_par/  clothing
     430    NAMELIST /biometeorology_parameters/  clothing
    428431   
    429432    line = ' '
     
    433436    REWIND ( 11 )
    434437    line = ' '
    435     DO   WHILE ( INDEX( line, '&uvexposure_par' ) == 0 )
     438    DO   WHILE ( INDEX( line, '&biometerology_parameters' ) == 0 )
    436439       READ ( 11, '(A)', END=10 )  line
    437440    ENDDO
     
    440443!
    441444!-- Read user-defined namelist
    442     READ ( 11, uvexposure_par )
     445    READ ( 11, biometeorology_parameters )
    443446
    444447!
  • palm/trunk/SOURCE/virtual_flight_mod.f90

    r2894 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed flight_par to virtual_flight_parameters
     28!
     29! 2894 2018-03-15 09:17:58Z Giersch
    2730! variable named found has been introduced for checking if restart data was
    2831! found, reading of restart strings has been moved completely to
     
    218221
    219222       USE control_parameters,                                                 &
    220            ONLY:  initializing_actions 
     223           ONLY:  initializing_actions, message_string 
    221224     
    222225       IMPLICIT NONE
     
    227230                              flight_level, max_elev_change, rate_of_climb,    &
    228231                              speed_agl, x_end, x_start, y_end, y_start
    229                              
     232 
     233
     234       NAMELIST /virtual_flight_parameters/                                    &
     235                              flight_angle, flight_end, flight_begin, leg_mode,&
     236                              flight_level, max_elev_change, rate_of_climb,    &
     237                              speed_agl, x_end, x_start, y_end, y_start
    230238!
    231239!--    Try to find the namelist flight_par
    232240       REWIND ( 11 )
    233241       line = ' '
    234        DO   WHILE ( INDEX( line, '&flight_par' ) == 0 )
     242       DO   WHILE ( INDEX( line, '&virtual_flight_parameters' ) == 0 )
    235243          READ ( 11, '(A)', END=10 )  line
    236244       ENDDO
     
    239247!
    240248!--    Read namelist
    241        READ ( 11, flight_par )
     249       READ ( 11, virtual_flight_parameters )
    242250!
    243251!--    Set switch that virtual flights shall be carried out
    244252       virtual_flight = .TRUE.
    245253
    246 
    247  10    CONTINUE
     254       GOTO 12
     255!
     256!--    Try to find the old namelist
     257 10    REWIND ( 11 )
     258       line = ' '
     259       DO   WHILE ( INDEX( line, '&flight_par' ) == 0 )
     260          READ ( 11, '(A)', END=12 )  line
     261       ENDDO
     262       BACKSPACE ( 11 )
     263
     264!
     265!--    Read namelist
     266       READ ( 11, flight_par )
     267       
     268       message_string = 'namelist flight_par is deprecated and will be ' // &
     269                     'removed in near future. Please &use namelist ' //     &
     270                     'virtual_flight_parameters instead'
     271       CALL message( 'flight_parin', 'PA0487', 0, 1, 0, 6, 0 )     
     272!
     273!--    Set switch that virtual flights shall be carried out
     274       virtual_flight = .TRUE.
     275
     276 12    CONTINUE
    248277
    249278    END SUBROUTINE flight_parin
  • palm/trunk/SOURCE/wind_turbine_model_mod.f90

    r2894 r2932  
    2626! -----------------
    2727! $Id$
     28! renamed wind_turbine_par to wind_turbine_parameters
     29!
     30! 2894 2018-03-15 09:17:58Z Giersch
    2831! variable named found has been introduced for checking if restart data was
    2932! found, reading of restart strings has been moved completely to
     
    493496                                  turb_cd_nacelle, turb_cd_tower, pitch_rate,  &
    494497                                  yaw_control, yaw_speed, tl_cor
    495 
     498                                 
     499       NAMELIST /wind_turbine_parameters/                                      &
     500                                  air_dens, dtow, gear_eff, gear_ratio,        &
     501                                  gen_eff, inertia_gen, inertia_rot, max_miss, &
     502                                  max_torque_gen, max_trq_rate, min_miss,      &
     503                                  min_reg15, min_reg2, nairfoils, nturbines,   &
     504                                  omega_rot, phi_yaw, pitch_add, pitch_control,&
     505                                  rated_genspeed, rated_power, rcx, rcy, rcz,  &
     506                                  rnac, rr, segment_length, segment_width,     &
     507                                  slope2, speed_control, tilt, time_turbine_on,&
     508                                  turb_cd_nacelle, turb_cd_tower, pitch_rate,  &
     509                                  yaw_control, yaw_speed, tl_cor
    496510!
    497511!--    Try to find wind turbine model package
    498512       REWIND ( 11 )
    499513       line = ' '
     514       DO  WHILE ( INDEX( line, '&wind_turbine_parameters' ) == 0 )
     515          READ ( 11, '(A)', END=10 )  line
     516       ENDDO
     517       BACKSPACE ( 11 )
     518
     519!
     520!--    Read user-defined namelist
     521       READ ( 11, wind_turbine_parameters, IOSTAT=ierrn )
     522
     523       IF ( ierrn < 0 )  THEN
     524          message_string = 'no wind_turbine_parameters-NAMELIST found: '  //    &
     525                           'End of file has reached'
     526          CALL message( 'wtm_parin', 'PA0460', 1, 2, 0, 6, 0 )
     527       ELSEIF ( ierrn > 0 ) THEN
     528          message_string = 'errors in wind_turbine_parameters-NAMELIST: '  //   &
     529                           'some variables for steering may not be properly set'
     530          CALL message( 'wtm_parin', 'PA0466', 1, 2, 0, 6, 0 )               
     531       ENDIF
     532       
     533!
     534!--    Set flag that indicates that the wind turbine model is switched on
     535       wind_turbine = .TRUE.
     536       
     537       GOTO 12
     538
     539!
     540!--    Try to find wind turbine model package
     541 10    REWIND ( 11 )
     542       line = ' '
    500543       DO  WHILE ( INDEX( line, '&wind_turbine_par' ) == 0 )
    501           READ ( 11, '(A)', END=10 )  line
     544          READ ( 11, '(A)', END=12 )  line
    502545       ENDDO
    503546       BACKSPACE ( 11 )
     
    512555          CALL message( 'wtm_parin', 'PA0460', 1, 2, 0, 6, 0 )
    513556       ELSEIF ( ierrn > 0 ) THEN
    514           message_string = 'errors in wind_turbine_par-NAMELIST: '  //          &
     557          message_string = 'errors in wind_turbine_par-NAMELIST: '  //         &
    515558                           'some variables for steering may not be properly set'
    516559          CALL message( 'wtm_parin', 'PA0466', 1, 2, 0, 6, 0 )               
    517560       ENDIF
    518        
     561     
     562       message_string = 'namelist wind_tubrine_par is deprecated and will ' // &
     563                        'be removed in near future. Please &use namelist ' //  &
     564                        'wind_turbine_parameters instead'
     565       CALL message( 'wtm_parin', 'PA0487', 0, 1, 0, 6, 0 )     
     566     
    519567!
    520568!--    Set flag that indicates that the wind turbine model is switched on
    521569       wind_turbine = .TRUE.
    522570
    523 
    524  10    CONTINUE   ! TBD Change from continue, mit ierrn machen
     571 12    CONTINUE   ! TBD Change from continue, mit ierrn machen
    525572
    526573
Note: See TracChangeset for help on using the changeset viewer.