Ignore:
Timestamp:
Apr 13, 2018 11:22:08 AM (6 years ago)
Author:
raasch
Message:

bugfix: missing parallel cpp-directives added

File:
1 edited

Legend:

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

    r2841 r2967  
    2525! -----------------
    2626! $Id$
     27! nesting routine is only called if nesting is switched on
     28! bugfix: missing parallel cpp-directives added
     29!
     30! 2841 2018-02-27 15:02:57Z knoop
    2731! Bugfix: wrong placement of include 'mpif.h' corrected,
    2832! kinds module added and pegrid module scope restricted
     
    7680 SUBROUTINE lpm_write_exchange_statistics
    7781
    78 #if !defined( __mpifh )
     82#if defined( __parallel )  &&  !defined( __mpifh )
    7983    USE MPI
    8084#endif
     
    100104        ONLY:  comm2d, ierr, pleft, pright, psouth, pnorth
    101105
     106    USE pmc_interface,                                                         &
     107        ONLY: nested_run
     108
    102109    IMPLICIT NONE
    103110
    104 #if defined( __mpifh )
     111#if defined( __parallel )  &&  defined( __mpifh )
    105112    INCLUDE "mpif.h"
    106113#endif
     
    140147
    141148    IF ( number_of_particles > 0 ) THEN
    142         WRITE(9,*) 'number_of_particles ', number_of_particles, current_timestep_number + 1, simulated_time + dt_3d
     149        WRITE(9,*) 'number_of_particles ', number_of_particles,                &
     150                    current_timestep_number + 1, simulated_time + dt_3d
    143151    ENDIF
    144152
    145153#if defined( __parallel )
    146     CALL MPI_ALLREDUCE( number_of_particles, tot_number_of_particles, 1, MPI_INTEGER,      &
    147                                     MPI_SUM, comm2d, ierr)
     154    CALL MPI_ALLREDUCE( number_of_particles, tot_number_of_particles, 1,       &
     155                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
    148156#else
    149157    tot_number_of_particles = number_of_particles
    150158#endif
    151159
    152     CALL pmcp_g_print_number_of_particles (simulated_time+dt_3d, tot_number_of_particles)
     160    IF ( nested_run )  THEN
     161       CALL pmcp_g_print_number_of_particles( simulated_time+dt_3d,            &
     162                                              tot_number_of_particles)
     163    ENDIF
    153164
    154165!
Note: See TracChangeset for help on using the changeset viewer.