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

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

last commit documented

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