source: branches/publications/ORCHIDEE-LEAK-r5919/src_parallel/timer.f90 @ 5925

Last change on this file since 5925 was 1925, checked in by josefine.ghattas, 10 years ago
  • xios : adapted for use with OpenMP (only master thread do call to xios), added coherence check between cpp key XIOS and run time flag
  • mod_orchidee_para : moved declaration part into mod_orchidee_para_var
  • simplifications in the use of modules in src_parallel : only use mod_orchidee_para_var if this is sufficient
  • small corrections for OpenMP
  • Property svn:keywords set to HeadURL Date Author Revision
File size: 4.0 KB
Line 
1! Timer functions to calculate MPI use speed up.
2
3!-
4!< $HeadURL$
5!< $Date$
6!< $Author$
7!< $Revision$
8!-
9
10MODULE timer
11
12  USE mod_orchidee_para_var, ONLY : numout
13 
14  INTEGER, PARAMETER :: nb_timer=2
15  INTEGER, PARAMETER :: timer_global=1
16  INTEGER, PARAMETER :: timer_mpi=2
17  INTEGER, PARAMETER :: stopped = 1
18  INTEGER, PARAMETER :: running = 2
19  INTEGER, PARAMETER :: suspended = 3
20 
21  DOUBLE PRECISION, DIMENSION(nb_timer),SAVE :: cpu_timer
22  DOUBLE PRECISION, DIMENSION(nb_timer),SAVE :: real_timer
23  INTEGER, DIMENSION(nb_timer),SAVE :: timer_state
24  DOUBLE PRECISION, DIMENSION(nb_timer),SAVE :: last_cpu_time
25  INTEGER, DIMENSION(nb_timer),SAVE :: last_real_time
26 
27 
28 
29 
30  CONTAINS
31 
32  SUBROUTINE init_timer
33  IMPLICIT NONE
34   
35    cpu_timer(:)=0.
36    real_timer(:)=0.
37    timer_state(:)=stopped
38    last_cpu_time(:)=0.
39    last_real_time(:)=0
40   
41  END SUBROUTINE init_timer
42 
43 
44  SUBROUTINE start_timer(no_timer)
45  IMPLICIT NONE
46     INTEGER :: no_timer
47     DOUBLE PRECISION :: x
48     
49     IF (timer_state(no_timer)/=stopped) THEN
50       STOP 'start_timer :: timer is already running or suspended'
51     ELSE
52        timer_state(no_timer)=running
53     ENDIF
54     
55     cpu_timer(no_timer)=0. 
56     real_timer(no_timer)=0.
57     x=Diff_real_time(no_timer)
58     x=Diff_cpu_time(no_timer)
59     
60  END SUBROUTINE start_timer
61 
62 
63 
64  SUBROUTINE stop_timer(no_timer)
65  IMPLICIT NONE
66    INTEGER :: no_timer
67   
68     IF (timer_state(no_timer)==running) THEN
69        CALL suspend_timer(no_timer)
70     ELSE IF (timer_state(no_timer)==stopped) THEN
71       WRITE(numout,*) 'stop_timer :: timer is already stopped'
72     ENDIF
73
74     timer_state(no_timer)=stopped
75
76  END SUBROUTINE stop_timer
77 
78 
79 
80  SUBROUTINE resume_timer(no_timer)
81  IMPLICIT NONE
82    INTEGER :: no_timer
83    DOUBLE PRECISION :: x
84     IF (timer_state(no_timer)/=suspended) THEN
85       STOP 'resume_timer :: timer is not suspended'
86     ELSE
87        timer_state(no_timer)=running
88     ENDIF
89 
90     x=Diff_cpu_time(no_timer)
91     x=Diff_real_time(no_timer) 
92 
93  END SUBROUTINE resume_timer
94 
95 
96 
97  SUBROUTINE suspend_timer(no_timer)
98 
99    IMPLICIT NONE
100    INTEGER :: no_timer
101   
102     IF (timer_state(no_timer)/=running) THEN
103       STOP 'suspend_timer :: timer is not running'
104     ELSE
105        timer_state(no_timer)=suspended
106     ENDIF
107 
108     cpu_timer(no_timer)=cpu_timer(no_timer)+Diff_cpu_time(no_timer)
109     real_timer(no_timer)=real_timer(no_timer)+Diff_real_time(no_timer)
110 
111  END SUBROUTINE suspend_timer
112 
113 
114  FUNCTION diff_real_time(no_timer)
115  IMPLICIT NONE
116    INTEGER :: no_timer
117    DOUBLE PRECISION :: Diff_real_Time
118    integer :: Last_Count,count,count_rate,count_max
119   
120    Last_Count=Last_real_time(no_timer)
121   
122    call system_clock(count,count_rate,count_max)
123    if (Count>=Last_Count) then
124      Diff_real_time=(1.*(Count-last_Count))/count_rate
125    else
126      Diff_real_time=(1.*(Count-last_Count+Count_max))/count_rate
127    endif
128    Last_real_time(no_timer)=Count
129   
130  END FUNCTION diff_real_time
131 
132  function Diff_Cpu_Time(no_timer)
133  implicit none
134    INTEGER :: no_timer
135    DOUBLE PRECISION :: Diff_Cpu_Time
136    DOUBLE PRECISION :: Last_Count,Count
137   
138    Last_Count=Last_cpu_time(no_timer)
139   
140    call cpu_time(Count)
141    Diff_Cpu_Time=Count-Last_Count
142    Last_cpu_time(no_timer)=Count
143   
144  end function Diff_Cpu_Time
145 
146  FUNCTION Get_cpu_time(no_timer)
147  IMPLICIT NONE
148  INTEGER :: no_timer
149  DOUBLE PRECISION :: Get_cpu_time
150 
151    IF (timer_state(no_timer)==running) THEN
152      CALL suspend_timer(no_timer)
153      Get_cpu_time=cpu_timer(no_timer)
154      CALL resume_timer(no_timer)
155    ELSE
156      Get_cpu_time=cpu_timer(no_timer)
157    ENDIF
158   
159  END FUNCTION Get_cpu_time
160 
161  FUNCTION Get_real_time(no_timer)
162  IMPLICIT NONE
163  INTEGER :: no_timer
164  DOUBLE PRECISION :: Get_real_time
165 
166    IF (timer_state(no_timer)==running) THEN
167      CALL suspend_timer(no_timer)
168      Get_real_time=real_timer(no_timer)
169      CALL resume_timer(no_timer)
170    ELSE
171      Get_real_time=real_timer(no_timer)
172    ENDIF
173 
174  END FUNCTION Get_real_time
175 
176END MODULE Timer
177 
Note: See TracBrowser for help on using the repository browser.