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

Last change on this file since 2152 was 2119, checked in by raasch, 7 years ago

last commit documented

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