AbstractMeter.F90 Source File


This file depends on

sourcefile~~abstractmeter.f90~~EfferentGraph sourcefile~abstractmeter.f90 AbstractMeter.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~abstractmeter.f90->sourcefile~errorhandling.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

sourcefile~~abstractmeter.f90~~AfferentGraph sourcefile~abstractmeter.f90 AbstractMeter.F90 sourcefile~abstractgauge.f90 AbstractGauge.F90 sourcefile~abstractgauge.f90->sourcefile~abstractmeter.f90 sourcefile~abstractmeterfactory.f90 AbstractMeterFactory.F90 sourcefile~abstractmeterfactory.f90->sourcefile~abstractmeter.f90 sourcefile~abstractmeternode.f90 AbstractMeterNode.F90 sourcefile~abstractmeternode.f90->sourcefile~abstractmeter.f90 sourcefile~advancedmeter.f90 AdvancedMeter.F90 sourcefile~advancedmeter.f90->sourcefile~abstractmeter.f90 sourcefile~baseprofiler.f90 BaseProfiler.F90 sourcefile~baseprofiler.f90->sourcefile~abstractmeter.f90 sourcefile~distributedmeter.f90 DistributedMeter.F90 sourcefile~distributedmeter.f90->sourcefile~abstractmeter.f90 sourcefile~distributedprofiler.f90 DistributedProfiler.F90 sourcefile~distributedprofiler.f90->sourcefile~abstractmeter.f90 sourcefile~exclusivecolumn.f90 ExclusiveColumn.F90 sourcefile~exclusivecolumn.f90->sourcefile~abstractmeter.f90 sourcefile~inclusivecolumn.f90 InclusiveColumn.F90 sourcefile~inclusivecolumn.f90->sourcefile~abstractmeter.f90 sourcefile~mapl_profiler.f90 MAPL_Profiler.F90 sourcefile~mapl_profiler.f90->sourcefile~abstractmeter.f90 sourcefile~maxcyclecolumn.f90 MaxCycleColumn.F90 sourcefile~maxcyclecolumn.f90->sourcefile~abstractmeter.f90 sourcefile~meancyclecolumn.f90 MeanCycleColumn.F90 sourcefile~meancyclecolumn.f90->sourcefile~abstractmeter.f90 sourcefile~memoryprofiler.f90 MemoryProfiler.F90 sourcefile~memoryprofiler.f90->sourcefile~abstractmeter.f90 sourcefile~meternode.f90 MeterNode.F90 sourcefile~meternode.f90->sourcefile~abstractmeter.f90 sourcefile~mincyclecolumn.f90 MinCycleColumn.F90 sourcefile~mincyclecolumn.f90->sourcefile~abstractmeter.f90 sourcefile~numcyclescolumn.f90 NumCyclesColumn.F90 sourcefile~numcyclescolumn.f90->sourcefile~abstractmeter.f90 sourcefile~stddevcolumn.f90 StdDevColumn.F90 sourcefile~stddevcolumn.f90->sourcefile~abstractmeter.f90 sourcefile~stubprofiler.f90 StubProfiler.F90 sourcefile~stubprofiler.f90->sourcefile~abstractmeter.f90 sourcefile~timeprofiler.f90 TimeProfiler.F90 sourcefile~timeprofiler.f90->sourcefile~abstractmeter.f90

Source Code

#include "unused_dummy.H"
#include "MAPL_ErrLog.h"
module MAPL_AbstractMeter
   use MAPL_ErrorHandlingMod
   use, intrinsic :: iso_fortran_env, only: REAL64
   implicit none
   private

   public :: AbstractMeter

   logical, save, public :: dist_initialized = .false.
   integer, save, public :: type_dist_struct, type_dist_real64, type_dist_integer
   integer, save, public :: dist_reduce_op

   type, abstract :: AbstractMeter
      private
   contains
      ! Override in subclasses for different timing mechanisms
      procedure(i_action), deferred :: start
      procedure(i_action), deferred :: stop
      procedure(i_action), deferred :: reset
      procedure(i_add_cycle), deferred :: add_cycle

      procedure(i_get), deferred :: get_total
      procedure(i_accumulate), deferred :: accumulate
      procedure :: finalize

   end type AbstractMeter


   abstract interface

      subroutine i_action(this)
         import AbstractMeter
         class (AbstractMeter), intent(inout) :: this
      end subroutine i_action

      subroutine i_add_cycle(this, increment)
         import AbstractMeter
         import REAL64
         class (AbstractMeter), intent(inout) :: this
         real(kind=REAL64), intent(in) :: increment
      end subroutine i_add_cycle

      function i_get(this) result(val)
         import AbstractMeter
         import REAL64
         real(kind=REAL64) :: val
         class (AbstractMeter), intent(in) :: this
      end function i_get

      subroutine i_accumulate(this, lap)
         import AbstractMeter
         class(AbstractMeter), intent(inout) :: this
         class(AbstractMeter), intent(in) :: lap
      end subroutine i_accumulate

   end interface

   contains

      subroutine finalize(this, rc)
        class(AbstractMeter), intent(in) :: this
        integer, optional, intent(out) :: rc
        integer :: ierror, status

        ierror = 0
        if (dist_initialized) then
           call MPI_type_free(type_dist_struct, ierror)
           _VERIFY(ierror)
           call MPI_type_free(type_dist_real64, ierror)
           _VERIFY(ierror)
           call MPI_type_free(type_dist_integer, ierror)
           _VERIFY(ierror)
           call MPI_Op_free(dist_reduce_op,ierror)
           _VERIFY(ierror)
           dist_initialized = .false.
        endif
        if (present(rc)) rc = ierror
        _UNUSED_DUMMY(this)
      end subroutine

end module MAPL_AbstractMeter