Ignore:
Timestamp:
Apr 15, 2020 2:26:31 PM (4 years ago)
Author:
raasch
Message:

bugfix for creation of filetypes, argument removed from rd_mpi_io_open, files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4497 r4498  
    2424! -----------------
    2525! $Id$
     26! bugfix for creation of filetypes, argument removed from rd_mpi_io_open
     27!
     28! 4497 2020-04-15 10:20:51Z raasch
    2629! last bugfix deactivated because of compile problems
    2730!
     
    244247!> Open restart file for read or write with MPI-IO
    245248!--------------------------------------------------------------------------------------------------!
    246  SUBROUTINE rd_mpi_io_open( action, file_name, only_global )
     249 SUBROUTINE rd_mpi_io_open( action, file_name )
    247250
    248251    IMPLICIT NONE
     
    251254    CHARACTER(LEN=*), INTENT(IN)  ::  file_name                        !<
    252255
    253     LOGICAL, INTENT(IN), OPTIONAL ::  only_global                      !<
    254     LOGICAL                       ::  set_filetype                     !<
    255 
    256256    INTEGER(iwp)                  ::  i                                !<
    257257    INTEGER(iwp)                  ::  gh_size                          !<
     
    276276!-- Create subarrays and file types
    277277    filetypes_created = .FALSE.
    278     set_filetype      = .TRUE.
    279 
    280     IF ( PRESENT( only_global ) )  THEN
    281        IF ( only_global )  set_filetype = .FALSE.
    282     ENDIF
    283278
    284279!
    285280!-- In case of read it is not known yet if data include total domain. Filetypes will be created
    286281!-- further below.
    287     IF ( set_filetype  .AND.  wr_flag)  THEN
     282    IF ( wr_flag)  THEN
    288283       CALL rs_mpi_io_create_filetypes
    289284       filetypes_created = .TRUE.
     
    368363
    369364!
    370 !--    File types deoend on if boundaries of the total domain is included in data
    371        IF ( set_filetype )  THEN
    372           CALL rs_mpi_io_create_filetypes
    373           filetypes_created = .TRUE.
    374        ENDIF
     365!--    File types depend on if boundaries of the total domain is included in data. This has been
     366!--    checked with the previous statement.
     367       CALL rs_mpi_io_create_filetypes
     368       filetypes_created = .TRUE.
    375369
    376370#if defined( __parallel )
Note: See TracChangeset for help on using the changeset viewer.