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

Last change on this file since 2101 was 2101, checked in by suehring, 7 years ago

last commit documented

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