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

Last change on this file since 2307 was 2266, checked in by raasch, 7 years ago

bugfix for calculating cpu-time per gridpoint, nech related parts removed from subjob script

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