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

Last change on this file since 4546 was 4539, checked in by raasch, 4 years ago

checks added, if index limits in header are exceeded (restart_data_mpi_io_mod), bugfix in rrd_mpi_io_int_2d, location and log_point names added/modified, cpu time per grid point and timestep does not included initialization and spinup any more (cpulog_mod)

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