PercentageColumn.F90 Source File


This file depends on

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

Files dependent on this one

sourcefile~~percentagecolumn.f90~~AfferentGraph sourcefile~percentagecolumn.f90 PercentageColumn.F90 sourcefile~mapl_profiler.f90 MAPL_Profiler.F90 sourcefile~mapl_profiler.f90->sourcefile~percentagecolumn.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

#include "unused_dummy.H"

module MAPL_PercentageColumn
   use, intrinsic :: iso_fortran_env, only: REAL64
   use MAPL_AbstractMeterNode
   use MAPL_AbstractColumn
   implicit none
   private

   public :: PercentageColumn

   type, extends(AbstractColumn) :: PercentageColumn
      private
      character(:), allocatable :: mode
      class (AbstractColumn), allocatable :: reference_column
   contains
      procedure :: get_rows
      procedure :: get_row
   end type PercentageColumn

   interface PercentageColumn
      module procedure new_PercentageColumn
   end interface PercentageColumn


contains


   function new_PercentageColumn(reference_column, mode) result(column)
      type (PercentageColumn) :: column
      class (AbstractColumn), intent(in) :: reference_column
      character(*), optional, intent(in) :: mode

      column%reference_column = reference_column
      if (present(mode)) then
         column%mode = mode
      else
         column%mode = 'TOTAL'
      end if

   end function new_PercentageColumn


   function get_rows(this, node) result(rows)
      use GFTL_UnlimitedVector
      type (UnlimitedVector) :: rows
      class (PercentageColumn), intent(in) :: this
      class (AbstractMeterNode), target, intent(in) :: node

      type (UnlimitedVector) :: values
      integer :: i
      real(kind=REAL64) :: s, x

      values = this%reference_column%get_rows(node)

      s = 0
      do i = 1, values%size()
         select type (v => values%at(i))
         type is (real(kind=REAL64))
            x = v
         type is (integer)
            x = v
         end select
         
         select case (this%mode)
         case ('TOTAL')
            s = s + x
         case ('MAX')
            s = max(s, x)
         end select

      end do

      do i = 1, values%size()
         select type (v => values%at(i))
         type is (real(kind=REAL64))
            x = v
         type is (integer)
            x = v
         end select
         call rows%push_back(100*x/s)
      end do

   end function get_rows

   ! Not used - PercentageColumn combines results across rows
   function get_row(this, node) result(row)
      class(*), allocatable :: row
      class (PercentageColumn), intent(in) :: this
      class (AbstractMeterNode), target, intent(in) :: node

      row = 0
      allocate(row,source=0) ! to eliminate compiler warning.

      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(node)
   end function get_row
   
end module MAPL_PercentageColumn