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

Last change on this file since 3152 was 3049, checked in by Giersch, 6 years ago

Revision history corrected

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