source: palm/trunk/SOURCE/cpu_statistics.f90 @ 222

Last change on this file since 222 was 222, checked in by letzel, 15 years ago
  • Bugfixes for nonparallel execution
  • Property svn:keywords set to Id
File size: 8.6 KB
Line 
1 SUBROUTINE cpu_statistics
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! Bugfix for nonparallel execution
7!
8! Former revisions:
9! -----------------
10! $Id: cpu_statistics.f90 222 2009-01-12 16:04:16Z letzel $
11!
12! 197 2008-09-16 15:29:03Z raasch
13! Format adjustments in order to allow CPU# > 999,
14! data are collected from PE0 in an ordered sequence which seems to avoid
15! hanging of processes on SGI-ICE
16!
17! 82 2007-04-16 15:40:52Z raasch
18! Preprocessor directives for old systems removed
19!
20! RCS Log replace by Id keyword, revision history cleaned up
21!
22! Revision 1.13  2006/04/26 12:10:51  raasch
23! Output of number of threads per task, max = min in case of 1 PE
24!
25! Revision 1.1  1997/07/24 11:11:11  raasch
26! Initial revision
27!
28!
29! Description:
30! ------------
31! Analysis and output of the cpu-times measured. All PE results are collected
32! on PE0 in order to calculate the mean cpu-time over all PEs and other
33! statistics. The output is sorted according to the amount of cpu-time consumed
34! and output on PE0.
35!------------------------------------------------------------------------------!
36
37    USE cpulog
38    USE pegrid
39    USE control_parameters
40
41    IMPLICIT NONE
42
43    INTEGER    ::  i, ii(1), iii, lp, sender
44    REAL, SAVE ::  norm = 1.0
45    REAL, DIMENSION(:),   ALLOCATABLE ::  pe_max, pe_min, pe_rms, sum
46    REAL, DIMENSION(:,:), ALLOCATABLE ::  pe_log_points
47
48
49!
50!-- Compute cpu-times in seconds
51    log_point%mtime  = log_point%mtime  / norm
52    log_point%sum    = log_point%sum    / norm
53    log_point%vector = log_point%vector / norm
54    WHERE ( log_point%counts /= 0 )
55       log_point%mean = log_point%sum / log_point%counts
56    END WHERE
57
58
59!
60!-- Collect cpu-times from all PEs and calculate statistics
61    IF ( myid == 0 )  THEN
62!
63!--    Allocate and initialize temporary arrays needed for statistics
64       ALLOCATE( pe_max( SIZE( log_point ) ), pe_min( SIZE( log_point ) ), &
65                 pe_rms( SIZE( log_point ) ),                              &
66                 pe_log_points( SIZE( log_point ), 0:numprocs-1 ) )
67       pe_min = log_point%sum
68       pe_max = log_point%sum    ! need to be set in case of 1 PE
69       pe_rms = 0.0
70
71#if defined( __parallel )
72!
73!--    Receive data from all PEs
74       DO  i = 1, numprocs-1
75          CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL, &
76                         i, i, comm2d, status, ierr )
77          sender = status(MPI_SOURCE)
78          pe_log_points(:,sender) = pe_max
79       ENDDO
80       pe_log_points(:,0) = log_point%sum   ! Results from PE0
81!
82!--    Calculate mean of all PEs, store it on log_point%sum
83!--    and find minimum and maximum
84       DO  iii = 1, SIZE( log_point )
85          DO  i = 1, numprocs-1
86             log_point(iii)%sum = log_point(iii)%sum + pe_log_points(iii,i)
87             pe_min(iii) = MIN( pe_min(iii), pe_log_points(iii,i) )
88             pe_max(iii) = MAX( pe_max(iii), pe_log_points(iii,i) )
89          ENDDO
90          log_point(iii)%sum = log_point(iii)%sum / numprocs
91!
92!--       Calculate rms
93          DO  i = 0, numprocs-1
94             pe_rms(iii) = pe_rms(iii) + ( &
95                                 pe_log_points(iii,i) - log_point(iii)%sum &
96                                         )**2
97          ENDDO
98          pe_rms(iii) = SQRT( pe_rms(iii) / numprocs )
99       ENDDO
100    ELSE
101!
102!--    Send data to PE0 (pe_max is used as temporary storage to send
103!--    the data in order to avoid sending the data type log)
104       ALLOCATE( pe_max( SIZE( log_point ) ) )
105       pe_max = log_point%sum
106       CALL MPI_SEND( pe_max(1), SIZE( log_point ), MPI_REAL, 0, myid, comm2d, &
107                      ierr )
108#endif
109
110    ENDIF
111
112!
113!-- Write cpu-times
114    IF ( myid == 0 )  THEN
115!
116!--    Re-store sums
117       ALLOCATE( sum( SIZE( log_point ) ) )
118       WHERE ( log_point%counts /= 0 )
119          sum = log_point%sum
120       ELSEWHERE
121          sum = -1.0
122       ENDWHERE
123
124!
125!--    Write cpu-times sorted by size
126       CALL check_open( 18 )
127#if defined( __parallel )
128       WRITE ( 18, 100 )  TRIM( run_description_header ),        &
129                          numprocs * threads_per_task, pdims(1), pdims(2), &
130                          threads_per_task
131#else
132       WRITE ( 18, 100 )  TRIM( run_description_header ),        &
133                          numprocs * threads_per_task, 1, 1, &
134                          threads_per_task
135#endif
136       DO
137          ii = MAXLOC( sum )
138          i = ii(1)
139          IF ( sum(i) /= -1.0 )  THEN
140             WRITE ( 18, 102 ) &
141                log_point(i)%place, log_point(i)%sum,                &
142                log_point(i)%sum / log_point(1)%sum * 100.0,         &
143                log_point(i)%counts, pe_min(i), pe_max(i), pe_rms(i)
144             sum(i) = -1.0
145          ELSE
146             EXIT
147          ENDIF
148       ENDDO
149    ENDIF
150
151
152!
153!-- The same procedure again for the individual measurements.
154!
155!-- Compute cpu-times in seconds
156    log_point_s%mtime  = log_point_s%mtime  / norm
157    log_point_s%sum    = log_point_s%sum    / norm
158    log_point_s%vector = log_point_s%vector / norm
159    WHERE ( log_point_s%counts /= 0 )
160       log_point_s%mean = log_point_s%sum / log_point_s%counts
161    END WHERE
162
163!
164!-- Collect cpu-times from all PEs and calculate statistics
165#if defined( __parallel )
166!
167!-- Set barrier in order to avoid that PE0 receives log_point_s-data
168!-- while still busy with receiving log_point-data (see above)
169    CALL MPI_BARRIER( comm2d, ierr )   
170#endif
171    IF ( myid == 0 )  THEN
172!
173!--    Initialize temporary arrays needed for statistics
174       pe_min = log_point_s%sum
175       pe_max = log_point_s%sum    ! need to be set in case of 1 PE
176       pe_rms = 0.0
177
178#if defined( __parallel )
179!
180!--    Receive data from all PEs
181       DO  i = 1, numprocs-1
182          CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL, &
183                         MPI_ANY_SOURCE, MPI_ANY_TAG, comm2d, status, ierr )
184          sender = status(MPI_SOURCE)
185          pe_log_points(:,sender) = pe_max
186       ENDDO
187       pe_log_points(:,0) = log_point_s%sum   ! Results from PE0
188!
189!--    Calculate mean of all PEs, store it on log_point_s%sum
190!--    and find minimum and maximum
191       DO  iii = 1, SIZE( log_point )
192          DO  i = 1, numprocs-1
193             log_point_s(iii)%sum = log_point_s(iii)%sum + pe_log_points(iii,i)
194             pe_min(iii) = MIN( pe_min(iii), pe_log_points(iii,i) )
195             pe_max(iii) = MAX( pe_max(iii), pe_log_points(iii,i) )
196          ENDDO
197          log_point_s(iii)%sum = log_point_s(iii)%sum / numprocs
198!
199!--       Calculate rms
200          DO  i = 0, numprocs-1
201             pe_rms(iii) = pe_rms(iii) + ( &
202                                 pe_log_points(iii,i) - log_point_s(iii)%sum &
203                                         )**2
204          ENDDO
205          pe_rms(iii) = SQRT( pe_rms(iii) / numprocs )
206       ENDDO
207    ELSE
208!
209!--    Send data to PE0 (pe_max is used as temporary storage to send
210!--    the data in order to avoid sending the data type log)
211       pe_max = log_point_s%sum
212       CALL MPI_SEND( pe_max(1), SIZE( log_point ), MPI_REAL, 0, 0, comm2d, &
213                      ierr )
214#endif
215
216    ENDIF
217
218!
219!-- Write cpu-times
220    IF ( myid == 0 )  THEN
221!
222!--    Re-store sums
223       WHERE ( log_point_s%counts /= 0 )
224          sum = log_point_s%sum
225       ELSEWHERE
226          sum = -1.0
227       ENDWHERE
228
229!
230!--    Write cpu-times sorted by size
231       WRITE ( 18, 101 )
232       DO
233          ii = MAXLOC( sum )
234          i = ii(1)
235          IF ( sum(i) /= -1.0 )  THEN
236             WRITE ( 18, 102 ) &
237                log_point_s(i)%place, log_point_s(i)%sum, &
238                log_point_s(i)%sum / log_point(1)%sum * 100.0, &
239                log_point_s(i)%counts, pe_min(i), pe_max(i), pe_rms(i)
240             sum(i) = -1.0
241          ELSE
242             EXIT
243          ENDIF
244       ENDDO
245
246!
247!--    Empty lines in order to create a gap to the results of the model
248!--    continuation runs
249       WRITE ( 18, 103 )
250
251!
252!--    Unit 18 is not needed anymore
253       CALL close_file( 18 )
254
255    ENDIF
256
257
258100 FORMAT (A/11('-')//'CPU measures for ',I5,' PEs (',I5,'(x) * ',I5,'(y', &
259            &') tasks *',I5,' threads):'/ &
260             &'----------------------------------------------------------', &
261             &'------------'//&
262            &'place:                        mean        counts      min  ', &
263             &'     max       rms'/ &
264            &'                           sec.      %                sec. ', &
265             &'     sec.      sec.'/  &
266            &'-----------------------------------------------------------', &
267             &'-------------------')
268
269101 FORMAT (/'special measures:'/ &
270            &'-----------------------------------------------------------', &
271            &'--------------------')
272
273102 FORMAT (A20,2X,F9.3,2X,F7.2,1X,I7,3(1X,F9.3))
274103 FORMAT (//)
275
276 END SUBROUTINE cpu_statistics
277
Note: See TracBrowser for help on using the repository browser.