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

renamed all Fortran NAMELISTS

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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!
Note: See TracChangeset for help on using the changeset viewer.