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

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