Ignore:
Timestamp:
May 3, 2020 2:29:30 PM (4 years ago)
Author:
raasch
Message:

added restart with MPI-IO for reading local arrays

File:
1 edited

Legend:

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

    r4504 r4517  
    2121! -----------------
    2222!
    23 !
     23! 
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! added restart with MPI-IO for reading local arrays
     28!
     29! 4504 2020-04-20 12:11:24Z raasch
    2730! hint for setting rmask arrays added
    2831!
     
    207210
    208211    INTERFACE user_rrd_local
    209        MODULE PROCEDURE user_rrd_local
     212       MODULE PROCEDURE user_rrd_local_ftn
     213       MODULE PROCEDURE user_rrd_local_mpi
    210214    END INTERFACE user_rrd_local
    211215
     
    11301134 SUBROUTINE user_rrd_global_mpi
    11311135
     1136!    USE restart_data_mpi_io_mod,                                                                   &
     1137!        ONLY:  rrd_mpi_io
     1138
    11321139!    CALL rrd_mpi_io( 'global_parameter', global_parameter )
    11331140    CONTINUE
     
    11391146! Description:
    11401147! ------------
    1141 !> Reading processor specific restart data from file(s) that has been defined by the user. Subdomain
     1148!> Read module-specific local restart data arrays (Fortran binary format).
     1149!> Subdomain
    11421150!> index limits on file are given by nxl_on_file, etc. Indices nxlc, etc. indicate the range of
    11431151!> gridpoints to be mapped from the subdomain on file (f) to the subdomain of the current PE (c).
    11441152!> They have been calculated in routine rrd_local.
    11451153!--------------------------------------------------------------------------------------------------!
    1146  SUBROUTINE user_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,       &
    1147                             nyn_on_file, nysf, nysc, nys_on_file, tmp_3d, found )
     1154 SUBROUTINE user_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,   &
     1155                                nyn_on_file, nysf, nysc, nys_on_file, tmp_3d, found )
    11481156
    11491157
     
    11941202    END SELECT
    11951203
    1196  END SUBROUTINE user_rrd_local
     1204 END SUBROUTINE user_rrd_local_ftn
     1205
     1206
     1207!--------------------------------------------------------------------------------------------------!
     1208! Description:
     1209! ------------
     1210!> Read module-specific local restart data arrays (MPI-IO).
     1211!--------------------------------------------------------------------------------------------------!
     1212 SUBROUTINE user_rrd_local_mpi
     1213
     1214!    USE restart_data_mpi_io_mod,                                                                   &
     1215!        ONLY:  rd_mpi_io_check_array, rrd_mpi_io
     1216
     1217!    CALL rd_mpi_io_check_array( 'u2_av' , found = array_found )
     1218!    IF ( array_found )  THEN
     1219!       IF ( .NOT. ALLOCATED( u2_av ) )  ALLOCATE( u2_av(nysg:nyng,nxlg:nxrg) )
     1220!       CALL rrd_mpi_io( 'rad_u2_av', rad_u2_av )
     1221!    ENDIF
     1222
     1223    CONTINUE
     1224
     1225 END SUBROUTINE user_rrd_local_mpi
    11971226
    11981227
     
    12031232!--------------------------------------------------------------------------------------------------!
    12041233 SUBROUTINE user_wrd_global
     1234
     1235!    USE restart_data_mpi_io_mod,                                                                   &
     1236!        ONLY:  wrd_mpi_io
    12051237
    12061238    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     
    12241256!--------------------------------------------------------------------------------------------------!
    12251257 SUBROUTINE user_wrd_local
     1258
     1259!    USE restart_data_mpi_io_mod,                                                                   &
     1260!        ONLY:  wrd_mpi_io
    12261261
    12271262!
Note: See TracChangeset for help on using the changeset viewer.