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

Last change on this file since 82 was 82, checked in by raasch, 17 years ago

vorlaeufige Standalone-Version fuer Linux-Cluster

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