module_timing.F
References to this file elsewhere.
1 !WRF:DRIVER_LAYER:UTIL
2 !
3
4 MODULE module_timing
5
6 INTEGER, PARAMETER, PRIVATE :: cnmax = 30
7 INTEGER, PRIVATE, DIMENSION(cnmax) :: count_int1 , count_rate_int1 , count_max_int1
8 INTEGER, PRIVATE, DIMENSION(cnmax) :: count_int2 , count_rate_int2 , count_max_int2
9 INTEGER, PRIVATE :: cn = 0
10 REAL, PRIVATE :: elapsed_seconds , elapsed_seconds_total = 0
11 REAL, PRIVATE :: cpu_1 , cpu_2 , cpu_seconds , cpu_seconds_total = 0
12
13 CONTAINS
14
15 SUBROUTINE init_module_timing
16 cn = 0
17 END SUBROUTINE init_module_timing
18
19
20 SUBROUTINE start_timing
21
22 IMPLICIT NONE
23
24 cn = cn + 1
25 IF ( cn .gt. cnmax ) THEN
26 CALL wrf_error_fatal( 'module_timing: clock nesting error (too many nests)' )
27 RETURN
28 ENDIF
29 CALL SYSTEM_CLOCK ( count_int1(cn) , count_rate_int1(cn) , count_max_int1(cn) )
30 ! CALL CPU_TIME ( cpu_1 )
31
32 END SUBROUTINE start_timing
33
34
35 SUBROUTINE end_timing ( string )
36
37 IMPLICIT NONE
38
39 CHARACTER *(*) :: string
40
41 IF ( cn .lt. 1 ) THEN
42 CALL wrf_error_fatal( 'module_timing: clock nesting error, cn<1' )
43 ELSE IF ( cn .gt. cnmax ) THEN
44 CALL wrf_error_fatal( 'module_timing: clock nesting error, cn>cnmax' )
45 ENDIF
46
47 CALL SYSTEM_CLOCK ( count_int2(cn) , count_rate_int2(cn) , count_max_int2(cn) )
48 ! CALL CPU_TIME ( cpu_2 )
49
50 IF ( count_int2(cn) < count_int1(cn) ) THEN
51 count_int2(cn) = count_int2(cn) + count_max_int2(cn)
52 ENDIF
53
54 count_int2(cn) = count_int2(cn) - count_int1(cn)
55 elapsed_seconds = REAL(count_int2(cn)) / REAL(count_rate_int2(cn))
56 elapsed_seconds_total = elapsed_seconds_total + elapsed_seconds
57
58 WRITE(6,'(A,A,A,F10.5,A)') 'Timing for ',TRIM(string),': ',elapsed_seconds,' elapsed seconds.'
59 #if defined(DM_PARALLEL) && ! defined(STUBMPI)
60 WRITE(0,'(A,A,A,F10.5,A)') 'Timing for ',TRIM(string),': ',elapsed_seconds,' elapsed seconds.'
61 #endif
62
63 ! cpu_seconds = cpu_2 - cpu_1
64 ! cpu_seconds_total = cpu_seconds_total + cpu_seconds
65 ! PRINT '(A,A,A,F10.5,A)' ,'Timing for ',TRIM(string),': ',cpu_seconds,' cpu seconds.'
66
67 cn = cn - 1
68
69 END SUBROUTINE end_timing
70
71 END MODULE module_timing
72