Ignore:
Timestamp:
Nov 9, 2020 1:40:05 PM (3 years ago)
Author:
raasch
Message:

first preliminary version for output of particle data time series

File:
1 edited

Legend:

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

    r4629 r4778  
    2525! -----------------
    2626! $Id$
     27! additions for output of particle time series
     28!
     29! 4629 2020-07-29 09:37:56Z raasch
    2730! support for MPI Fortran77 interface (mpif.h) removed
    2831!
     
    151154    TYPE, PUBLIC ::  sm_class  !<
    152155
    153        INTEGER(iwp) ::  nr_io_pe_per_node = 2         !< typical configuration, 2 sockets per node
     156       INTEGER(iwp) ::  nr_io_pe_per_node             !< typical configuration, 2 sockets per node
    154157       LOGICAL      ::  no_shared_Memory_in_this_run  !<
    155158
     
    185188          PROCEDURE, PASS(this), PUBLIC ::  sm_free_shared
    186189          PROCEDURE, PASS(this), PUBLIC ::  sm_init_comm
    187           PROCEDURE, PASS(this), PUBLIC ::  sm_init_part
     190          PROCEDURE, PASS(this), PUBLIC ::  sm_init_data_output_particles
    188191          PROCEDURE, PASS(this), PUBLIC ::  sm_node_barrier
    189192#if defined( __parallel )
     
    232235    LOGICAL, INTENT(IN) ::  sm_active  !< flag to activate shared-memory IO
    233236
     237    this%nr_io_pe_per_node = 2
     238
    234239    IF ( PRESENT( comm_input ) )  THEN
    235240       this%comm_model = comm_input
     
    414419
    415420!
    416 !-- TODO: short description required, about the meaning of the following routine
    417 !--       part must be renamed particles!
    418  SUBROUTINE sm_init_part( this )
     421!-- Initializing setup for output of particle time series.
     422!-- This output always uses a shared memory to reduce the number of particle transfers.
     423 SUBROUTINE sm_init_data_output_particles( this )
    419424
    420425    IMPLICIT NONE
     
    430435    LOGICAL :: sm_active  !<
    431436
     437
     438    this%nr_io_pe_per_node = 2
    432439
    433440    sm_active       = .TRUE.   ! particle IO always uses shared memory
     
    505512
    506513       WRITE( *, * ) 'shared_memory_io_mod: internal error'
    507        WRITE( *, * ) 'only 2 or 4 shared memory groups per node are allowed'
     514       WRITE( *, * ) 'only 1, 2 or 4 shared memory groups per node are allowed '
     515       WRITE( *, * ) 'here, ', this%nr_io_pe_per_node, ' groups have been set'
    508516       STOP
    509517
     
    540548#endif
    541549
    542 !    write(9,'(a,8i7)') 'sm_init_comm_part ',this%sh_rank,this%sh_npes,this%io_rank,this%io_npes
    543 
    544  END SUBROUTINE sm_init_part
     550 END SUBROUTINE sm_init_data_output_particles
    545551
    546552!--------------------------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.