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

Last change on this file since 3842 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

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