source: palm/trunk/SOURCE/cpulog_mod.f90

Last change on this file was 4835, checked in by raasch, 3 years ago

openmp bugfix (some private statements were missing); output format for cpu measures slightly changed

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