Ignore:
Timestamp:
Jul 22, 2019 8:51:35 AM (5 years ago)
Author:
gronemeier
Message:

changes in data-output module (data_output_module.f90, data_output_binary_module.f90, data_output_netcdf4_module.f90, binary_to_netcdf.f90):

  • add support for different output groups of MPI ranks (required for, e.g., nesting runs)
  • revise output messages
File:
1 edited

Legend:

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

    r4106 r4107  
    136136
    137137   CHARACTER(LEN=charlen) ::  output_file_format = 'binary'  !< file format (namelist parameter)
     138   CHARACTER(LEN=charlen) ::  output_file_suffix = ''        !< file suffix added to each file name
    138139
    139140   CHARACTER(LEN=800) ::  internal_error_message = '' !< string containing the last error message
     
    142143   INTEGER(iwp) ::  debug_output_unit  !< Fortran Unit Number of the debug-output file
    143144   INTEGER(iwp) ::  nf                 !< number of files
     145   INTEGER      ::  master_rank = 0    !< master rank for tasks to be executed by single PE only
     146   INTEGER      ::  output_group_comm  !< MPI communicator addressing all MPI ranks which participate in output
    144147
    145148   INTEGER(iwp), PARAMETER ::  no_var_id = -1  !< value of var_id if no variable is selected
     
    223226!> Initialize data-output module
    224227!--------------------------------------------------------------------------------------------------!
    225 SUBROUTINE dom_init( program_debug_output_unit, debug_output )
    226 
    227    INTEGER(iwp), INTENT(IN) ::  program_debug_output_unit  !< file unit number for debug output
     228SUBROUTINE dom_init( file_suffix_of_output_group, mpi_comm_of_output_group, master_output_rank, &
     229                     program_debug_output_unit, debug_output )
     230
     231   CHARACTER(LEN=*), INTENT(IN), OPTIONAL ::  file_suffix_of_output_group  !< file-name suffix added to each file;
     232                                                                           !> must be unique for each output group
     233
     234   INTEGER, INTENT(IN), OPTIONAL ::  master_output_rank         !< MPI rank executing tasks which must
     235                                                                !> be executed by a single PE only
     236   INTEGER, INTENT(IN)           ::  mpi_comm_of_output_group   !< MPI communicator specifying the MPI group
     237                                                                !> which participate in the output
     238   INTEGER, INTENT(IN)           ::  program_debug_output_unit  !< file unit number for debug output
    228239
    229240   LOGICAL, INTENT(IN) ::  debug_output  !< if true, debug output is printed
    230241
    231242
     243   IF ( PRESENT( file_suffix_of_output_group ) )  output_file_suffix = file_suffix_of_output_group
     244   IF ( PRESENT( master_output_rank ) )  master_rank = master_output_rank
     245
     246   output_group_comm = mpi_comm_of_output_group
     247
    232248   debug_output_unit = program_debug_output_unit
    233 
    234249   print_debug_output = debug_output
    235250
    236    CALL binary_init_module( debug_output_unit, debug_output, no_var_id )
    237 
    238    CALL netcdf4_init_module( debug_output_unit, debug_output, no_var_id )
     251   CALL binary_init_module( output_file_suffix, output_group_comm, master_rank, &
     252                            debug_output_unit, debug_output, no_var_id )
     253
     254   CALL netcdf4_init_module( output_file_suffix, output_group_comm, master_rank, &
     255                            debug_output_unit, debug_output, no_var_id )
    239256
    240257END SUBROUTINE dom_init
Note: See TracChangeset for help on using the changeset viewer.