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

Last change on this file since 4739 was 4665, checked in by hellstea, 4 years ago

Interpolation and anterpolation subroutines renamed and all missing subroutine description comments added (pmc_interface_mod). Format descriptor 102 slightly modified (cpulog_mod).

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