source: palm/trunk/SOURCE/lpm_write_exchange_statistics.f90 @ 979

Last change on this file since 979 was 850, checked in by raasch, 12 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 1.5 KB
Line 
1 SUBROUTINE lpm_write_exchange_statistics
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! ------------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: lpm_write_exchange_statistics.f90 850 2012-03-15 12:09:25Z fricke $
11!
12! 849 2012-03-15 10:35:09Z raasch
13! initial revision (former part of advec_particles)
14!
15!
16! Description:
17! ------------
18! Write particle statistics (total particle numbers and number of particles
19! exchanged between subdomains) on ASCII file.
20!
21! ATTENTION: output format of this file could be further improved! At current
22!            stage it is only a test output.
23!------------------------------------------------------------------------------!
24
25    USE control_parameters
26    USE particle_attributes
27    USE pegrid
28
29    IMPLICIT NONE
30
31
32    CALL check_open( 80 )
33#if defined( __parallel )
34    WRITE ( 80, 8000 )  current_timestep_number+1, simulated_time+dt_3d, &
35                        number_of_particles, pleft, trlp_count_sum,      &
36                        trlp_count_recv_sum, pright, trrp_count_sum,     &
37                        trrp_count_recv_sum, psouth, trsp_count_sum,     &
38                        trsp_count_recv_sum, pnorth, trnp_count_sum,     &
39                        trnp_count_recv_sum, maximum_number_of_particles
40    CALL close_file( 80 )
41#else
42    WRITE ( 80, 8000 )  current_timestep_number+1, simulated_time+dt_3d, &
43                        number_of_particles, maximum_number_of_particles
44#endif
45
46!
47!-- Formats
488000 FORMAT (I6,1X,F7.2,4X,I6,5X,4(I3,1X,I4,'/',I4,2X),6X,I6)
49
50
51 END SUBROUTINE lpm_write_exchange_statistics
Note: See TracBrowser for help on using the repository browser.