Skip to content

Commit

Permalink
Add timer to set the timer method.
Browse files Browse the repository at this point in the history
- Avaiavle options are: omp, mpi, cpu, wall, date_and_time
- Default is wall
- To use omp, you need to compile with -DUSE_OMP option
- To use mpi, you need to compile with -DUSE_MPI option
- Update demo
  • Loading branch information
gha3mi committed Jan 2, 2024
1 parent 3f85ffb commit b00f1d5
Show file tree
Hide file tree
Showing 3 changed files with 166 additions and 18 deletions.
3 changes: 2 additions & 1 deletion example/demo.f90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,8 @@ program demo
! title: optional
! filename: optional. make sure directory exists
! nloops: optional. number of loops for each benchmark. default is 10.
call bench%init(nmarks=2, title='Demo Benchmark', filename='results/demo', nloops=2)
! timer: optional. default is 'wall'. other options are 'cpu', 'omp'. 'mpi', 'date_and_time'
call bench%init(nmarks=2, title='Demo Benchmark', filename='results/demo', nloops=2, timer='wall')

! start the benchmark
do p = 100,400, 100 ! loop over problem size
Expand Down
94 changes: 84 additions & 10 deletions src/forbenchmark_coarray.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module forbenchmark_coarray
type :: mark_co
!! author: Seyed Ali Ghasemi
type(timer) :: time
real(rk) :: elapsed_time
real(rk) :: flops
end type mark_co
!===============================================================================
Expand Down Expand Up @@ -47,6 +48,7 @@ module forbenchmark_coarray
integer :: nloops
integer, dimension(:), allocatable :: argi
real(rk), dimension(:), allocatable :: argr
character(:), allocatable :: timer
contains
procedure :: init
procedure :: start_benchmark
Expand All @@ -59,15 +61,16 @@ module forbenchmark_coarray
contains

!===============================================================================
elemental impure subroutine init(this, nmarks, title, filename, nloops)
!! author: Seyed Ali Ghasemi
elemental impure subroutine init(this, nmarks, title, filename, nloops, timer)
!! author: Seyed Ali Ghasemi
use, intrinsic :: iso_fortran_env, only: compiler_version, compiler_options

class(benchmark), intent(inout) :: this
integer, intent(in) :: nmarks
character(*), intent(in), optional :: title
character(*), intent(in), optional :: filename
integer, intent(in), optional :: nloops
character(*), intent(in), optional :: timer
integer :: nunit
integer :: iostat
character(10) :: im_chr
Expand All @@ -90,6 +93,33 @@ elemental impure subroutine init(this, nmarks, title, filename, nloops)
this%nloops = 10
end if

if (present(timer)) then
select case (trim(timer))
case ('wall')
this%timer = 'wall'
case ('date_and_time')
this%timer = 'date_and_time'
case ('cpu')
this%timer = 'cpu'
case ('omp')
#if defined(USE_OMP)
this%timer = 'omp'
#else
error stop 'Use -DUSE_OMP to enable OpenMP.'
#endif
case ('mpi')
#if defined(USE_MPI)
this%timer = 'mpi'
#else
error stop 'Use -DUSE_MPI to enable MPI.'
#endif
case default
error stop 'timer is not valid. Valid options are: wall, date_and_time, cpu, omp, mpi.'
end select
else
this%timer = 'wall'
end if

allocate(this%marks_co(nmarks)[*])
allocate(this%marks(nmarks))

