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

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

routine description added, usage of module interfaces removed

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