Ignore:
Timestamp:
Feb 14, 2018 4:01:55 PM (6 years ago)
Author:
thiele
Message:

Introduce particle transfer in nested models

File:
1 edited

Legend:

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

    r2718 r2801  
    2525! -----------------
    2626! $Id$
     27! Introduce particle transfer in nested models.
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    6972 SUBROUTINE lpm_write_exchange_statistics
    7073 
     74    USE MPI
    7175
    7276    USE control_parameters,                                                    &
     
    8286               trsp_count_sum, trsp_count_recv_sum
    8387
     88    USE pmc_particle_interface,                                                &
     89        ONLY:  pmcp_g_print_number_of_particles
     90
    8491    USE pegrid
    8592
     
    8996    INTEGER(iwp) :: jp         !<
    9097    INTEGER(iwp) :: kp         !<
     98    INTEGER(iwp) :: tot_number_of_particles
     99
     100
    91101
    92102!
     
    110120                        trsp_count_recv_sum, pnorth, trnp_count_sum,     &
    111121                        trnp_count_recv_sum
    112     CALL close_file( 80 )
    113122#else
    114123    WRITE ( 80, 8000 )  current_timestep_number+1, simulated_time+dt_3d, &
    115124                        number_of_particles
    116125#endif
     126    CALL close_file( 80 )
     127
     128    IF ( number_of_particles > 0 ) THEN
     129        WRITE(9,*) 'number_of_particles ', number_of_particles, current_timestep_number + 1, simulated_time + dt_3d
     130    ENDIF
     131
     132#if defined( __parallel )
     133    CALL MPI_ALLREDUCE( number_of_particles, tot_number_of_particles, 1, MPI_INTEGER,      &
     134                                    MPI_SUM, comm2d, ierr)
     135#else
     136    tot_number_of_particles = number_of_particles
     137#endif
     138
     139    CALL pmcp_g_print_number_of_particles (simulated_time+dt_3d, tot_number_of_particles)
    117140
    118141!
Note: See TracChangeset for help on using the changeset viewer.