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

Last change on this file since 1808 was 1808, checked in by raasch, 8 years ago

preprocessor directives using machine dependent flags (lc, ibm, etc.) mostly removed from the code

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