demo Program

Uses

  • program~~demo~~UsesGraph program~demo demo kinds kinds program~demo->kinds module~forbenchmark forbenchmark program~demo->module~forbenchmark module~forbenchmark_coarray forbenchmark_coarray module~forbenchmark->module~forbenchmark_coarray module~forbenchmark_default forbenchmark_default module~forbenchmark->module~forbenchmark_default module~forbenchmark_coarray->kinds fortime fortime module~forbenchmark_coarray->fortime module~forbenchmark_default->kinds module~forbenchmark_default->fortime

Calls

program~~demo~~CallsGraph program~demo demo proc~finalize forbenchmark_default::benchmark%finalize program~demo->proc~finalize proc~init forbenchmark_default::benchmark%init program~demo->proc~init proc~start_benchmark forbenchmark_default::benchmark%start_benchmark program~demo->proc~start_benchmark proc~stop_benchmark forbenchmark_default::benchmark%stop_benchmark program~demo->proc~stop_benchmark proc~finalize_mark forbenchmark_default::mark%finalize_mark proc~finalize->proc~finalize_mark proc~current_date_and_time forbenchmark_default::current_date_and_time proc~init->proc~current_date_and_time colorize colorize proc~start_benchmark->colorize ctimer_start ctimer_start proc~start_benchmark->ctimer_start dtimer_start dtimer_start proc~start_benchmark->dtimer_start mtimer_start mtimer_start proc~start_benchmark->mtimer_start otimer_start otimer_start proc~start_benchmark->otimer_start timer_start timer_start proc~start_benchmark->timer_start ctimer_stop ctimer_stop proc~stop_benchmark->ctimer_stop dtimer_stop dtimer_stop proc~stop_benchmark->dtimer_stop mtimer_stop mtimer_stop proc~stop_benchmark->mtimer_stop otimer_stop otimer_stop proc~stop_benchmark->otimer_stop proc~write_benchmark forbenchmark_default::benchmark%write_benchmark proc~stop_benchmark->proc~write_benchmark timer_stop timer_stop proc~stop_benchmark->timer_stop

Variables

Type Attributes Name Initial
type(benchmark) :: bench
real(kind=rk), dimension(:,:), allocatable :: A
real(kind=rk), dimension(:,:), allocatable :: B
real(kind=rk), dimension(:,:), allocatable :: C
integer(kind=ik) :: p
integer(kind=ik) :: nl
integer(kind=ik) :: i
integer(kind=ik) :: j
integer(kind=ik) :: k

Functions

function cmp_gflops(argi, argr) result(gflops)

Arguments

Type IntentOptional Attributes Name
integer(kind=ik), intent(in), optional, dimension(:) :: argi
real(kind=rk), intent(in), optional, dimension(:) :: argr

Return Value real(kind=rk)


Source Code

program demo

   use kinds,        only: rk, ik     ! use -DREAL32 or -DREAL64 to switch between real32 and real64, default is real64
                                      ! use -DINT32 or -DINT64 to switch between int32 and int64, default is int32
   use forbenchmark, only: benchmark  ! forbenchmark module

   implicit none

   ! benchmark object
   type(benchmark)                       :: bench
   ! define your variables here
   real(rk), dimension(:,:), allocatable :: A, B, C
   integer(ik)                           :: p
   integer(ik)                           :: nl, i, j, k

   ! initialize the benchmark
   ! nmarks: number of methods to benchmark
   ! title: optional
   ! filename: optional. make sure directory exists
   ! nloops: optional. number of loops for each benchmark. default is 10.
   ! 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 = 600_ik,900_ik, 100_ik ! loop over problem size

      !===============================================================================
      ! allocate and initialize your variables here
      if (allocated(A)) deallocate(A)
      if (allocated(B)) deallocate(B)
      if (allocated(C)) deallocate(C)
      allocate(A(p,p))
      allocate(B(p,p))
      allocate(C(p,p), source=0.0_rk)
      call random_number(A)
      call random_number(B)
      !===============================================================================


      !===============================================================================
      ! start benchmark for method 1
      ! imark is an integer to identify the method, 1 is for reference method
      ! method is a string to identify the method
      ! description is optional
      ! argi is an optional integer array of arguments to write in the output file and to compute gflops
      ! the first element in argi is used for x-axis in the plot
      ! argr is an optional real array of arguments to compute gflops
      ! loop over nloops
      call bench%start_benchmark(imark=1, method='m1', description='intrinsic, C = matmul(A,B)', argi=[p,p,p])
      ! loop over nloops
      do nl = 1, bench%nloops

         ! call your function or subroutine or ...
         ! here is used intrinsic matmul
         C = matmul(A,B)

      end do
      ! stop benchmark for method 1
      ! flops is an optional function to compute flops
      call bench%stop_benchmark(flops=cmp_gflops)
      !===============================================================================


      !===============================================================================
      ! start benchmark for method 2, same as above.
      call bench%start_benchmark(2,'m2', 'my_matmul, C = matmul(A,B)', [p,p,p])
      do nl = 1, bench%nloops

         ! call your function or subroutine or ...
         ! here is used another matmul
         C = 0.0_rk
         do i = 1,p
            do j = 1,p
               do k = 1,p
                  C(i,j) = C(i,j) + A(i,k)*B(k,j)
               end do
            end do
         end do

      end do
      call bench%stop_benchmark(cmp_gflops)
      !===============================================================================

      ! you can add more methods ...

   end do ! end loop over p

   ! finalize the benchmark
   call bench%finalize()

   ! you can use a python script to plot and export the results as follows:
   ! python results/export.py demo_<compiler>.data
   ! for coarray benchmarks, utilize:
   ! python results/export_co.py demo_co.data
   ! python results/export_im.py demo_im1.data
   ! python results/export_im.py demo_im2.data
   ! ...
   
contains

   !===============================================================================
   ! define an optional function to compute gflops
   function cmp_gflops(argi,argr) result(gflops)
      integer(ik), dimension(:), intent(in), optional :: argi
      real(rk),    dimension(:), intent(in), optional :: argr
      real(rk)                                        :: gflops

      gflops = real(argi(1),rk) * real(argi(2),rk) * real(argi(3),rk) * 1.0e-9_rk
   end function cmp_gflops
   !===============================================================================

end program demo