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

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

REAL constants provided with KIND-attribute

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