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

Last change on this file since 4401 was 4378, checked in by Giersch, 4 years ago

Format of rms output in cpu measurements changed to allow values >= 100

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