NameColumn.F90 Source File


This file depends on

sourcefile~~namecolumn.f90~~EfferentGraph sourcefile~namecolumn.f90 NameColumn.F90 sourcefile~abstractmeternode.f90 AbstractMeterNode.F90 sourcefile~namecolumn.f90->sourcefile~abstractmeternode.f90 sourcefile~simpletextcolumn.f90 SimpleTextColumn.F90 sourcefile~namecolumn.f90->sourcefile~simpletextcolumn.f90 sourcefile~abstractmeter.f90 AbstractMeter.F90 sourcefile~abstractmeternode.f90->sourcefile~abstractmeter.f90 sourcefile~simpletextcolumn.f90->sourcefile~abstractmeternode.f90 sourcefile~textcolumn.f90 TextColumn.F90 sourcefile~simpletextcolumn.f90->sourcefile~textcolumn.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~abstractmeter.f90->sourcefile~errorhandling.f90 sourcefile~textcolumn.f90->sourcefile~abstractmeternode.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

sourcefile~~namecolumn.f90~~AfferentGraph sourcefile~namecolumn.f90 NameColumn.F90 sourcefile~mapl_profiler.f90 MAPL_Profiler.F90 sourcefile~mapl_profiler.f90->sourcefile~namecolumn.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_NameColumn
   use MAPL_AbstractMeterNode
   use MAPL_SimpleTextColumn
   implicit none
   private

   public :: NameColumn

   type, extends(SimpleTextColumn) :: NameColumn
      private
      character(:), allocatable :: indent
   contains
      procedure :: get_header
      procedure :: get_num_rows_header
      procedure :: get_row
   end type NameColumn

   interface NameColumn
      module procedure new_NameColumn
   end interface NameColumn


contains


   function new_NameColumn(width, indent, separator) result(column)
      type (NameColumn) :: column
      integer, intent(in) :: width
      character(*), optional, intent(in) :: indent
      character(1), optional, intent(in) :: separator

      call column%set_width(width)
      if (present(indent)) then
         column%indent = indent
      else
         column%indent = '--'
      end if

      if (present(separator)) call column%set_separator(separator)

   end function new_NameColumn


   subroutine get_header(this, header)
      class (NameColumn), intent(in) :: this
      character(:), allocatable, intent(out) :: header(:)

      integer :: w, h

      w = this%get_width()
      h = this%get_num_rows_header()

      allocate(character(len=w) :: header(h))
      header(1) = 'Name'
      if ( h <=1 ) return ! when separator is not in the constructor
      call this%get_separator(header(2), h-1)
      
   end subroutine get_header


   function get_row(this, node) result(row)
      character(:), allocatable :: row
      class (NameColumn), intent(in) :: this
      class (AbstractMeterNode), intent(in) :: node

      integer :: n

      n = this%get_width()
      allocate(character(len=n) :: row)
      row(:) = repeat(this%indent, ncopies=node%get_depth()) // node%get_name()

   end function get_row


   integer function get_num_rows_header(this) result(num_rows)
      class(NameColumn), intent(in) :: this
      num_rows = 1 + this%get_num_rows_separator()
   end function get_num_rows_header


end module MAPL_NameColumn