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

Last change on this file since 4181 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

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