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

Last change on this file since 2932 was 2932, checked in by maronga, 6 years ago

renamed all Fortran NAMELISTS

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