Ignore:
Timestamp:
Apr 13, 2020 8:11:20 PM (4 years ago)
Author:
raasch
Message:

restart data handling with MPI-IO added, first part

File:
1 edited

Legend:

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

    r4360 r4495  
    2525! -----------------
    2626! $Id$
     27! restart data handling with MPI-IO added
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Introduction of wall_flags_total_0, which currently sets bits based on static
    2831! topography information used in wall_flags_static_0
     
    193196
    194197    INTERFACE user_rrd_global
    195        MODULE PROCEDURE user_rrd_global
     198       MODULE PROCEDURE user_rrd_global_ftn
     199       MODULE PROCEDURE user_rrd_global_mpi
    196200    END INTERFACE user_rrd_global
    197201
     
    247251!-- current revision does not match with previous revisions (e.g. if routines
    248252!-- have been added/deleted or if parameter lists in subroutines have been changed).
    249     user_interface_current_revision = 'r3703'
     253    user_interface_current_revision = 'r4495'
    250254
    251255!
     
    11061110! Description:
    11071111! ------------
    1108 !> Reading global restart data that has been defined by the user.
    1109 !------------------------------------------------------------------------------!
    1110  SUBROUTINE user_rrd_global( found )
     1112!> Read module-specific global restart data (Fortran binary format).
     1113!------------------------------------------------------------------------------!
     1114 SUBROUTINE user_rrd_global_ftn( found )
    11111115
    11121116
     
    11291133
    11301134
    1131  END SUBROUTINE user_rrd_global
     1135 END SUBROUTINE user_rrd_global_ftn
     1136
     1137
     1138!------------------------------------------------------------------------------!
     1139! Description:
     1140! ------------
     1141!> Read module-specific global restart data (MPI-IO).
     1142!------------------------------------------------------------------------------!
     1143 SUBROUTINE user_rrd_global_mpi
     1144
     1145!    CALL rrd_mpi_io( 'global_parameter', global_parameter )
     1146    CONTINUE
     1147
     1148 END SUBROUTINE user_rrd_global_mpi
    11321149
    11331150
     
    12041221 SUBROUTINE user_wrd_global
    12051222
    1206 !    CALL wrd_write_string( 'global_parameter' )
    1207 !    WRITE ( 14 )  global_parameter
     1223    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     1224
     1225!       CALL wrd_write_string( 'global_parameter' )
     1226!       WRITE ( 14 )  global_parameter
     1227
     1228    ELSEIF ( TRIM( restart_data_format_output ) == 'mpi' )  THEN
     1229
     1230!    CALL rrd_mpi_io( 'global_parameter', global_parameter )
     1231
     1232    ENDIF
    12081233
    12091234 END SUBROUTINE user_wrd_global
     
    12211246!-- Here the user-defined actions at the end of a job follow.
    12221247!-- Sample for user-defined output:
    1223 !    IF ( ALLOCATED( u2_av ) )  THEN
    1224 !       CALL wrd_write_string( 'u2_av' )
    1225 !       WRITE ( 14 )  u2_av
    1226 !    ENDIF
     1248    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     1249
     1250!       IF ( ALLOCATED( u2_av ) )  THEN
     1251!          CALL wrd_write_string( 'u2_av' )
     1252!          WRITE ( 14 )  u2_av
     1253!       ENDIF
     1254
     1255    ELSEIF ( TRIM( restart_data_format_output ) == 'mpi' )  THEN
     1256
     1257!       IF ( ALLOCATED( u2_av ) )  CALL wrd_mpi_io( 'u2_av', u2_av )
     1258
     1259    ENDIF
    12271260
    12281261 END SUBROUTINE user_wrd_local
Note: See TracChangeset for help on using the changeset viewer.