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

Last change on this file since 5272 was 5272, checked in by abarral, 25 hours ago

Turn paramet.h into a module

  • 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.2 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, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
30          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
31implicit none
32
33
34   
35    max_size=jjm+1
36    allocate(timer_table(max_size,nb_timer,0:mpi_size-1))
37    allocate(timer_table_sqr(max_size,nb_timer,0:mpi_size-1))
38    allocate(timer_iteration(max_size,nb_timer,0:mpi_size-1))
39    allocate(timer_average(max_size,nb_timer,0:mpi_size-1))
40    allocate(timer_delta(max_size,nb_timer,0:mpi_size-1))
41    allocate(timer_running(nb_timer))
42    allocate(timer_state(nb_timer))
43    allocate(last_time(nb_timer))
44   
45    timer_table(:,:,:)=0
46    timer_table_sqr(:,:,:)=0
47    timer_iteration(:,:,:)=0
48    timer_average(:,:,:)=0
49    timer_delta(:,:,:)=0
50    timer_state(:)=stopped     
51  end subroutine init_timer
52 
53  subroutine start_timer(no_timer)
54    implicit none
55    integer :: no_timer
56   
57    if (AllTimer_IsActive) then
58   
59      if (timer_state(no_timer)/=stopped) then
60        CALL abort_gcm("times","start_timer :: timer is already running or suspended",1)
61      else
62        timer_state(no_timer)=running
63      endif
64     
65      timer_running(no_timer)=0
66      call cpu_time(last_time(no_timer))
67   
68    endif
69   
70  end subroutine start_timer
71 
72  subroutine suspend_timer(no_timer)
73    implicit none
74    integer :: no_timer
75     
76    if (AllTimer_IsActive) then   
77      if (timer_state(no_timer)/=running) then
78         CALL abort_gcm("times","suspend_timer :: timer is not running",1)
79      else
80        timer_state(no_timer)=suspended
81      endif
82   
83      timer_running(no_timer)=timer_running(no_timer)-last_time(no_timer)
84      call cpu_time(last_time(no_timer))
85      timer_running(no_timer)=timer_running(no_timer)+last_time(no_timer)
86    endif
87  end subroutine suspend_timer
88 
89  subroutine resume_timer(no_timer)
90    implicit none
91    integer :: no_timer
92     
93    if (AllTimer_IsActive) then   
94      if (timer_state(no_timer)/=suspended) then
95        CALL abort_gcm("times","resume_timer :: timer is not suspended",1)
96      else
97        timer_state(no_timer)=running
98      endif
99     
100      call cpu_time(last_time(no_timer))
101    endif
102   
103  end subroutine resume_timer
104
105  subroutine stop_timer(no_timer)
106    USE parallel_lmdz
107    implicit none
108    integer :: no_timer
109    integer :: N
110    real :: V,V2
111   
112    if (AllTimer_IsActive) then
113       
114      if (timer_state(no_timer)/=running) then
115        CALL abort_gcm("times","stop_timer :: timer is not running",1)
116      else
117        timer_state(no_timer)=stopped
118      endif
119   
120      timer_running(no_timer)=timer_running(no_timer)-last_time(no_timer)
121      call cpu_time(last_time(no_timer))
122      timer_running(no_timer)=timer_running(no_timer)+last_time(no_timer)
123   
124      timer_table(jj_nb,no_timer,mpi_rank)=timer_table(jj_nb,no_timer,mpi_rank)+timer_running(no_timer)
125      timer_table_sqr(jj_nb,no_timer,mpi_rank)=timer_table_sqr(jj_nb,no_timer,mpi_rank)+timer_running(no_timer)**2
126      timer_iteration(jj_nb,no_timer,mpi_rank)=timer_iteration(jj_nb,no_timer,mpi_rank)+1
127      timer_average(jj_nb,no_timer,mpi_rank)=timer_table(jj_nb,no_timer,mpi_rank)/timer_iteration(jj_nb,no_timer,mpi_rank)
128      if (timer_iteration(jj_nb,no_timer,mpi_rank)>=2) then
129        N=timer_iteration(jj_nb,no_timer,mpi_rank)
130        V2=timer_table_sqr(jj_nb,no_timer,mpi_rank)
131        V=timer_table(jj_nb,no_timer,mpi_rank)
132        timer_delta(jj_nb,no_timer,mpi_rank)=sqrt(ABS(V2-V*V/N)/(N-1))
133      else
134        timer_delta(jj_nb,no_timer,mpi_rank)=0
135      endif
136    endif
137   
138  end subroutine stop_timer
139   
140  subroutine allgather_timer
141    USE parallel_lmdz
142    USE lmdz_mpi
143    implicit none
144
145    integer :: ierr
146    integer :: data_size
147    real, allocatable,dimension(:,:) :: tmp_table
148
149    IF (using_mpi) THEN   
150   
151      if (AllTimer_IsActive) then
152   
153   
154      allocate(tmp_table(max_size,nb_timer))
155   
156      data_size=max_size*nb_timer
157   
158      tmp_table(:,:)=timer_table(:,:,mpi_rank)
159      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)
160      tmp_table(:,:)=timer_table_sqr(:,:,mpi_rank)
161      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)
162      deallocate(tmp_table)
163   
164      endif
165     
166    ENDIF ! using_mpi
167   
168  end subroutine allgather_timer
169 
170  subroutine allgather_timer_average
171    USE parallel_lmdz
172    USE lmdz_mpi
173    implicit none
174    integer :: ierr
175    integer :: data_size
176    real, allocatable,dimension(:,:),target :: tmp_table
177    integer, allocatable,dimension(:,:),target :: tmp_iter
178    integer :: istats
179
180    IF (using_mpi) THEN
181       
182      if (AllTimer_IsActive) then
183   
184      allocate(tmp_table(max_size,nb_timer))
185      allocate(tmp_iter(max_size,nb_timer))
186   
187      data_size=max_size*nb_timer
188
189      tmp_table(:,:)=timer_average(:,:,mpi_rank)
190      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)
191      tmp_table(:,:)=timer_delta(:,:,mpi_rank)
192      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)
193      tmp_iter(:,:)=timer_iteration(:,:,mpi_rank)
194      call mpi_allgather(tmp_iter(1,1),data_size,MPI_INTEGER,timer_iteration(1,1,0),data_size,MPI_INTEGER,COMM_LMDZ,ierr)
195      deallocate(tmp_table)
196   
197      endif
198     
199    ENDIF  ! using_mp�
200  end subroutine allgather_timer_average
201 
202  subroutine InitTime
203  implicit none
204    integer :: count,count_rate,count_max
205   
206    AllTimer_IsActive=.TRUE.
207    if (AllTimer_IsActive) then
208      call system_clock(count,count_rate,count_max)
209      call cpu_time(Last_cpuCount)
210      Last_Count=count
211    endif
212  end subroutine InitTime
213 
214  function DiffTime()
215  implicit none
216    double precision :: DiffTime
217    integer :: count,count_rate,count_max
218 
219    call system_clock(count,count_rate,count_max)
220    if (Count>=Last_Count) then
221      DiffTime=(1.*(Count-last_Count))/count_rate
222    else
223      DiffTime=(1.*(Count-last_Count+Count_max))/count_rate
224    endif
225    Last_Count=Count
226  end function DiffTime
227 
228  function DiffCpuTime()
229  implicit none
230    real :: DiffCpuTime
231    real :: Count
232   
233    call cpu_time(Count)
234    DiffCpuTime=Count-Last_cpuCount
235    Last_cpuCount=Count
236  end function DiffCpuTime
237
238end module times
Note: See TracBrowser for help on using the repository browser.