source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/times.F90 @ 5116

Last change on this file since 5116 was 5116, checked in by abarral, 2 months ago

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

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