StdDevColumn.F90 Source File


This file depends on

sourcefile~~stddevcolumn.f90~~EfferentGraph sourcefile~stddevcolumn.f90 StdDevColumn.F90 sourcefile~abstractcolumn.f90 AbstractColumn.F90 sourcefile~stddevcolumn.f90->sourcefile~abstractcolumn.f90 sourcefile~abstractmeter.f90 AbstractMeter.F90 sourcefile~stddevcolumn.f90->sourcefile~abstractmeter.f90 sourcefile~abstractmeternode.f90 AbstractMeterNode.F90 sourcefile~stddevcolumn.f90->sourcefile~abstractmeternode.f90 sourcefile~advancedmeter.f90 AdvancedMeter.F90 sourcefile~stddevcolumn.f90->sourcefile~advancedmeter.f90 sourcefile~distributedmeter.f90 DistributedMeter.F90 sourcefile~stddevcolumn.f90->sourcefile~distributedmeter.f90 sourcefile~simplecolumn.f90 SimpleColumn.F90 sourcefile~stddevcolumn.f90->sourcefile~simplecolumn.f90 sourcefile~abstractcolumn.f90->sourcefile~abstractmeternode.f90 sourcefile~abstractcolumn.f90->sourcefile~distributedmeter.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~abstractmeter.f90->sourcefile~errorhandling.f90 sourcefile~abstractmeternode.f90->sourcefile~abstractmeter.f90 sourcefile~advancedmeter.f90->sourcefile~abstractmeter.f90 sourcefile~abstractgauge.f90 AbstractGauge.F90 sourcefile~advancedmeter.f90->sourcefile~abstractgauge.f90 sourcefile~distributedmeter.f90->sourcefile~abstractmeter.f90 sourcefile~distributedmeter.f90->sourcefile~advancedmeter.f90 sourcefile~distributedmeter.f90->sourcefile~abstractgauge.f90 sourcefile~distributedmeter.f90->sourcefile~errorhandling.f90 sourcefile~simplecolumn.f90->sourcefile~abstractcolumn.f90 sourcefile~simplecolumn.f90->sourcefile~abstractmeternode.f90 sourcefile~simplecolumn.f90->sourcefile~distributedmeter.f90 sourcefile~abstractgauge.f90->sourcefile~abstractmeter.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

sourcefile~~stddevcolumn.f90~~AfferentGraph sourcefile~stddevcolumn.f90 StdDevColumn.F90 sourcefile~mapl_profiler.f90 MAPL_Profiler.F90 sourcefile~mapl_profiler.f90->sourcefile~stddevcolumn.f90 sourcefile~abstractserver.f90 AbstractServer.F90 sourcefile~abstractserver.f90->sourcefile~mapl_profiler.f90 sourcefile~applicationsupport.f90 ApplicationSupport.F90 sourcefile~applicationsupport.f90->sourcefile~mapl_profiler.f90 sourcefile~base_base_implementation.f90 Base_Base_implementation.F90 sourcefile~base_base_implementation.f90->sourcefile~mapl_profiler.f90 sourcefile~demo.f90 demo.F90 sourcefile~demo.f90->sourcefile~mapl_profiler.f90 sourcefile~extdatadrivergridcomp.f90 ExtDataDriverGridComp.F90 sourcefile~extdatadrivergridcomp.f90->sourcefile~mapl_profiler.f90 sourcefile~mapl.f90 MAPL.F90 sourcefile~mapl.f90->sourcefile~mapl_profiler.f90 sourcefile~mapl_bundleio_test.f90 mapl_bundleio_test.F90 sourcefile~mapl_bundleio_test.f90->sourcefile~mapl_profiler.f90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~mapl_profiler.f90 sourcefile~mapl_generic.f90 MAPL_Generic.F90 sourcefile~mapl_generic.f90->sourcefile~mapl_profiler.f90 sourcefile~mapl_nuopcwrappermod.f90 MAPL_NUOPCWrapperMod.F90 sourcefile~mapl_nuopcwrappermod.f90->sourcefile~mapl_profiler.f90 sourcefile~mapl_verticalmethods.f90 MAPL_VerticalMethods.F90 sourcefile~mapl_verticalmethods.f90->sourcefile~mapl_profiler.f90 sourcefile~maplframework.f90 MaplFramework.F90 sourcefile~maplframework.f90->sourcefile~mapl_profiler.f90 sourcefile~mpi_demo.f90 mpi_demo.F90 sourcefile~mpi_demo.f90->sourcefile~mapl_profiler.f90 sourcefile~mpiserver.f90 MpiServer.F90 sourcefile~mpiserver.f90->sourcefile~mapl_profiler.f90 sourcefile~multigroupserver.f90 MultiGroupServer.F90 sourcefile~multigroupserver.f90->sourcefile~mapl_profiler.f90 sourcefile~regrid_util.f90 Regrid_Util.F90 sourcefile~regrid_util.f90->sourcefile~mapl_profiler.f90 sourcefile~serverthread.f90 ServerThread.F90 sourcefile~serverthread.f90->sourcefile~mapl_profiler.f90 sourcefile~test_advancedmeter.pf test_AdvancedMeter.pf sourcefile~test_advancedmeter.pf->sourcefile~mapl_profiler.f90 sourcefile~test_column.pf test_Column.pf sourcefile~test_column.pf->sourcefile~mapl_profiler.f90 sourcefile~test_distributedmeter.pf test_DistributedMeter.pf sourcefile~test_distributedmeter.pf->sourcefile~mapl_profiler.f90 sourcefile~test_exclusivecolumn.pf test_ExclusiveColumn.pf sourcefile~test_exclusivecolumn.pf->sourcefile~mapl_profiler.f90 sourcefile~test_meternode.pf test_MeterNode.pf sourcefile~test_meternode.pf->sourcefile~mapl_profiler.f90 sourcefile~test_meternodeiterator.pf test_MeterNodeIterator.pf sourcefile~test_meternodeiterator.pf->sourcefile~mapl_profiler.f90 sourcefile~test_namecolumn.pf test_NameColumn.pf sourcefile~test_namecolumn.pf->sourcefile~mapl_profiler.f90 sourcefile~test_percentagecolumn.pf test_PercentageColumn.pf sourcefile~test_percentagecolumn.pf->sourcefile~mapl_profiler.f90 sourcefile~test_profilereporter.pf test_ProfileReporter.pf sourcefile~test_profilereporter.pf->sourcefile~mapl_profiler.f90 sourcefile~test_timeprofiler.pf test_TimeProfiler.pf sourcefile~test_timeprofiler.pf->sourcefile~mapl_profiler.f90

