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

Last change on this file since 3229 was 3229, checked in by sward, 6 years ago

Bugfix: maximum time per log point now includes PE0

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