source: LMDZ6/trunk/libf/dyn3dmem/times.f90 @ 5300

Last change on this file since 5300 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 7.1 KB
Line 
1module times
2  integer,private,save :: Last_Count=0
3  real, private,save :: Last_cpuCount=0
4  logical, private,save :: AllTimer_IsActive=.false.
5 
6  integer, parameter :: nb_timer = 4
7  integer, parameter :: timer_caldyn  = 1
8  integer, parameter :: timer_vanleer = 2
9  integer, parameter :: timer_dissip = 3
10  integer, parameter :: timer_physic = 4
11  integer, parameter :: stopped = 1
12  integer, parameter :: running = 2
13  integer, parameter :: suspended = 3
14 
15  integer :: max_size
16  real,    allocatable, dimension(:,:,:) :: timer_table
17  real,    allocatable, dimension(:,:,:) :: timer_table_sqr
18  integer, allocatable, dimension(:,:,:) :: timer_iteration
19  real,    allocatable, dimension(:,:,:) :: timer_average
20  real,    allocatable, dimension(:,:,:) :: timer_delta
21  real,    allocatable,dimension(:) :: timer_running, last_time
22  integer, allocatable,dimension(:) :: timer_state
23 
24  contains
25 
26  subroutine init_timer
27    USE parallel_lmdz
28    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
29USE paramet_mod_h
30implicit none
31
32
33   
34    max_size=jjm+1
35    allocate(timer_table(max_size,nb_timer,0:mpi_size-1))
36    allocate(timer_table_sqr(max_size,nb_timer,0:mpi_size-1))
37    allocate(timer_iteration(max_size,nb_timer,0:mpi_size-1))
38    allocate(timer_average(max_size,nb_timer,0:mpi_size-1))
39    allocate(timer_delta(max_size,nb_timer,0:mpi_size-1))
40    allocate(timer_running(nb_timer))
41    allocate(timer_state(nb_timer))
42    allocate(last_time(nb_timer))
43   
44    timer_table(:,:,:)=0
45    timer_table_sqr(:,:,:)=0
46    timer_iteration(:,:,:)=0
47    timer_average(:,:,:)=0
48    timer_delta(:,:,:)=0
49    timer_state(:)=stopped     
50  end subroutine init_timer
51 
52  subroutine start_timer(no_timer)
53    implicit none
54    integer :: no_timer
55   
56    if (AllTimer_IsActive) then
57   
58      if (timer_state(no_timer)/=stopped) then
59        CALL abort_gcm("times","start_timer :: timer is already running or suspended",1)
60      else
61        timer_state(no_timer)=running
62      endif
63     
64      timer_running(no_timer)=0
65      call cpu_time(last_time(no_timer))
66   
67    endif
68   
69  end subroutine start_timer
70 
71  subroutine suspend_timer(no_timer)
72    implicit none
73    integer :: no_timer
74     
75    if (AllTimer_IsActive) then   
76      if (timer_state(no_timer)/=running) then
77         CALL abort_gcm("times","suspend_timer :: timer is not running",1)
78      else
79        timer_state(no_timer)=suspended
80      endif
81   
82      timer_running(no_timer)=timer_running(no_timer)-last_time(no_timer)
83      call cpu_time(last_time(no_timer))
84      timer_running(no_timer)=timer_running(no_timer)+last_time(no_timer)
85    endif
86  end subroutine suspend_timer
87 
88  subroutine resume_timer(no_timer)
89    implicit none
90    integer :: no_timer
91     
92    if (AllTimer_IsActive) then   
93      if (timer_state(no_timer)/=suspended) then
94        CALL abort_gcm("times","resume_timer :: timer is not suspended",1)
95      else
96        timer_state(no_timer)=running
97      endif
98     
99      call cpu_time(last_time(no_timer))
100    endif
101   
102  end subroutine resume_timer
103
104  subroutine stop_timer(no_timer)
105    USE parallel_lmdz
106    implicit none
107    integer :: no_timer
108    integer :: N
109    real :: V,V2
110   
111    if (AllTimer_IsActive) then
112       
113      if (timer_state(no_timer)/=running) then
114        CALL abort_gcm("times","stop_timer :: timer is not running",1)
115      else
116        timer_state(no_timer)=stopped
117      endif
118   
119      timer_running(no_timer)=timer_running(no_timer)-last_time(no_timer)
120      call cpu_time(last_time(no_timer))
121      timer_running(no_timer)=timer_running(no_timer)+last_time(no_timer)
122   
123      timer_table(jj_nb,no_timer,mpi_rank)=timer_table(jj_nb,no_timer,mpi_rank)+timer_running(no_timer)
124      timer_table_sqr(jj_nb,no_timer,mpi_rank)=timer_table_sqr(jj_nb,no_timer,mpi_rank)+timer_running(no_timer)**2
125      timer_iteration(jj_nb,no_timer,mpi_rank)=timer_iteration(jj_nb,no_timer,mpi_rank)+1
126      timer_average(jj_nb,no_timer,mpi_rank)=timer_table(jj_nb,no_timer,mpi_rank)/timer_iteration(jj_nb,no_timer,mpi_rank)
127      if (timer_iteration(jj_nb,no_timer,mpi_rank)>=2) then
128        N=timer_iteration(jj_nb,no_timer,mpi_rank)
129        V2=timer_table_sqr(jj_nb,no_timer,mpi_rank)
130        V=timer_table(jj_nb,no_timer,mpi_rank)
131        timer_delta(jj_nb,no_timer,mpi_rank)=sqrt(ABS(V2-V*V/N)/(N-1))
132      else
133        timer_delta(jj_nb,no_timer,mpi_rank)=0
134      endif
135    endif
136   
137  end subroutine stop_timer
138   
139  subroutine allgather_timer
140    USE parallel_lmdz
141    USE lmdz_mpi
142    implicit none
143
144    integer :: ierr
145    integer :: data_size
146    real, allocatable,dimension(:,:) :: tmp_table
147
148    IF (using_mpi) THEN   
149   
150      if (AllTimer_IsActive) then
151   
152   
153      allocate(tmp_table(max_size,nb_timer))
154   
155      data_size=max_size*nb_timer
156   
157      tmp_table(:,:)=timer_table(:,:,mpi_rank)
158      call mpi_allgather(tmp_table(1,1),data_size,MPI_REAL_LMDZ,timer_table(1,1,0),data_size,MPI_REAL_LMDZ,COMM_LMDZ,ierr)
159      tmp_table(:,:)=timer_table_sqr(:,:,mpi_rank)
160      call mpi_allgather(tmp_table(1,1),data_size,MPI_REAL_LMDZ,timer_table_sqr(1,1,0),data_size,MPI_REAL_LMDZ,COMM_LMDZ,ierr)
161      deallocate(tmp_table)
162   
163      endif
164     
165    ENDIF ! using_mpi
166   
167  end subroutine allgather_timer
168 
169  subroutine allgather_timer_average
170    USE parallel_lmdz
171    USE lmdz_mpi
172    implicit none
173    integer :: ierr
174    integer :: data_size
175    real, allocatable,dimension(:,:),target :: tmp_table
176    integer, allocatable,dimension(:,:),target :: tmp_iter
177    integer :: istats
178
179    IF (using_mpi) THEN
180       
181      if (AllTimer_IsActive) then
182   
183      allocate(tmp_table(max_size,nb_timer))
184      allocate(tmp_iter(max_size,nb_timer))
185   
186      data_size=max_size*nb_timer
187
188      tmp_table(:,:)=timer_average(:,:,mpi_rank)
189      call mpi_allgather(tmp_table(1,1),data_size,MPI_REAL_LMDZ,timer_average(1,1,0),data_size,MPI_REAL_LMDZ,COMM_LMDZ,ierr)
190      tmp_table(:,:)=timer_delta(:,:,mpi_rank)
191      call mpi_allgather(tmp_table(1,1),data_size,MPI_REAL_LMDZ,timer_delta(1,1,0),data_size,MPI_REAL_LMDZ,COMM_LMDZ,ierr)
192      tmp_iter(:,:)=timer_iteration(:,:,mpi_rank)
193      call mpi_allgather(tmp_iter(1,1),data_size,MPI_INTEGER,timer_iteration(1,1,0),data_size,MPI_INTEGER,COMM_LMDZ,ierr)
194      deallocate(tmp_table)
195   
196      endif
197     
198    ENDIF  ! using_mp�
199  end subroutine allgather_timer_average
200 
201  subroutine InitTime
202  implicit none
203    integer :: count,count_rate,count_max
204   
205    AllTimer_IsActive=.TRUE.
206    if (AllTimer_IsActive) then
207      call system_clock(count,count_rate,count_max)
208      call cpu_time(Last_cpuCount)
209      Last_Count=count
210    endif
211  end subroutine InitTime
212 
213  function DiffTime()
214  implicit none
215    double precision :: DiffTime
216    integer :: count,count_rate,count_max
217 
218    call system_clock(count,count_rate,count_max)
219    if (Count>=Last_Count) then
220      DiffTime=(1.*(Count-last_Count))/count_rate
221    else
222      DiffTime=(1.*(Count-last_Count+Count_max))/count_rate
223    endif
224    Last_Count=Count
225  end function DiffTime
226 
227  function DiffCpuTime()
228  implicit none
229    real :: DiffCpuTime
230    real :: Count
231   
232    call cpu_time(Count)
233    DiffCpuTime=Count-Last_cpuCount
234    Last_cpuCount=Count
235  end function DiffCpuTime
236
237end module times
Note: See TracBrowser for help on using the repository browser.