Merge remote-tracking branch 'origin/release-v4.6.1'
[WRF.git] / frame / module_timing.F
blobe8dfe883f0cd033ce73e42efaa4306712cc96442
1 !WRF:DRIVER_LAYER:UTIL
4 MODULE module_timing
6    INTEGER, PARAMETER, PRIVATE :: cnmax = 30
7    INTEGER, PRIVATE :: cn = 0 
8    REAL, PRIVATE    :: elapsed_seconds , elapsed_seconds_total = 0
10 #if defined(OLD_TIMERS)
11    INTEGER, PRIVATE, DIMENSION(cnmax) :: count_int1 , count_rate_int1 , count_max_int1
12    INTEGER, PRIVATE, DIMENSION(cnmax) :: count_int2 , count_rate_int2 , count_max_int2
13    REAL, PRIVATE    :: cpu_1 , cpu_2 , cpu_seconds , cpu_seconds_total = 0
14 #else
15    REAL(kind=8) :: epoch_seconds_hires(cnmax)
16 #endif
18 CONTAINS
20    SUBROUTINE init_module_timing
21 #if defined(OLD_TIMERS)
22       ! Nothing to do here.
23 #else
24       ! Initialize the high-res timer.  This is optional, but will allow
25       ! higher precision.  Read hires_timer.c for details.
26       call init_hires_timer()
27 #endif
28       cn = 0
29    END SUBROUTINE init_module_timing
32    SUBROUTINE start_timing
33      use module_wrf_error, only: silence
35       IMPLICIT NONE
37       if(silence/=0) return
38       cn = cn + 1
39       IF ( cn .gt. cnmax ) THEN
40         CALL wrf_error_fatal( 'module_timing: clock nesting error (too many nests)' )
41         RETURN
42       ENDIF
44 #if defined(OLD_TIMERS)
45       CALL SYSTEM_CLOCK ( count_int1(cn) , count_rate_int1(cn) , count_max_int1(cn) )
46 !     CALL CPU_TIME ( cpu_1 )
47 #else
48       call hires_timer(epoch_seconds_hires(cn))
49 #endif
51    END SUBROUTINE start_timing
54    SUBROUTINE end_timing ( string )
55      use module_wrf_error, only: silence, stderrlog, buffered
56    
57       IMPLICIT NONE
58       REAL(kind=8) :: now_hires
59       CHARACTER *(*) :: string
60       character*512 :: buf
62       if(silence/=0) return
64       IF ( cn .lt. 1 ) THEN
65         CALL wrf_error_fatal( 'module_timing: clock nesting error, cn<1' ) 
66       ELSE IF ( cn .gt. cnmax ) THEN
67         CALL wrf_error_fatal( 'module_timing: clock nesting error, cn>cnmax' ) 
68       ENDIF
70 #if defined(OLD_TIMERS)
71       CALL SYSTEM_CLOCK ( count_int2(cn) , count_rate_int2(cn) , count_max_int2(cn) )
72 !     CALL CPU_TIME ( cpu_2 )
74       IF ( count_int2(cn) < count_int1(cn) ) THEN
75          count_int2(cn) = count_int2(cn) + count_max_int2(cn)
76       ENDIF
78       count_int2(cn) = count_int2(cn) - count_int1(cn)
79       elapsed_seconds = REAL(count_int2(cn)) / REAL(count_rate_int2(cn))
80 #else
81       call hires_timer(now_hires)
82       ! The REAL() here should convert to default real from REAL(kind=8)
83       elapsed_seconds = REAL(now_hires-epoch_seconds_hires(cn))
84 #endif
85       elapsed_seconds_total = elapsed_seconds_total + elapsed_seconds
87 3031 format("Timing for ",A,": ",F10.5," elapsed seconds")
88       if(buffered/=0) then
89          write(buf,3031) TRIM(string),elapsed_seconds
90          call wrf_message(buf)
91       else
92          if(stderrlog/=0) &
93               write(0,3031) TRIM(string),elapsed_seconds
94          write(6,3031) TRIM(string),elapsed_seconds
95       endif
97 !     cpu_seconds = cpu_2 - cpu_1
98 !     cpu_seconds_total = cpu_seconds_total + cpu_seconds
99 !     PRINT '(A,A,A,F10.5,A)' ,'Timing for ',TRIM(string),': ',cpu_seconds,' cpu seconds.'
101       cn = cn - 1
103    END SUBROUTINE end_timing
105    FUNCTION now_time() result(timef)
106      ! This is a simple subroutine that returns the current time in
107      ! seconds since some arbitrary reference point.  This routine is
108      ! meant to be used to accumulate timing information.  See solve_nmm
109      ! for examples.
110      implicit none
111      real*8 :: timef
112 #if defined(OLD_TIMERS)
113      integer :: ic,ir
114      call system_clock(count=ic,count_rate=ir)
115      timef=real(ic)/real(ir)
116 #else
117      call hires_timer(timef)
118 #endif
119    END FUNCTION now_time
121 END MODULE module_timing