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

Last change on this file since 4457 was 4429, checked in by raasch, 4 years ago

serial (non-MPI) test case added, several bugfixes for the serial mode

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