source: palm/trunk/SOURCE/cpulog_mod.f90 @ 1952

Last change on this file since 1952 was 1932, checked in by suehring, 8 years ago

last commit documented

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