source: palm/trunk/SOURCE/cpulog.f90 @ 1321

Last change on this file since 1321 was 1321, checked in by raasch, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 18.9 KB
Line 
1 MODULE cpulog
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: cpulog.f90 1321 2014-03-20 09:40:40Z raasch $
27!
28! 1320 2014-03-20 08:40:49Z raasch
29! ONLY-attribute added to USE-statements,
30! kind-parameters added to all INTEGER and REAL declaration statements,
31! kinds are defined in new module kinds,
32! revision history before 2012 removed,
33! comment fields (!:) to be used for variable explanations added to
34! all variable declaration statements
35!
36! 1318 2014-03-17 13:35:16Z raasch
37! former files/routines cpu_log and cpu_statistics combined to one module,
38! which also includes the former data module cpulog from the modules-file
39!
40! 1036 2012-10-22 13:43:42Z raasch
41! code put under GPL (PALM 3.9)
42!
43! Revision 1.1  1997/07/24 11:12:29  raasch
44! Initial revision
45!
46!
47! Description:
48! ------------
49! Cpu-time measurements for any program part whatever.
50!------------------------------------------------------------------------------!
51
52    USE control_parameters,                                                    &
53        ONLY: message_string, nr_timesteps_this_run, run_description_header,   &
54              synchronous_exchange
55               
56    USE indices,                                                               &
57        ONLY: nx, ny, nz
58       
59    USE kinds
60   
61    USE pegrid
62
63    IMPLICIT NONE
64
65    PRIVATE
66    PUBLIC   cpu_log, cpu_log_barrierwait, cpu_log_nowait, cpu_statistics,     &
67             initial_wallclock_time, log_point, log_point_s
68
69    INTERFACE cpu_log
70       MODULE PROCEDURE cpu_log
71    END INTERFACE cpu_log
72
73    INTERFACE cpu_statistics
74       MODULE PROCEDURE cpu_statistics
75    END INTERFACE cpu_statistics
76
77    INTEGER(iwp), PARAMETER ::  cpu_log_continue = 0  !:
78    INTEGER(iwp), PARAMETER ::  cpu_log_pause = 1     !:
79    INTEGER(iwp), PARAMETER ::  cpu_log_start = 2     !:
80    INTEGER(iwp), PARAMETER ::  cpu_log_stop = 3      !:
81
82    LOGICAL            ::  cpu_log_barrierwait = .FALSE.  !:
83    LOGICAL, PARAMETER ::  cpu_log_nowait = .FALSE.       !:
84
85    REAL(wp) ::  initial_wallclock_time  !:
86
87    TYPE logpoint
88       REAL(wp)           ::  isum       !:
89       REAL(wp)           ::  ivect      !:
90       REAL(wp)           ::  mean       !:
91       REAL(wp)           ::  mtime      !:
92       REAL(wp)           ::  mtimevec   !:
93       REAL(wp)           ::  sum        !:
94       REAL(wp)           ::  vector     !:
95       INTEGER(iwp)       ::  counts     !:
96       CHARACTER (LEN=20) ::  place      !:
97    END TYPE logpoint
98
99    TYPE(logpoint), DIMENSION(100) ::  log_point = logpoint( 0.0, 0.0, 0.0,   &
100                                       0.0, 0.0, 0.0, 0.0, 0, ' ' ),          &
101                                       log_point_s = logpoint( 0.0, 0.0, 0.0, &
102                                       0.0, 0.0, 0.0, 0.0, 0, ' ' )
103
104    SAVE
105
106 CONTAINS
107
108    SUBROUTINE cpu_log( log_event, place, modus, barrierwait )
109
110       IMPLICIT NONE
111
112       CHARACTER (LEN=*) ::  modus              !:
113       CHARACTER (LEN=*) ::  place              !:
114       
115       LOGICAL           ::  wait_allowed       !:
116       LOGICAL, OPTIONAL ::  barrierwait        !:
117       LOGICAL, SAVE     ::  first = .TRUE.     !:
118       
119       REAL(wp)          ::  mtime = 0.0        !:
120       REAL(wp)          ::   mtimevec = 0.0    !:
121       TYPE(logpoint)    ::  log_event          !:
122
123#if defined( __lc ) || defined( __decalpha )
124       INTEGER(idp)     ::  count        !:
125       INTEGER(idp)     ::  count_rate   !:
126#elif defined( __nec )
127       INTEGER(iwp)      ::  count       !:
128       INTEGER(iwp)      ::  count_rate  !:
129#elif defined( __ibm )
130       INTEGER(idp)     ::  IRTC         !:
131#endif
132
133
134!
135!--    Initialize and check, respectively, point of measurement
136       IF ( log_event%place == ' ' )  THEN
137          log_event%place = place
138       ELSEIF ( log_event%place /= place )  THEN
139          WRITE( message_string, * ) 'wrong argument & expected: ',            &
140                            TRIM(log_event%place), '  given: ',  TRIM( place )
141          CALL message( 'cpu_log', 'PA0174', 1, 2, 0, 6, 0 )
142       ENDIF
143
144!
145!--    Determine, if barriers are allowed to set
146       IF ( PRESENT( barrierwait ) )  THEN
147          wait_allowed = barrierwait
148       ELSE
149          wait_allowed = .TRUE.
150       ENDIF
151
152!
153!--    MPI barrier, if requested, in order to avoid measuring wait times
154!--    caused by MPI routines waiting for other MPI routines of other
155!--    PEs that have not yet finished
156#if defined( __parallel )
157       IF ( cpu_log_barrierwait  .AND.  wait_allowed  .AND.                    &
158            ( modus == 'start'  .OR.  modus == 'continue' ) )  THEN
159          CALL MPI_BARRIER( comm2d, ierr )
160       ENDIF
161#endif
162
163!
164!--    Take current time
165#if defined( __lc ) || defined( __decalpha ) || defined( __nec )
166       CALL SYSTEM_CLOCK( count, count_rate )
167       mtime = REAL( count ) / REAL( count_rate )
168#elif defined( __ibm )
169       mtime = IRTC( ) * 1E-9
170#else
171       message_string = 'no time measurement defined on this host'
172       CALL message( 'cpu_log', 'PA0175', 1, 2, 0, 6, 0 )
173#endif
174
175!
176!--    Start, stop or pause measurement
177       IF ( modus == 'start'  .OR.  modus == 'continue' )  THEN
178          log_event%mtime    = mtime
179          log_event%mtimevec = mtimevec
180       ELSEIF ( modus == 'pause' )  THEN
181          IF ( ( mtime - log_event%mtime ) < 0.0  .AND.  first )  THEN
182             WRITE( message_string, * ) 'negative time interval occured',      &
183                         ' &PE',myid,' L=PAUSE "',TRIM(log_event%place),       &
184                         '" new=', mtime,' last=',log_event%mtime
185             CALL message( 'cpu_log', 'PA0176', 0, 1, -1, 6, 0 )
186             first = .FALSE.
187          ENDIF
188          log_event%isum     = log_event%isum + mtime - log_event%mtime
189          log_event%ivect    = log_event%ivect  + mtimevec - log_event%mtimevec
190       ELSEIF ( modus == 'stop' )  THEN
191          IF ( ( mtime - log_event%mtime + log_event%isum ) < 0.0  .AND.       &
192               first )  THEN
193             WRITE( message_string, * ) 'negative time interval occured',      &
194                         ' &PE',myid,' L=STOP "',TRIM(log_event%place),'" new=', &
195                         mtime,' last=',log_event%mtime,' isum=',log_event%isum
196             CALL message( 'cpu_log', 'PA0177', 0, 1, -1, 6, 0 )
197             first = .FALSE.
198          ENDIF
199          log_event%mtime    = mtime    - log_event%mtime    + log_event%isum
200          log_event%mtimevec = mtimevec - log_event%mtimevec + log_event%ivect
201          log_event%sum      = log_event%sum  + log_event%mtime
202          IF ( log_event%sum < 0.0  .AND.  first )  THEN
203             WRITE( message_string, * ) 'negative time interval occured',      &
204                         ' &PE',myid,' L=STOP "',TRIM(log_event%place),'" sum=', &
205                                         log_event%sum,' mtime=',log_event%mtime
206             CALL message( 'cpu_log', 'PA0178', 0, 1, -1, 6, 0 )
207             first = .FALSE.
208          ENDIF
209          log_event%vector   = log_event%vector + log_event%mtimevec
210          log_event%counts   = log_event%counts + 1
211          log_event%isum     = 0.0
212          log_event%ivect    = 0.0
213       ELSE
214          message_string = 'unknown modus of time measurement: ' // TRIM( modus )
215          CALL message( 'cpu_log', 'PA0179', 0, 1, -1, 6, 0 )
216       ENDIF
217
218    END SUBROUTINE cpu_log
219
220
221    SUBROUTINE cpu_statistics
222!------------------------------------------------------------------------------!
223! Description:
224! ------------
225! Analysis and output of the cpu-times measured. All PE results are collected
226! on PE0 in order to calculate the mean cpu-time over all PEs and other
227! statistics. The output is sorted according to the amount of cpu-time consumed
228! and output on PE0.
229!------------------------------------------------------------------------------!
230
231       IMPLICIT NONE
232
233       INTEGER(iwp)    ::  i               !:
234       INTEGER(iwp)    ::  ii(1)           !:
235       INTEGER(iwp)    ::  iii             !:
236       INTEGER(iwp)    ::  sender          !:
237       REAL(wp)       ::  average_cputime  !:
238       REAL(wp), SAVE ::  norm = 1.0       !:
239       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_max        !:
240       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_min        !:
241       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_rms        !:
242       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  sum           !:
243       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pe_log_points !:
244
245
246!
247!--    Compute cpu-times in seconds
248       log_point%mtime  = log_point%mtime  / norm
249       log_point%sum    = log_point%sum    / norm
250       log_point%vector = log_point%vector / norm
251       WHERE ( log_point%counts /= 0 )
252          log_point%mean = log_point%sum / log_point%counts
253       END WHERE
254
255
256!
257!--    Collect cpu-times from all PEs and calculate statistics
258       IF ( myid == 0 )  THEN
259!
260!--       Allocate and initialize temporary arrays needed for statistics
261          ALLOCATE( pe_max( SIZE( log_point ) ), pe_min( SIZE( log_point ) ),  &
262                    pe_rms( SIZE( log_point ) ),                               &
263                    pe_log_points( SIZE( log_point ), 0:numprocs-1 ) )
264          pe_min = log_point%sum
265          pe_max = log_point%sum    ! need to be set in case of 1 PE
266          pe_rms = 0.0
267
268#if defined( __parallel )
269!
270!--       Receive data from all PEs
271          DO  i = 1, numprocs-1
272             CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL,            &
273                            i, i, comm2d, status, ierr )
274             sender = status(MPI_SOURCE)
275             pe_log_points(:,sender) = pe_max
276          ENDDO
277          pe_log_points(:,0) = log_point%sum   ! Results from PE0
278!
279!--       Calculate mean of all PEs, store it on log_point%sum
280!--       and find minimum and maximum
281          DO  iii = 1, SIZE( log_point )
282             DO  i = 1, numprocs-1
283                log_point(iii)%sum = log_point(iii)%sum + pe_log_points(iii,i)
284                pe_min(iii) = MIN( pe_min(iii), pe_log_points(iii,i) )
285                pe_max(iii) = MAX( pe_max(iii), pe_log_points(iii,i) )
286             ENDDO
287             log_point(iii)%sum = log_point(iii)%sum / numprocs
288!
289!--          Calculate rms
290             DO  i = 0, numprocs-1
291                pe_rms(iii) = pe_rms(iii) + (                                  &
292                                    pe_log_points(iii,i) - log_point(iii)%sum  &
293                                            )**2
294             ENDDO
295             pe_rms(iii) = SQRT( pe_rms(iii) / numprocs )
296          ENDDO
297       ELSE
298!
299!--       Send data to PE0 (pe_max is used as temporary storage to send
300!--       the data in order to avoid sending the data type log)
301          ALLOCATE( pe_max( SIZE( log_point ) ) )
302          pe_max = log_point%sum
303          CALL MPI_SEND( pe_max(1), SIZE( log_point ), MPI_REAL, 0, myid, comm2d, &
304                         ierr )
305#endif
306
307       ENDIF
308
309!
310!--    Write cpu-times
311       IF ( myid == 0 )  THEN
312!
313!--       Re-store sums
314          ALLOCATE( sum( SIZE( log_point ) ) )
315          WHERE ( log_point%counts /= 0 )
316             sum = log_point%sum
317          ELSEWHERE
318             sum = -1.0
319          ENDWHERE
320
321!
322!--       Get total time in order to calculate CPU-time per gridpoint and timestep
323          IF ( nr_timesteps_this_run /= 0 )  THEN
324             average_cputime = log_point(1)%sum / REAL( (nx+1) * (ny+1) * nz ) / &
325                               REAL( nr_timesteps_this_run ) * 1E6  ! in micro-sec
326          ELSE
327             average_cputime = -1.0
328          ENDIF
329
330!
331!--       Write cpu-times sorted by size
332          CALL check_open( 18 )
333#if defined( __parallel )
334          WRITE ( 18, 100 )  TRIM( run_description_header ),                          &
335                             numprocs * threads_per_task, pdims(1), pdims(2),         &
336                             threads_per_task, nx+1, ny+1, nz, nr_timesteps_this_run, &
337                             average_cputime
338
339          IF ( num_acc_per_node /= 0 )  WRITE ( 18, 108 )  num_acc_per_node
340          WRITE ( 18, 110 )
341#else
342          WRITE ( 18, 100 )  TRIM( run_description_header ),                          &
343                             numprocs * threads_per_task, 1, 1,                       &
344                             threads_per_task, nx+1, ny+1, nz, nr_timesteps_this_run, &
345                             average_cputime
346
347          IF ( num_acc_per_node /= 0 )  WRITE ( 18, 109 )  num_acc_per_node
348          WRITE ( 18, 110 )
349#endif
350          DO
351             ii = MAXLOC( sum )
352             i = ii(1)
353             IF ( sum(i) /= -1.0 )  THEN
354                WRITE ( 18, 102 ) &
355              log_point(i)%place, log_point(i)%sum,                &
356                   log_point(i)%sum / log_point(1)%sum * 100.0,         &
357                   log_point(i)%counts, pe_min(i), pe_max(i), pe_rms(i)
358                sum(i) = -1.0
359             ELSE
360                EXIT
361             ENDIF
362          ENDDO
363       ENDIF
364
365
366!
367!--    The same procedure again for the individual measurements.
368!
369!--    Compute cpu-times in seconds
370       log_point_s%mtime  = log_point_s%mtime  / norm
371       log_point_s%sum    = log_point_s%sum    / norm
372       log_point_s%vector = log_point_s%vector / norm
373       WHERE ( log_point_s%counts /= 0 )
374          log_point_s%mean = log_point_s%sum / log_point_s%counts
375       END WHERE
376
377!
378!--    Collect cpu-times from all PEs and calculate statistics
379#if defined( __parallel )
380!
381!--    Set barrier in order to avoid that PE0 receives log_point_s-data
382!--    while still busy with receiving log_point-data (see above)
383       CALL MPI_BARRIER( comm2d, ierr )
384#endif
385       IF ( myid == 0 )  THEN
386!
387!--       Initialize temporary arrays needed for statistics
388          pe_min = log_point_s%sum
389          pe_max = log_point_s%sum    ! need to be set in case of 1 PE
390          pe_rms = 0.0
391
392#if defined( __parallel )
393!
394!--       Receive data from all PEs
395          DO  i = 1, numprocs-1
396             CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL, &
397                            MPI_ANY_SOURCE, MPI_ANY_TAG, comm2d, status, ierr )
398             sender = status(MPI_SOURCE)
399             pe_log_points(:,sender) = pe_max
400          ENDDO
401          pe_log_points(:,0) = log_point_s%sum   ! Results from PE0
402!
403!--       Calculate mean of all PEs, store it on log_point_s%sum
404!--       and find minimum and maximum
405          DO  iii = 1, SIZE( log_point )
406             DO  i = 1, numprocs-1
407                log_point_s(iii)%sum = log_point_s(iii)%sum + pe_log_points(iii,i)
408                pe_min(iii) = MIN( pe_min(iii), pe_log_points(iii,i) )
409                pe_max(iii) = MAX( pe_max(iii), pe_log_points(iii,i) )
410             ENDDO
411             log_point_s(iii)%sum = log_point_s(iii)%sum / numprocs
412!
413!--          Calculate rms
414             DO  i = 0, numprocs-1
415                pe_rms(iii) = pe_rms(iii) + ( &
416                                    pe_log_points(iii,i) - log_point_s(iii)%sum &
417                                            )**2
418             ENDDO
419             pe_rms(iii) = SQRT( pe_rms(iii) / numprocs )
420          ENDDO
421       ELSE
422!
423!--       Send data to PE0 (pe_max is used as temporary storage to send
424!--       the data in order to avoid sending the data type log)
425          pe_max = log_point_s%sum
426          CALL MPI_SEND( pe_max(1), SIZE( log_point ), MPI_REAL, 0, 0, comm2d, &
427                         ierr )
428#endif
429
430       ENDIF
431
432!
433!--    Write cpu-times
434       IF ( myid == 0 )  THEN
435!
436!--       Re-store sums
437          WHERE ( log_point_s%counts /= 0 )
438             sum = log_point_s%sum
439          ELSEWHERE
440             sum = -1.0
441          ENDWHERE
442
443!
444!--       Write cpu-times sorted by size
445          WRITE ( 18, 101 )
446          DO
447             ii = MAXLOC( sum )
448             i = ii(1)
449             IF ( sum(i) /= -1.0 )  THEN
450                WRITE ( 18, 102 ) &
451                   log_point_s(i)%place, log_point_s(i)%sum, &
452                   log_point_s(i)%sum / log_point(1)%sum * 100.0, &
453                   log_point_s(i)%counts, pe_min(i), pe_max(i), pe_rms(i)
454                sum(i) = -1.0
455             ELSE
456                EXIT
457             ENDIF
458          ENDDO
459
460!
461!--       Output of handling of MPI operations
462          IF ( collective_wait )  THEN
463             WRITE ( 18, 103 )
464          ELSE
465             WRITE ( 18, 104 )
466          ENDIF
467          IF ( cpu_log_barrierwait )  WRITE ( 18, 111 )
468          IF ( synchronous_exchange )  THEN
469             WRITE ( 18, 105 )
470          ELSE
471             WRITE ( 18, 106 )
472          ENDIF
473
474!
475!--       Empty lines in order to create a gap to the results of the model
476!--       continuation runs
477          WRITE ( 18, 107 )
478
479!
480!--       Unit 18 is not needed anymore
481          CALL close_file( 18 )
482
483       ENDIF
484
485
486   100 FORMAT (A/11('-')//'CPU measures for ',I5,' PEs (',I5,'(x) * ',I5,'(y', &
487               &') tasks *',I5,' threads):'//                                  &
488               'gridpoints (x/y/z): ',20X,I5,' * ',I5,' * ',I5/                &
489               'nr of timesteps: ',22X,I6/                                     &
490               'cpu time per grid point and timestep: ',5X,F8.5,' * 10**-6 s')
491
492   101 FORMAT (/'special measures:'/ &
493               &'-----------------------------------------------------------', &
494               &'--------------------')
495
496   102 FORMAT (A20,2X,F9.3,2X,F7.2,1X,I7,3(1X,F9.3))
497   103 FORMAT (/'Barriers are set in front of collective operations')
498   104 FORMAT (/'No barriers are set in front of collective operations')
499   105 FORMAT (/'Exchange of ghostpoints via MPI_SENDRCV')
500   106 FORMAT (/'Exchange of ghostpoints via MPI_ISEND/MPI_IRECV')
501   107 FORMAT (//)
502   108 FORMAT ('Accelerator boards per node: ',14X,I2)
503   109 FORMAT ('Accelerator boards: ',23X,I2)
504   110 FORMAT ('----------------------------------------------------------',   &
505               &'------------'//&
506               &'place:                        mean        counts      min  ', &
507               &'     max       rms'/ &
508               &'                           sec.      %                sec. ', &
509               &'     sec.      sec.'/  &
510               &'-----------------------------------------------------------', &
511               &'-------------------')
512   111 FORMAT (/'Barriers are set at beginning (start/continue) of measurements')
513
514    END SUBROUTINE cpu_statistics
515
516 END MODULE cpulog
Note: See TracBrowser for help on using the repository browser.