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/ocean_mod.f90

    r4495 r4517  
    2525! -----------------
    2626! $Id$
     27! added restart with MPI-IO for reading local arrays
     28!
     29! 4495 2020-04-13 20:11:20Z raasch
    2730! restart data handling with MPI-IO added
    2831!
     
    102105
    103106    USE restart_data_mpi_io_mod,                                                                   &
    104         ONLY:  rrd_mpi_io, rrd_mpi_io_global_array, wrd_mpi_io, wrd_mpi_io_global_array
     107        ONLY:  rd_mpi_io_check_array, rrd_mpi_io, rrd_mpi_io_global_array, wrd_mpi_io,             &
     108               wrd_mpi_io_global_array
    105109
    106110    USE surface_mod,                                                           &
     
    232236
    233237    INTERFACE ocean_rrd_local
    234        MODULE PROCEDURE ocean_rrd_local
     238       MODULE PROCEDURE ocean_rrd_local_ftn
     239       MODULE PROCEDURE ocean_rrd_local_mpi
    235240    END INTERFACE ocean_rrd_local
    236241
     
    20392044! Description:
    20402045! ------------
    2041 !> This routine reads the respective restart data for the ocean module.
    2042 !------------------------------------------------------------------------------!
    2043  SUBROUTINE ocean_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,           &
    2044                              nxr_on_file, nynf, nync, nyn_on_file, nysf,       &
    2045                              nysc, nys_on_file, tmp_3d, found )
     2046!> Read module-specific local restart data arrays (Fortran binary format).
     2047!------------------------------------------------------------------------------!
     2048 SUBROUTINE ocean_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,           &
     2049                                 nxr_on_file, nynf, nync, nyn_on_file, nysf,       &
     2050                                 nysc, nys_on_file, tmp_3d, found )
    20462051
    20472052    USE averaging,                                                             &
     
    21082113    END SELECT
    21092114
    2110  END SUBROUTINE ocean_rrd_local
     2115 END SUBROUTINE ocean_rrd_local_ftn
     2116
     2117
     2118!------------------------------------------------------------------------------!
     2119! Description:
     2120! ------------
     2121!> Read module-specific local restart data arrays (MPI-IO).
     2122!------------------------------------------------------------------------------!
     2123 SUBROUTINE ocean_rrd_local_mpi
     2124
     2125    USE averaging,                                                             &
     2126        ONLY:  rho_ocean_av, sa_av
     2127
     2128    USE indices,                                                               &
     2129        ONLY:  nxlg, nxrg, nyng, nysg, nzb, nzt
     2130
     2131    IMPLICIT NONE
     2132
     2133    LOGICAL ::  array_found  !<
     2134
     2135
     2136    CALL rd_mpi_io_check_array( 'rho_ocean_av' , found = array_found )
     2137    IF ( array_found )  THEN
     2138       IF ( .NOT. ALLOCATED( rho_ocean_av ) )  ALLOCATE( rho_ocean_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     2139       CALL rrd_mpi_io( 'rho_ocean_av', rho_ocean_av )
     2140    ENDIF
     2141
     2142    CALL rrd_mpi_io( 'sa', sa )
     2143
     2144    CALL rd_mpi_io_check_array( 'sa_av' , found = array_found )
     2145    IF ( array_found )  THEN
     2146       IF ( .NOT. ALLOCATED( sa_av ) )  ALLOCATE( sa_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     2147       CALL rrd_mpi_io( 'sa_av', sa_av )
     2148    ENDIF
     2149
     2150 END SUBROUTINE ocean_rrd_local_mpi
    21112151
    21122152
Note: See TracChangeset for help on using the changeset viewer.