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

Last change on this file since 4565 was 4559, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

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