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

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

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

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