source: tags/ORCHIDEE/src_parallel/timer.f90 @ 6

Last change on this file since 6 was 6, checked in by orchidee, 14 years ago

import first tag equivalent to CVS orchidee_1_9_5 + OOL_1_9_5

File size: 4.0 KB
Line 
1! Timer functions to calculate MPI use speed up.
2
3!-
4!- $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_parallel/timer.f90,v 1.2 2007/06/12 08:04:26 ssipsl Exp $
5!-
6
7MODULE timer
8
9  USE constantes
10 
11  INTEGER, PARAMETER :: nb_timer=2
12  INTEGER, PARAMETER :: timer_global=1
13  INTEGER, PARAMETER :: timer_mpi=2
14  INTEGER, PARAMETER :: stopped = 1
15  INTEGER, PARAMETER :: running = 2
16  INTEGER, PARAMETER :: suspended = 3
17 
18  DOUBLE PRECISION, DIMENSION(nb_timer),SAVE :: cpu_timer
19  DOUBLE PRECISION, DIMENSION(nb_timer),SAVE :: real_timer
20  INTEGER, DIMENSION(nb_timer),SAVE :: timer_state
21  DOUBLE PRECISION, DIMENSION(nb_timer),SAVE :: last_cpu_time
22  INTEGER, DIMENSION(nb_timer),SAVE :: last_real_time
23 
24 
25 
26 
27  CONTAINS
28 
29  SUBROUTINE init_timer
30  IMPLICIT NONE
31   
32    cpu_timer(:)=0.
33    real_timer(:)=0.
34    timer_state(:)=stopped
35    last_cpu_time(:)=0.
36    last_real_time(:)=0
37   
38  END SUBROUTINE init_timer
39 
40 
41  SUBROUTINE start_timer(no_timer)
42  IMPLICIT NONE
43     INTEGER :: no_timer
44     DOUBLE PRECISION :: x
45     
46     IF (timer_state(no_timer)/=stopped) THEN
47       STOP 'start_timer :: timer is already running or suspended'
48     ELSE
49        timer_state(no_timer)=running
50     ENDIF
51     
52     cpu_timer(no_timer)=0. 
53     real_timer(no_timer)=0.
54     x=Diff_real_time(no_timer)
55     x=Diff_cpu_time(no_timer)
56     
57  END SUBROUTINE start_timer
58 
59 
60 
61  SUBROUTINE stop_timer(no_timer)
62  IMPLICIT NONE
63    INTEGER :: no_timer
64   
65     IF (timer_state(no_timer)==running) THEN
66        CALL suspend_timer(no_timer)
67     ELSE IF (timer_state(no_timer)==stopped) THEN
68       WRITE(numout,*) 'stop_timer :: timer is already stopped'
69     ENDIF
70
71     timer_state(no_timer)=stopped
72
73  END SUBROUTINE stop_timer
74 
75 
76 
77  SUBROUTINE resume_timer(no_timer)
78  IMPLICIT NONE
79    INTEGER :: no_timer
80    DOUBLE PRECISION :: x
81     IF (timer_state(no_timer)/=suspended) THEN
82       STOP 'resume_timer :: timer is not suspended'
83     ELSE
84        timer_state(no_timer)=running
85     ENDIF
86 
87     x=Diff_cpu_time(no_timer)
88     x=Diff_real_time(no_timer) 
89 
90  END SUBROUTINE resume_timer
91 
92 
93 
94  SUBROUTINE suspend_timer(no_timer)
95 
96    IMPLICIT NONE
97    INTEGER :: no_timer
98   
99     IF (timer_state(no_timer)/=running) THEN
100       STOP 'suspend_timer :: timer is not running'
101     ELSE
102        timer_state(no_timer)=suspended
103     ENDIF
104 
105     cpu_timer(no_timer)=cpu_timer(no_timer)+Diff_cpu_time(no_timer)
106     real_timer(no_timer)=real_timer(no_timer)+Diff_real_time(no_timer)
107 
108  END SUBROUTINE suspend_timer
109 
110 
111  FUNCTION diff_real_time(no_timer)
112  IMPLICIT NONE
113    INTEGER :: no_timer
114    DOUBLE PRECISION :: Diff_real_Time
115    integer :: Last_Count,count,count_rate,count_max
116   
117    Last_Count=Last_real_time(no_timer)
118   
119    call system_clock(count,count_rate,count_max)
120    if (Count>=Last_Count) then
121      Diff_real_time=(1.*(Count-last_Count))/count_rate
122    else
123      Diff_real_time=(1.*(Count-last_Count+Count_max))/count_rate
124    endif
125    Last_real_time(no_timer)=Count
126   
127  END FUNCTION diff_real_time
128 
129  function Diff_Cpu_Time(no_timer)
130  implicit none
131    INTEGER :: no_timer
132    DOUBLE PRECISION :: Diff_Cpu_Time
133    DOUBLE PRECISION :: Last_Count,Count
134   
135    Last_Count=Last_cpu_time(no_timer)
136   
137    call cpu_time(Count)
138    Diff_Cpu_Time=Count-Last_Count
139    Last_cpu_time(no_timer)=Count
140   
141  end function Diff_Cpu_Time
142 
143  FUNCTION Get_cpu_time(no_timer)
144  IMPLICIT NONE
145  INTEGER :: no_timer
146  DOUBLE PRECISION :: Get_cpu_time
147 
148    IF (timer_state(no_timer)==running) THEN
149      CALL suspend_timer(no_timer)
150      Get_cpu_time=cpu_timer(no_timer)
151      CALL resume_timer(no_timer)
152    ELSE
153      Get_cpu_time=cpu_timer(no_timer)
154    ENDIF
155   
156  END FUNCTION Get_cpu_time
157 
158  FUNCTION Get_real_time(no_timer)
159  IMPLICIT NONE
160  INTEGER :: no_timer
161  DOUBLE PRECISION :: Get_real_time
162 
163    IF (timer_state(no_timer)==running) THEN
164      CALL suspend_timer(no_timer)
165      Get_real_time=real_timer(no_timer)
166      CALL resume_timer(no_timer)
167    ELSE
168      Get_real_time=real_timer(no_timer)
169    ENDIF
170 
171  END FUNCTION Get_real_time
172 
173END MODULE Timer
174 
Note: See TracBrowser for help on using the repository browser.