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

Last change on this file since 4536 was 4536, checked in by raasch, 5 years ago

messages and debug output converted to PALM routines (restart_data_mpi_io_mod), binary version number set to 5.0, heeader output for restart data format added, restart data filesize and I/O transfer speed added in cpu_measures, handling of single restart files (created with MPI-I/O) added to palmrun, bugfix: preprocessor directive adjusted (virtual_measurement_mod), location message format changed

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