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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

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