Expand Down Expand Up @@ -208,7 +238,27 @@ impure subroutine start_benchmark(this, imark, method, description, argi, argr)
print'(a)', colorize('Meth.: '//this%marks(imark)%method, color_fg='green',style='bold_on')
end if

call this%marks_co(imark)%time%timer_start()
select case (trim(this%timer))
case ('wall')
call this%marks_co(imark)%time%timer_start()
case ('date_and_time')
call this%marks_co(imark)%time%dtimer_start()
case ('cpu')
call this%marks_co(imark)%time%ctimer_start()
case ('omp')
#if defined(USE_OMP)
call this%marks_co(imark)%time%ptimer_start()
#else
error stop 'Use -DUSE_OMP to enable OpenMP.'
#endif
case ('mpi')
#if defined(USE_MPI)
call this%marks_co(imark)%time%mtimer_start()
#else
error stop 'Use -DUSE_MPI to enable MPI.'
#endif
end select

end subroutine start_benchmark
!===============================================================================

Expand Down Expand Up @@ -238,10 +288,34 @@ end function Fun

if (imark <= 0 .or. imark > size(this%marks)) error stop 'imark is out of range.'

call this%marks_co(imark)%time%timer_stop(message=' Elapsed time :',nloops=this%nloops)
select case (trim(this%timer))
case ('wall')
call this%marks_co(imark)%time%timer_stop(message=' Elapsed time :',nloops=this%nloops)
this%marks_co(imark)%elapsed_time = this%marks_co(imark)%time%elapsed_time
case ('date_and_time')
call this%marks_co(imark)%time%dtimer_stop(message=' Elapsed time :',nloops=this%nloops)
this%marks_co(imark)%elapsed_time = this%marks_co(imark)%time%elapsed_dtime
case ('cpu')
call this%marks_co(imark)%time%ctimer_stop(message=' Elapsed time :',nloops=this%nloops)
this%marks_co(imark)%elapsed_time = this%marks_co(imark)%time%cpu_time
case ('omp')
#if defined(USE_OMP)
call this%marks_co(imark)%time%otimer_stop(message=' Elapsed time :',nloops=this%nloops)
this%marks_co(imark)%elapsed_time = this%marks_co(imark)%time%omp_time
#else
error stop 'Use -DUSE_OMP to enable OpenMP.'
#endif
case ('mpi')
#if defined(USE_MPI)
call this%marks_co(imark)%time%mtimer_stop(message=' Elapsed time :',nloops=this%nloops)
this%marks_co(imark)%elapsed_time = this%marks_co(imark)%time%mpi_time
#else
error stop 'Use -DUSE_MPI to enable MPI.'
#endif
end select

if (present(flops)) then
this%marks_co(imark)%flops = flops(this%argi,this%argr)/this%marks_co(imark)%time%elapsed_time
this%marks_co(imark)%flops = flops(this%argi,this%argr)/this%marks_co(imark)%elapsed_time
print'(a,f7.3,a)', ' Performance :', this%marks_co(imark)%flops,' [GFLOPS/image]'
else
this%marks_co(imark)%flops = 0.0_rk
Expand All @@ -252,7 +326,7 @@ end function Fun
if (this_image() == 1) then
allocate(elapsed_times(num_images()))
do i = 1, num_images()
elapsed_times(i) = this%marks_co(imark)[i]%time%elapsed_time
elapsed_times(i) = this%marks_co(imark)[i]%elapsed_time
end do
elapsed_time_max = maxval(elapsed_times)
elapsed_time_min = minval(elapsed_times)
Expand Down Expand Up @@ -360,7 +434,7 @@ end subroutine write_benchmark

!===============================================================================
pure elemental subroutine finalize_mark(this)
!! author: Seyed Ali Ghasemi
!! author: Seyed Ali Ghasemi
class(mark), intent(inout) :: this

if (allocated(this%method)) deallocate(this%method)
Expand All @@ -371,7 +445,7 @@ end subroutine finalize_mark

!===============================================================================
elemental impure subroutine finalize(this)
!! author: Seyed Ali Ghasemi
!! author: Seyed Ali Ghasemi
class(benchmark), intent(inout) :: this
integer :: nunit
logical :: exist
Expand All @@ -393,7 +467,7 @@ elemental impure subroutine finalize(this)
open (newunit = nunit, file = this%filename, access = 'append')
write(nunit,'(a)') 'end of benchmark'
close(nunit)
end if
end if

if (allocated(this%marks_co)) deallocate(this%marks_co)
call this%marks%finalize_mark()
Expand All @@ -410,7 +484,7 @@ end subroutine finalize

!===============================================================================
impure function current_date_and_time() result(datetime)
!! author: Seyed Ali Ghasemi
!! author: Seyed Ali Ghasemi
character(21) :: datetime
character(10) :: date
character(8) :: time
Expand Down
87 changes: 80 additions & 7 deletions src/forbenchmark_default.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module forbenchmark_default
character(:), allocatable :: method
character(:), allocatable :: description
type(timer) :: time
real(rk) :: elapsed_time
real(rk) :: speedup
real(rk) :: flops
contains
Expand All @@ -32,6 +33,7 @@ module forbenchmark_default
integer :: nloops
integer, dimension(:), allocatable :: argi
real(rk), dimension(:), allocatable :: argr
character(:), allocatable :: timer
contains
procedure :: init
procedure :: start_benchmark
Expand All @@ -44,7 +46,7 @@ module forbenchmark_default
contains

!===============================================================================
elemental impure subroutine init(this, nmarks, title, filename, nloops)
elemental impure subroutine init(this, nmarks, title, filename, nloops, timer)
!! author: Seyed Ali Ghasemi
use, intrinsic :: iso_fortran_env, only: compiler_version, compiler_options

Expand All @@ -53,6 +55,7 @@ elemental impure subroutine init(this, nmarks, title, filename, nloops)
character(*), intent(in), optional :: title
character(*), intent(in), optional :: filename
integer, intent(in), optional :: nloops
character(*), intent(in), optional :: timer
integer :: nunit
integer :: iostat

Expand All @@ -73,6 +76,33 @@ elemental impure subroutine init(this, nmarks, title, filename, nloops)
this%nloops = 10
end if

if (present(timer)) then
select case (trim(timer))
case ('wall')
this%timer = 'wall'
case ('date_and_time')
this%timer = 'date_and_time'
case ('cpu')
this%timer = 'cpu'
case ('omp')
#if defined(USE_OMP)
this%timer = 'omp'
#else
error stop 'Use -DUSE_OMP to enable OpenMP.'
#endif
case ('mpi')
#if defined(USE_MPI)
this%timer = 'mpi'
#else
error stop 'Use -DUSE_MPI to enable MPI.'
#endif
case default
error stop 'timer is not valid. Valid options are: wall, date_and_time, cpu, omp, mpi.'
end select
else
this%timer = 'wall'
end if

inquire(file=this%filename, iostat=iostat)
if (iostat /= 0) then
error stop 'file '//trim(this%filename)//' cannot be accessed.'
Expand Down Expand Up @@ -153,7 +183,26 @@ impure subroutine start_benchmark(this, imark, method, description, argi, argr)
print'(a)', colorize('Meth.: '//this%marks(imark)%method, color_fg='green',style='bold_on')
end if

call this%marks(imark)%time%timer_start()
select case (trim(this%timer))
case ('wall')
call this%marks(imark)%time%timer_start()
case ('date_and_time')
call this%marks(imark)%time%dtimer_start()
case ('cpu')
call this%marks(imark)%time%ctimer_start()
case ('omp')
#if defined(USE_OMP)
call this%marks(imark)%time%otimer_start()
#else
error stop 'Use -DUSE_OMP to enable OpenMP.'
#endif
case ('mpi')
#if defined(USE_MPI)
call this%marks(imark)%time%mtimer_start()
#else
error stop 'Use -DUSE_MPI to enable MPI.'
#endif
end select
end subroutine start_benchmark
!===============================================================================

Expand All @@ -178,13 +227,37 @@ end function Fun

if (imark <= 0 .or. imark > size(this%marks)) error stop 'imark is out of range.'

call this%marks(imark)%time%timer_stop(message=' Elapsed time :',nloops=this%nloops)

this%marks(imark)%speedup = this%marks(imark)%time%elapsed_time/this%marks(1)%time%elapsed_time
select case (trim(this%timer))
case ('wall')
call this%marks(imark)%time%timer_stop(message=' Elapsed time :',nloops=this%nloops)
this%marks(imark)%elapsed_time = this%marks(imark)%time%elapsed_time
case ('date_and_time')
call this%marks(imark)%time%dtimer_stop(message=' Elapsed time :',nloops=this%nloops)
this%marks(imark)%elapsed_time = this%marks(imark)%time%elapsed_dtime
case ('cpu')
call this%marks(imark)%time%ctimer_stop(message=' Elapsed time :',nloops=this%nloops)
this%marks(imark)%elapsed_time = this%marks(imark)%time%cpu_time
case ('omp')
#if defined(USE_OMP)
call this%marks(imark)%time%otimer_stop(message=' Elapsed time :',nloops=this%nloops)
this%marks(imark)%elapsed_time = this%marks(imark)%time%omp_time
#else
error stop 'Use -DUSE_OMP to enable OpenMP.'
#endif
case ('mpi')
#if defined(USE_MPI)
call this%marks(imark)%time%mtimer_stop(message=' Elapsed time :',nloops=this%nloops)
this%marks(imark)%elapsed_time = this%marks(imark)%time%mpi_time
#else
error stop 'Use -DUSE_MPI to enable MPI.'
#endif
end select

this%marks(imark)%speedup = this%marks(imark)%elapsed_time/this%marks(1)%elapsed_time

if (present(flops)) then
print'(a,f7.3,a)', ' Speedup :', this%marks(imark)%speedup,' [-]'
this%marks(imark)%flops = flops(this%argi,this%argr)/this%marks(imark)%time%elapsed_time
this%marks(imark)%flops = flops(this%argi,this%argr)/this%marks(imark)%elapsed_time
print'(a,f7.3,a)', ' Performance :', this%marks(imark)%flops,' [GFLOPS]'
else
this%marks(imark)%flops = 0.0_rk
Expand Down Expand Up @@ -222,7 +295,7 @@ impure subroutine write_benchmark(this, imark)
write(nunit,fmt) &
this%marks(imark)%method,&
this%marks(imark)%speedup,&
this%marks(imark)%time%elapsed_time,&
this%marks(imark)%elapsed_time,&
this%marks(imark)%flops,&
this%nloops,&
this%argi
Expand Down

0 comments on commit b00f1d5

Please sign in to comment.