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

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

Remaining error messages revised, comments extended

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