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

Last change on this file since 3990 was 3885, checked in by kanani, 5 years ago

restructure/add location/debug messages

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