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

Last change on this file since 1360 was 1354, checked in by heinze, 10 years ago

last commit documented

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