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

    r4502 r4517  
    2525! -----------------
    2626! $Id$
     27! added restart with MPI-IO for reading local arrays
     28!
     29! 4502 2020-04-17 16:14:16Z schwenkel
    2730! Implementation of ice microphysics
    2831!
     
    147150
    148151   USE restart_data_mpi_io_mod,                                                                    &
    149        ONLY:  rrd_mpi_io, wrd_mpi_io
     152       ONLY:  rd_mpi_io_check_array, rrd_mpi_io, wrd_mpi_io
    150153
    151154   USE surface_mod,                                                                                &
     
    267270
    268271   INTERFACE  surface_data_output_rrd_local
    269       MODULE PROCEDURE surface_data_output_rrd_local
     272      MODULE PROCEDURE surface_data_output_rrd_local_ftn
     273      MODULE PROCEDURE surface_data_output_rrd_local_mpi
    270274   END INTERFACE  surface_data_output_rrd_local
    271275
     
    48834887! Description:
    48844888! ------------
    4885 !> This routine reads the respective restart data.
     4889!> Read module-specific local restart data arrays (Fortran binary format).
    48864890!------------------------------------------------------------------------------!
    4887     SUBROUTINE surface_data_output_rrd_local( found )
     4891    SUBROUTINE surface_data_output_rrd_local_ftn( found )
    48884892
    48894893
     
    48954899       LOGICAL, INTENT(OUT)  ::  found
    48964900
    4897 !
    4898 !--    Here the reading of user-defined restart data follows:
    4899 !--    Sample for user-defined output
     4901
    49004902       found = .TRUE.
    49014903
     
    49124914
    49134915
    4914     END SUBROUTINE surface_data_output_rrd_local
     4916    END SUBROUTINE surface_data_output_rrd_local_ftn
     4917
     4918
     4919!------------------------------------------------------------------------------!
     4920! Description:
     4921! ------------
     4922!> Read module-specific local restart data arrays (MPI-IO).
     4923!------------------------------------------------------------------------------!
     4924    SUBROUTINE surface_data_output_rrd_local_mpi
     4925
     4926       IMPLICIT NONE
     4927
     4928       LOGICAL ::  array_found  !<
     4929
     4930
     4931       CALL rd_mpi_io_check_array( 'surfaces%var_av' , found = array_found )
     4932
     4933!> does not work this way: surface%var_av has non-standard dimensions
     4934!       IF ( array_found )  THEN
     4935!          IF ( .NOT. ALLOCATED( surfaces%var_av ) )  ALLOCATE( ....... )
     4936!          CALL rrd_mpi_io( 'surfaces%var_av', surfaces%var_av )
     4937!       ENDIF
     4938
     4939    END SUBROUTINE surface_data_output_rrd_local_mpi
     4940
    49154941
    49164942!------------------------------------------------------------------------------!
     
    49364962    END SUBROUTINE surface_data_output_wrd_global
    49374963
     4964
    49384965!------------------------------------------------------------------------------!
    49394966! Description:
Note: See TracChangeset for help on using the changeset viewer.