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

Last change on this file since 1925 was 1851, checked in by maronga, 8 years ago

last commit documented

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