Source Code

module MAPL_StdDevColumn
   use MAPL_AbstractColumn
   use MAPL_SimpleColumn
   use MAPL_AbstractMeterNode
   use MAPL_AbstractMeter
   use MAPL_AdvancedMeter
   use Mapl_DistributedMeter
   implicit none
   private

   public :: StdDevColumn

   type, extends(SimpleColumn) :: StdDevColumn
      private
      logical :: relative = .false.
      character(:), allocatable :: option
   contains
      procedure :: get_row
      procedure :: get_row_dist
   end type StdDevColumn

   interface StdDevColumn
      module procedure :: new_StdDevColumn
   end interface StdDevColumn


contains


   function new_StdDevColumn(relative, option) result(column)
      type(StdDevColumn) :: column
      logical, optional, intent(in) :: relative
      character(*), optional, intent(in) :: option

      if (present(relative)) column%relative = relative
      if (present(option)) column%option = option

   end function new_StdDevColumn


   function get_row(this, node) result(row)
      class(*), allocatable :: row
      class (StdDevColumn), intent(in) :: this
      class (AbstractMeterNode), target, intent(in) :: node

      class (AbstractMeter), pointer :: tmr


      if (.not. allocated(this%option)) then
         tmr => node%get_meter()
         select type (tmr)
         class is (AdvancedMeter)
            if (this%relative) then
               allocate(row, source=tmr%get_relative_deviation())
            else
               allocate(row, source=tmr%get_standard_deviation())
            end if
         class default
            print*,'error handling here'
         end select
      else
         call this%get_row_dist(node, row)
      end if

   end function get_row


   subroutine get_row_dist(this, node, row)
      class (StdDevColumn), target, intent(in) :: this
      class (AbstractMeterNode), target, intent(in) :: node
      class(*), allocatable, intent(out) :: row

      class(AbstractMeter), pointer :: m
      type(DistributedStatistics) :: stats
      type(DistributedReal64) :: std_deviation

      m => node%get_meter()

      select type (m)
      class is (DistributedMeter)
         stats = m%get_statistics()
         std_deviation = stats%sum_square_deviation
         print*,__FILE__,__LINE__,'std deviation not fully implemented'
         call this%fill_row(std_deviation, this%option, row)
      end select
   end subroutine get_row_dist

end module MAPL_StdDevColumn