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

Last change on this file since 4598 was 4577, checked in by raasch, 4 years ago

further re-formatting to follow the PALM coding standard

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