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

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

bugfix for r4539: values for min/max/rms stored in separate arrays

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