source: palm/trunk/SOURCE/cpulog.f90 @ 1319

Last change on this file since 1319 was 1319, checked in by raasch, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 17.8 KB
RevLine 
[1318]1 MODULE cpulog
[1]2
[1036]3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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!
[1310]17! Copyright 1997-2014 Leibniz Universitaet Hannover
[1036]18!--------------------------------------------------------------------------------!
19!
[254]20! Current revisions:
[1]21! -----------------
22!
[1319]23!
[1]24! Former revisions:
25! -----------------
[3]26! $Id: cpulog.f90 1319 2014-03-17 15:08:44Z raasch $
[83]27!
[1319]28! 1318 2014-03-17 13:35:16Z raasch
29! former files/routines cpu_log and cpu_statistics combined to one module,
30! which also includes the former data module cpulog from the modules-file
31!
[1037]32! 1036 2012-10-22 13:43:42Z raasch
33! code put under GPL (PALM 3.9)
34!
[392]35! 274 2009-03-26 15:11:21Z heinze
36! Output of messages replaced by message handling routine.
37! Type of count and count_rate changed to default INTEGER on NEC machines
38!
[226]39! 225 2009-01-26 14:44:20Z raasch
40! Type of count and count_rate changed to INTEGER(8)
41!
[83]42! 82 2007-04-16 15:40:52Z raasch
43! Preprocessor strings for different linux clusters changed to "lc",
44! preprocessor directives for old systems removed
45!
[3]46! RCS Log replace by Id keyword, revision history cleaned up
47!
[1]48! Revision 1.24  2006/06/02 15:12:17  raasch
49! cpp-directives extended for lctit
50!
51! Revision 1.1  1997/07/24 11:12:29  raasch
52! Initial revision
53!
54!
55! Description:
56! ------------
57! Cpu-time measurements for any program part whatever.
[3]58!------------------------------------------------------------------------------!
[1]59
[254]60    USE control_parameters
[1318]61    USE indices,  ONLY: nx, ny, nz
[1]62    USE pegrid
63
64    IMPLICIT NONE
65
[1318]66    PRIVATE
67    PUBLIC   cpu_log, cpu_log_barrierwait, cpu_log_nowait, cpu_statistics, &
68             initial_wallclock_time, log_point, log_point_s
[1]69
[1318]70    INTERFACE cpu_log
71       MODULE PROCEDURE cpu_log
72    END INTERFACE cpu_log
73
74    INTERFACE cpu_statistics
75       MODULE PROCEDURE cpu_statistics
76    END INTERFACE cpu_statistics
77
78    INTEGER, PARAMETER ::  cpu_log_continue = 0, cpu_log_pause = 1, &
79                           cpu_log_start = 2, cpu_log_stop = 3
80
81    LOGICAL            ::  cpu_log_barrierwait = .FALSE.
82    LOGICAL, PARAMETER ::  cpu_log_nowait = .FALSE.
83
84    REAL ::  initial_wallclock_time
85
86    TYPE logpoint
87       REAL               ::  isum, ivect, mean, mtime, mtimevec, sum, vector
88       INTEGER            ::  counts
89       CHARACTER (LEN=20) ::  place
90    END TYPE logpoint
91
92    TYPE(logpoint), DIMENSION(100) ::  log_point = logpoint( 0.0, 0.0, 0.0,   &
93                                       0.0, 0.0, 0.0, 0.0, 0, ' ' ),          &
94                                       log_point_s = logpoint( 0.0, 0.0, 0.0, &
95                                       0.0, 0.0, 0.0, 0.0, 0, ' ' )
96
97    SAVE
98
99 CONTAINS
100
101    SUBROUTINE cpu_log( log_event, place, modus, barrierwait )
102
103       IMPLICIT NONE
104
105       CHARACTER (LEN=*)           ::  modus, place
106       LOGICAL                     ::  wait_allowed
107       LOGICAL, OPTIONAL           ::  barrierwait
108       LOGICAL, SAVE               ::  first = .TRUE.
109       REAL                        ::  mtime = 0.0, mtimevec = 0.0
110       TYPE(logpoint)              ::  log_event
111
[239]112#if defined( __lc ) || defined( __decalpha )
[1318]113       INTEGER(8)                  ::  count, count_rate
[239]114#elif defined( __nec )
[1318]115       INTEGER                     ::  count, count_rate
[1]116#elif defined( __ibm )
[1318]117       INTEGER(8)                  ::  IRTC
[1]118#endif
119
120
121!
[1318]122!--    Initialize and check, respectively, point of measurement
123       IF ( log_event%place == ' ' )  THEN
124          log_event%place = place
125       ELSEIF ( log_event%place /= place )  THEN
126          WRITE( message_string, * ) 'wrong argument & expected: ', &
127                            TRIM(log_event%place), '  given: ',  TRIM( place )
128          CALL message( 'cpu_log', 'PA0174', 1, 2, 0, 6, 0 )
129       ENDIF
[1]130
131!
[1318]132!--    Determine, if barriers are allowed to set
133       IF ( PRESENT( barrierwait ) )  THEN
134          wait_allowed = barrierwait
135       ELSE
136          wait_allowed = .TRUE.
137       ENDIF
138
139!
140!--    MPI barrier, if requested, in order to avoid measuring wait times
141!--    caused by MPI routines waiting for other MPI routines of other
142!--    PEs that have not yet finished
143#if defined( __parallel )
144       IF ( cpu_log_barrierwait  .AND.  wait_allowed  .AND.  &
145            ( modus == 'start'  .OR.  modus == 'continue' ) )  THEN
146          CALL MPI_BARRIER( comm2d, ierr )
147       ENDIF
148#endif
149
150!
151!--    Take current time
[82]152#if defined( __lc ) || defined( __decalpha ) || defined( __nec )
[1318]153       CALL SYSTEM_CLOCK( count, count_rate )
154       mtime = REAL( count ) / REAL( count_rate )
[1]155#elif defined( __ibm )
[1318]156       mtime = IRTC( ) * 1E-9
[1]157#else
[1318]158       message_string = 'no time measurement defined on this host'
159       CALL message( 'cpu_log', 'PA0175', 1, 2, 0, 6, 0 )
[1]160#endif
161
162!
[1318]163!--    Start, stop or pause measurement
164       IF ( modus == 'start'  .OR.  modus == 'continue' )  THEN
165          log_event%mtime    = mtime
166          log_event%mtimevec = mtimevec
167       ELSEIF ( modus == 'pause' )  THEN
168          IF ( ( mtime - log_event%mtime ) < 0.0  .AND.  first )  THEN
169             WRITE( message_string, * ) 'negative time interval occured',         &
170                         ' &PE',myid,' L=PAUSE "',TRIM(log_event%place),'" new=', &
171                         mtime,' last=',log_event%mtime
172             CALL message( 'cpu_log', 'PA0176', 0, 1, -1, 6, 0 )
173             first = .FALSE.
174          ENDIF
175          log_event%isum     = log_event%isum + mtime - log_event%mtime
176          log_event%ivect    = log_event%ivect  + mtimevec - log_event%mtimevec
177       ELSEIF ( modus == 'stop' )  THEN
178          IF ( ( mtime - log_event%mtime + log_event%isum ) < 0.0  .AND. &
179               first )  THEN
180             WRITE( message_string, * ) 'negative time interval occured',        &
181                         ' &PE',myid,' L=STOP "',TRIM(log_event%place),'" new=', &
182                         mtime,' last=',log_event%mtime,' isum=',log_event%isum
183             CALL message( 'cpu_log', 'PA0177', 0, 1, -1, 6, 0 )
184             first = .FALSE.
185          ENDIF
186          log_event%mtime    = mtime    - log_event%mtime    + log_event%isum
187          log_event%mtimevec = mtimevec - log_event%mtimevec + log_event%ivect
188          log_event%sum      = log_event%sum  + log_event%mtime
189          IF ( log_event%sum < 0.0  .AND.  first )  THEN
190             WRITE( message_string, * ) 'negative time interval occured',        &
191                         ' &PE',myid,' L=STOP "',TRIM(log_event%place),'" sum=', &
192                                         log_event%sum,' mtime=',log_event%mtime
193             CALL message( 'cpu_log', 'PA0178', 0, 1, -1, 6, 0 )
194             first = .FALSE.
195          ENDIF
196          log_event%vector   = log_event%vector + log_event%mtimevec
197          log_event%counts   = log_event%counts + 1
198          log_event%isum     = 0.0
199          log_event%ivect    = 0.0
200       ELSE
201          message_string = 'unknown modus of time measurement: ' // TRIM( modus )
202          CALL message( 'cpu_log', 'PA0179', 0, 1, -1, 6, 0 )
[1]203       ENDIF
[1318]204
205    END SUBROUTINE cpu_log
206
207
208    SUBROUTINE cpu_statistics
209!------------------------------------------------------------------------------!
210! Description:
211! ------------
212! Analysis and output of the cpu-times measured. All PE results are collected
213! on PE0 in order to calculate the mean cpu-time over all PEs and other
214! statistics. The output is sorted according to the amount of cpu-time consumed
215! and output on PE0.
216!------------------------------------------------------------------------------!
217
218       IMPLICIT NONE
219
220       INTEGER    ::  i, ii(1), iii, sender
221       REAL       ::  average_cputime
222       REAL, SAVE ::  norm = 1.0
223       REAL, DIMENSION(:),   ALLOCATABLE ::  pe_max, pe_min, pe_rms, sum
224       REAL, DIMENSION(:,:), ALLOCATABLE ::  pe_log_points
225
226
227!
228!--    Compute cpu-times in seconds
229       log_point%mtime  = log_point%mtime  / norm
230       log_point%sum    = log_point%sum    / norm
231       log_point%vector = log_point%vector / norm
232       WHERE ( log_point%counts /= 0 )
233          log_point%mean = log_point%sum / log_point%counts
234       END WHERE
235
236
237!
238!--    Collect cpu-times from all PEs and calculate statistics
239       IF ( myid == 0 )  THEN
240!
241!--       Allocate and initialize temporary arrays needed for statistics
242          ALLOCATE( pe_max( SIZE( log_point ) ), pe_min( SIZE( log_point ) ), &
243                    pe_rms( SIZE( log_point ) ),                              &
244                    pe_log_points( SIZE( log_point ), 0:numprocs-1 ) )
245          pe_min = log_point%sum
246          pe_max = log_point%sum    ! need to be set in case of 1 PE
247          pe_rms = 0.0
248
249#if defined( __parallel )
250!
251!--       Receive data from all PEs
252          DO  i = 1, numprocs-1
253             CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL, &
254                            i, i, comm2d, status, ierr )
255             sender = status(MPI_SOURCE)
256             pe_log_points(:,sender) = pe_max
257          ENDDO
258          pe_log_points(:,0) = log_point%sum   ! Results from PE0
259!
260!--       Calculate mean of all PEs, store it on log_point%sum
261!--       and find minimum and maximum
262          DO  iii = 1, SIZE( log_point )
263             DO  i = 1, numprocs-1
264                log_point(iii)%sum = log_point(iii)%sum + pe_log_points(iii,i)
265                pe_min(iii) = MIN( pe_min(iii), pe_log_points(iii,i) )
266                pe_max(iii) = MAX( pe_max(iii), pe_log_points(iii,i) )
267             ENDDO
268             log_point(iii)%sum = log_point(iii)%sum / numprocs
269!
270!--          Calculate rms
271             DO  i = 0, numprocs-1
272                pe_rms(iii) = pe_rms(iii) + ( &
273                                    pe_log_points(iii,i) - log_point(iii)%sum &
274                                            )**2
275             ENDDO
276             pe_rms(iii) = SQRT( pe_rms(iii) / numprocs )
277          ENDDO
278       ELSE
279!
280!--       Send data to PE0 (pe_max is used as temporary storage to send
281!--       the data in order to avoid sending the data type log)
282          ALLOCATE( pe_max( SIZE( log_point ) ) )
283          pe_max = log_point%sum
284          CALL MPI_SEND( pe_max(1), SIZE( log_point ), MPI_REAL, 0, myid, comm2d, &
285                         ierr )
286#endif
287
[1]288       ENDIF
[1318]289
290!
291!--    Write cpu-times
292       IF ( myid == 0 )  THEN
293!
294!--       Re-store sums
295          ALLOCATE( sum( SIZE( log_point ) ) )
296          WHERE ( log_point%counts /= 0 )
297             sum = log_point%sum
298          ELSEWHERE
299             sum = -1.0
300          ENDWHERE
301
302!
303!--       Get total time in order to calculate CPU-time per gridpoint and timestep
304          IF ( nr_timesteps_this_run /= 0 )  THEN
305             average_cputime = log_point(1)%sum / REAL( (nx+1) * (ny+1) * nz ) / &
306                               REAL( nr_timesteps_this_run ) * 1E6  ! in micro-sec
307          ELSE
308             average_cputime = -1.0
309          ENDIF
310
311!
312!--       Write cpu-times sorted by size
313          CALL check_open( 18 )
314#if defined( __parallel )
315          WRITE ( 18, 100 )  TRIM( run_description_header ),                          &
316                             numprocs * threads_per_task, pdims(1), pdims(2),         &
317                             threads_per_task, nx+1, ny+1, nz, nr_timesteps_this_run, &
318                             average_cputime
319
320          IF ( num_acc_per_node /= 0 )  WRITE ( 18, 108 )  num_acc_per_node
321          WRITE ( 18, 110 )
322#else
323          WRITE ( 18, 100 )  TRIM( run_description_header ),                          &
324                             numprocs * threads_per_task, 1, 1,                       &
325                             threads_per_task, nx+1, ny+1, nz, nr_timesteps_this_run, &
326                             average_cputime
327
328          IF ( num_acc_per_node /= 0 )  WRITE ( 18, 109 )  num_acc_per_node
329          WRITE ( 18, 110 )
330#endif
331          DO
332             ii = MAXLOC( sum )
333             i = ii(1)
334             IF ( sum(i) /= -1.0 )  THEN
335                WRITE ( 18, 102 ) &
336              log_point(i)%place, log_point(i)%sum,                &
337                   log_point(i)%sum / log_point(1)%sum * 100.0,         &
338                   log_point(i)%counts, pe_min(i), pe_max(i), pe_rms(i)
339                sum(i) = -1.0
340             ELSE
341                EXIT
342             ENDIF
343          ENDDO
[1]344       ENDIF
345
346
[1318]347!
348!--    The same procedure again for the individual measurements.
349!
350!--    Compute cpu-times in seconds
351       log_point_s%mtime  = log_point_s%mtime  / norm
352       log_point_s%sum    = log_point_s%sum    / norm
353       log_point_s%vector = log_point_s%vector / norm
354       WHERE ( log_point_s%counts /= 0 )
355          log_point_s%mean = log_point_s%sum / log_point_s%counts
356       END WHERE
357
358!
359!--    Collect cpu-times from all PEs and calculate statistics
360#if defined( __parallel )
361!
362!--    Set barrier in order to avoid that PE0 receives log_point_s-data
363!--    while still busy with receiving log_point-data (see above)
364       CALL MPI_BARRIER( comm2d, ierr )
365#endif
366       IF ( myid == 0 )  THEN
367!
368!--       Initialize temporary arrays needed for statistics
369          pe_min = log_point_s%sum
370          pe_max = log_point_s%sum    ! need to be set in case of 1 PE
371          pe_rms = 0.0
372
373#if defined( __parallel )
374!
375!--       Receive data from all PEs
376          DO  i = 1, numprocs-1
377             CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL, &
378                            MPI_ANY_SOURCE, MPI_ANY_TAG, comm2d, status, ierr )
379             sender = status(MPI_SOURCE)
380             pe_log_points(:,sender) = pe_max
381          ENDDO
382          pe_log_points(:,0) = log_point_s%sum   ! Results from PE0
383!
384!--       Calculate mean of all PEs, store it on log_point_s%sum
385!--       and find minimum and maximum
386          DO  iii = 1, SIZE( log_point )
387             DO  i = 1, numprocs-1
388                log_point_s(iii)%sum = log_point_s(iii)%sum + pe_log_points(iii,i)
389                pe_min(iii) = MIN( pe_min(iii), pe_log_points(iii,i) )
390                pe_max(iii) = MAX( pe_max(iii), pe_log_points(iii,i) )
391             ENDDO
392             log_point_s(iii)%sum = log_point_s(iii)%sum / numprocs
393!
394!--          Calculate rms
395             DO  i = 0, numprocs-1
396                pe_rms(iii) = pe_rms(iii) + ( &
397                                    pe_log_points(iii,i) - log_point_s(iii)%sum &
398                                            )**2
399             ENDDO
400             pe_rms(iii) = SQRT( pe_rms(iii) / numprocs )
401          ENDDO
402       ELSE
403!
404!--       Send data to PE0 (pe_max is used as temporary storage to send
405!--       the data in order to avoid sending the data type log)
406          pe_max = log_point_s%sum
407          CALL MPI_SEND( pe_max(1), SIZE( log_point ), MPI_REAL, 0, 0, comm2d, &
408                         ierr )
409#endif
410
411       ENDIF
412
413!
414!--    Write cpu-times
415       IF ( myid == 0 )  THEN
416!
417!--       Re-store sums
418          WHERE ( log_point_s%counts /= 0 )
419             sum = log_point_s%sum
420          ELSEWHERE
421             sum = -1.0
422          ENDWHERE
423
424!
425!--       Write cpu-times sorted by size
426          WRITE ( 18, 101 )
427          DO
428             ii = MAXLOC( sum )
429             i = ii(1)
430             IF ( sum(i) /= -1.0 )  THEN
431                WRITE ( 18, 102 ) &
432                   log_point_s(i)%place, log_point_s(i)%sum, &
433                   log_point_s(i)%sum / log_point(1)%sum * 100.0, &
434                   log_point_s(i)%counts, pe_min(i), pe_max(i), pe_rms(i)
435                sum(i) = -1.0
436             ELSE
437                EXIT
438             ENDIF
439          ENDDO
440
441!
442!--       Output of handling of MPI operations
443          IF ( collective_wait )  THEN
444             WRITE ( 18, 103 )
445          ELSE
446             WRITE ( 18, 104 )
447          ENDIF
448          IF ( cpu_log_barrierwait )  WRITE ( 18, 111 )
449          IF ( synchronous_exchange )  THEN
450             WRITE ( 18, 105 )
451          ELSE
452             WRITE ( 18, 106 )
453          ENDIF
454
455!
456!--       Empty lines in order to create a gap to the results of the model
457!--       continuation runs
458          WRITE ( 18, 107 )
459
460!
461!--       Unit 18 is not needed anymore
462          CALL close_file( 18 )
463
464       ENDIF
465
466
467   100 FORMAT (A/11('-')//'CPU measures for ',I5,' PEs (',I5,'(x) * ',I5,'(y', &
468               &') tasks *',I5,' threads):'//                                  &
469               'gridpoints (x/y/z): ',20X,I5,' * ',I5,' * ',I5/                &
470               'nr of timesteps: ',22X,I6/                                     &
471               'cpu time per grid point and timestep: ',5X,F8.5,' * 10**-6 s')
472
473   101 FORMAT (/'special measures:'/ &
474               &'-----------------------------------------------------------', &
475               &'--------------------')
476
477   102 FORMAT (A20,2X,F9.3,2X,F7.2,1X,I7,3(1X,F9.3))
478   103 FORMAT (/'Barriers are set in front of collective operations')
479   104 FORMAT (/'No barriers are set in front of collective operations')
480   105 FORMAT (/'Exchange of ghostpoints via MPI_SENDRCV')
481   106 FORMAT (/'Exchange of ghostpoints via MPI_ISEND/MPI_IRECV')
482   107 FORMAT (//)
483   108 FORMAT ('Accelerator boards per node: ',14X,I2)
484   109 FORMAT ('Accelerator boards: ',23X,I2)
485   110 FORMAT ('----------------------------------------------------------',   &
486               &'------------'//&
487               &'place:                        mean        counts      min  ', &
488               &'     max       rms'/ &
489               &'                           sec.      %                sec. ', &
490               &'     sec.      sec.'/  &
491               &'-----------------------------------------------------------', &
492               &'-------------------')
493   111 FORMAT (/'Barriers are set at beginning (start/continue) of measurements')
494
495    END SUBROUTINE cpu_statistics
496
497 END MODULE cpulog
Note: See TracBrowser for help on using the repository browser.