module times integer,PRIVATE,save :: Last_Count=0 real, PRIVATE,save :: Last_cpuCount=0 logical, PRIVATE,save :: AllTimer_IsActive=.FALSE. integer, parameter :: nb_timer = 4 integer, parameter :: timer_caldyn = 1 integer, parameter :: timer_vanleer = 2 integer, parameter :: timer_dissip = 3 integer, parameter :: timer_physic = 4 integer, parameter :: stopped = 1 integer, parameter :: running = 2 integer, parameter :: suspended = 3 integer :: max_size real, allocatable, dimension(:,:,:) :: timer_table real, allocatable, dimension(:,:,:) :: timer_table_sqr integer, allocatable, dimension(:,:,:) :: timer_iteration real, allocatable, dimension(:,:,:) :: timer_average real, allocatable, dimension(:,:,:) :: timer_delta real, allocatable,dimension(:) :: timer_running, last_time integer, allocatable,dimension(:) :: timer_state contains SUBROUTINE init_timer USE parallel_lmdz IMPLICIT NONE INCLUDE "dimensions.h" INCLUDE "paramet.h" max_size=jjm+1 allocate(timer_table(max_size,nb_timer,0:mpi_size-1)) allocate(timer_table_sqr(max_size,nb_timer,0:mpi_size-1)) allocate(timer_iteration(max_size,nb_timer,0:mpi_size-1)) allocate(timer_average(max_size,nb_timer,0:mpi_size-1)) allocate(timer_delta(max_size,nb_timer,0:mpi_size-1)) allocate(timer_running(nb_timer)) allocate(timer_state(nb_timer)) allocate(last_time(nb_timer)) timer_table(:,:,:)=0 timer_table_sqr(:,:,:)=0 timer_iteration(:,:,:)=0 timer_average(:,:,:)=0 timer_delta(:,:,:)=0 timer_state(:)=stopped END SUBROUTINE init_timer SUBROUTINE start_timer(no_timer) IMPLICIT NONE integer :: no_timer if (AllTimer_IsActive) then if (timer_state(no_timer)/=stopped) then CALL abort_gcm("times","start_timer :: timer is already running or suspended",1) else timer_state(no_timer)=running endif timer_running(no_timer)=0 CALL cpu_time(last_time(no_timer)) endif END SUBROUTINE start_timer SUBROUTINE suspend_timer(no_timer) IMPLICIT NONE integer :: no_timer if (AllTimer_IsActive) then if (timer_state(no_timer)/=running) then CALL abort_gcm("times","suspend_timer :: timer is not running",1) else timer_state(no_timer)=suspended endif timer_running(no_timer)=timer_running(no_timer)-last_time(no_timer) CALL cpu_time(last_time(no_timer)) timer_running(no_timer)=timer_running(no_timer)+last_time(no_timer) endif END SUBROUTINE suspend_timer SUBROUTINE resume_timer(no_timer) IMPLICIT NONE integer :: no_timer if (AllTimer_IsActive) then if (timer_state(no_timer)/=suspended) then CALL abort_gcm("times","resume_timer :: timer is not suspended",1) else timer_state(no_timer)=running endif CALL cpu_time(last_time(no_timer)) endif END SUBROUTINE resume_timer SUBROUTINE stop_timer(no_timer) USE parallel_lmdz IMPLICIT NONE integer :: no_timer integer :: N real :: V,V2 if (AllTimer_IsActive) then if (timer_state(no_timer)/=running) then CALL abort_gcm("times","stop_timer :: timer is not running",1) else timer_state(no_timer)=stopped endif timer_running(no_timer)=timer_running(no_timer)-last_time(no_timer) CALL cpu_time(last_time(no_timer)) timer_running(no_timer)=timer_running(no_timer)+last_time(no_timer) timer_table(jj_nb,no_timer,mpi_rank)=timer_table(jj_nb,no_timer,mpi_rank)+timer_running(no_timer) timer_table_sqr(jj_nb,no_timer,mpi_rank)=timer_table_sqr(jj_nb,no_timer,mpi_rank)+timer_running(no_timer)**2 timer_iteration(jj_nb,no_timer,mpi_rank)=timer_iteration(jj_nb,no_timer,mpi_rank)+1 timer_average(jj_nb,no_timer,mpi_rank)=timer_table(jj_nb,no_timer,mpi_rank)/timer_iteration(jj_nb,no_timer,mpi_rank) if (timer_iteration(jj_nb,no_timer,mpi_rank)>=2) then N=timer_iteration(jj_nb,no_timer,mpi_rank) V2=timer_table_sqr(jj_nb,no_timer,mpi_rank) V=timer_table(jj_nb,no_timer,mpi_rank) timer_delta(jj_nb,no_timer,mpi_rank)=sqrt(ABS(V2-V*V/N)/(N-1)) else timer_delta(jj_nb,no_timer,mpi_rank)=0 endif endif END SUBROUTINE stop_timer SUBROUTINE allgather_timer USE parallel_lmdz USE lmdz_mpi IMPLICIT NONE integer :: ierr integer :: data_size real, allocatable,dimension(:,:) :: tmp_table IF (using_mpi) THEN if (AllTimer_IsActive) then allocate(tmp_table(max_size,nb_timer)) data_size=max_size*nb_timer tmp_table(:,:)=timer_table(:,:,mpi_rank) 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) tmp_table(:,:)=timer_table_sqr(:,:,mpi_rank) 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) deallocate(tmp_table) endif ENDIF ! using_mpi END SUBROUTINE allgather_timer SUBROUTINE allgather_timer_average USE parallel_lmdz USE lmdz_mpi IMPLICIT NONE integer :: ierr integer :: data_size real, allocatable,dimension(:,:),target :: tmp_table integer, allocatable,dimension(:,:),target :: tmp_iter integer :: istats IF (using_mpi) THEN if (AllTimer_IsActive) then allocate(tmp_table(max_size,nb_timer)) allocate(tmp_iter(max_size,nb_timer)) data_size=max_size*nb_timer tmp_table(:,:)=timer_average(:,:,mpi_rank) 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) tmp_table(:,:)=timer_delta(:,:,mpi_rank) 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) tmp_iter(:,:)=timer_iteration(:,:,mpi_rank) CALL mpi_allgather(tmp_iter(1,1),data_size,MPI_INTEGER,timer_iteration(1,1,0),data_size,MPI_INTEGER,COMM_LMDZ,ierr) deallocate(tmp_table) endif ENDIF ! using_mpi END SUBROUTINE allgather_timer_average SUBROUTINE InitTime IMPLICIT NONE integer :: count,count_rate,count_max AllTimer_IsActive=.TRUE. if (AllTimer_IsActive) then CALL system_clock(count,count_rate,count_max) CALL cpu_time(Last_cpuCount) Last_Count=count endif END SUBROUTINE InitTime function DiffTime() IMPLICIT NONE double precision :: DiffTime integer :: count,count_rate,count_max CALL system_clock(count,count_rate,count_max) if (Count>=Last_Count) then DiffTime=(1.*(Count-last_Count))/count_rate else DiffTime=(1.*(Count-last_Count+Count_max))/count_rate endif Last_Count=Count end function DiffTime function DiffCpuTime() IMPLICIT NONE real :: DiffCpuTime real :: Count CALL cpu_time(Count) DiffCpuTime=Count-Last_cpuCount Last_cpuCount=Count end function DiffCpuTime end module times