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

Last change on this file since 4027 was 4015, checked in by raasch, 5 years ago

all reals changed to double precision in order to work with 32-bit working precision, otherwise calculated time intervals would mostly give zero; variable child_domain_nvn eliminated

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