init Subroutine

private impure elemental subroutine init(this, nmarks, title, filename, nloops, timer)

Uses

  • proc~~init~~UsesGraph proc~init forbenchmark_default::benchmark%init iso_fortran_env iso_fortran_env proc~init->iso_fortran_env

Initialize the benchmark object.

Type Bound

benchmark

Arguments

Type IntentOptional Attributes Name
class(benchmark), intent(inout) :: this

Benchmark object

integer, intent(in) :: nmarks

Number of methods to be benchmarked

character(len=*), intent(in), optional :: title

Title of the benchmark

character(len=*), intent(in), optional :: filename

Filename for storing benchmark data

integer, intent(in), optional :: nloops

Number of loops for each benchmark (default: 10)

character(len=*), intent(in), optional :: timer

Timer object for measuring time (default: wall). The timer options available are 'wall', 'date_and_time', 'cpu', 'omp', and 'mpi'.


Calls

proc~~init~~CallsGraph proc~init forbenchmark_default::benchmark%init proc~current_date_and_time forbenchmark_default::current_date_and_time proc~init->proc~current_date_and_time

Called by

proc~~init~~CalledByGraph proc~init forbenchmark_default::benchmark%init program~demo demo program~demo->proc~init

Source Code

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

      class(benchmark), intent(inout)        :: this       !! Benchmark object
      integer,          intent(in)           :: nmarks     !! Number of methods to be benchmarked
      character(*),     intent(in), optional :: title      !! Title of the benchmark
      character(*),     intent(in), optional :: filename   !! Filename for storing benchmark data
      integer,          intent(in), optional :: nloops     !! Number of loops for each benchmark (default: 10)
      character(*),     intent(in), optional :: timer      !! Timer object for measuring time (default: wall). The timer options available are 'wall', 'date_and_time', 'cpu', 'omp', and 'mpi'.
      integer                                :: nunit      !! Unit number for file access
      integer                                :: iostat     !! I/O status
      integer                                :: which_compiler !! Logical variables for compiler detection
      character(:), allocatable              :: compiler   !! Compiler name

      if (nmarks <= 0) error stop 'nmarks must be greater than zero.'

      if (allocated(this%marks)) deallocate(this%marks)
      allocate(this%marks(nmarks))

      compiler =''
      which_compiler = index(compiler_version(), 'Intel(R) Fortran Compiler')
      if (which_compiler /= 0) compiler = '_ifx'
      which_compiler = index(compiler_version(), 'Intel(R) Fortran Intel(R)')
      if (which_compiler /= 0) compiler = '_ifort'
      which_compiler = index(compiler_version(), 'GCC')
      if (which_compiler /= 0) compiler = '_gfortran'
      which_compiler = index(compiler_version(), 'nvfortran')
      if (which_compiler /= 0) compiler = '_nvfortran'

      if (present(filename)) then
         this%filename = trim(filename//compiler//'.data')
      else
         this%filename = 'benchmark'//compiler//'.data'
      endif

      if (present(nloops)) then
         if (nloops <= 0) error stop 'nloops must be greater than zero.'
         this%nloops = nloops
      else
         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.'
      end if
      open (newunit = nunit, file = this%filename)
      write(nunit,'(a)') '-----------------------------------------------------'
      write(nunit,'(a)') 'ForBenchmark - https://github.com/gha3mi/forbenchmark'
      write(nunit,'(a)') '-----------------------------------------------------'
      write(nunit,'(a)') ''
      if (present(title)) then
         write(nunit,'(a)') trim(title)
      else
         write(nunit,'(a)') 'ForBenchmark'
      endif
      write(nunit,'(a)') current_date_and_time()
      write(nunit,'(a)') ''
      write(nunit,'(a,a)') 'compiler_version: ', compiler_version()
      write(nunit,'(a,a)') 'compiler_options: ', compiler_options()
      write(nunit,'(a)') ''
      write(nunit,'(a)') ''
      write(nunit,'(a)') &
      &'       METHOD        |&
      &   SPEEDUP    |&
      &         TIME         |&
      &        GFLOPS        |&
      &  NLOOPS  |&
      &   ARGI  '
      close(nunit)
   end subroutine init