MemoryTextColumn.F90 Source File


This file depends on

sourcefile~~memorytextcolumn.f90~~EfferentGraph sourcefile~memorytextcolumn.f90 MemoryTextColumn.F90 sourcefile~abstractcolumn.f90 AbstractColumn.F90 sourcefile~memorytextcolumn.f90->sourcefile~abstractcolumn.f90 sourcefile~abstractmeternode.f90 AbstractMeterNode.F90 sourcefile~memorytextcolumn.f90->sourcefile~abstractmeternode.f90 sourcefile~textcolumn.f90 TextColumn.F90 sourcefile~memorytextcolumn.f90->sourcefile~textcolumn.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~textcolumn.f90->sourcefile~abstractmeternode.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~~memorytextcolumn.f90~~AfferentGraph sourcefile~memorytextcolumn.f90 MemoryTextColumn.F90 sourcefile~mapl_profiler.f90 MAPL_Profiler.F90 sourcefile~mapl_profiler.f90->sourcefile~memorytextcolumn.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_MemoryTextColumn
   use, intrinsic :: iso_fortran_env, only: REAL64, INT64
   use MAPL_AbstractColumn
   use MAPL_AbstractMeterNode
   use MAPL_TextColumn
   use GFTL_UnlimitedVector
   implicit none
   private

   public :: MemoryTextColumn

   type String
      character(:), allocatable :: string
   end type String
   type, extends(TextColumn) :: MemoryTextColumn
      private
!!$      character(:), allocatable :: header(:)
      type (String), allocatable :: header(:)
      character(:), allocatable :: format
      class (AbstractColumn), allocatable :: data_column
   contains
      procedure :: get_header
      procedure :: get_num_rows_header
      procedure :: get_rows
   end type MemoryTextColumn


   interface MemoryTextColumn
      module procedure new_MemoryTextColumn
   end interface MemoryTextColumn


contains


   function new_MemoryTextColumn(header, format, width, data_column, separator) result(column)
      type (MemoryTextColumn) :: column
      character(*), intent(in) :: header(:)
      character(*), intent(in) :: format
      integer, intent(in) :: width
      class (AbstractColumn), intent(in) :: data_column
      character(1), optional, intent(in) :: separator

      integer :: i, n

      n = size(header)
      allocate(column%header(n))
      do i = 1, n
         column%header(i)%string = header(i)
      end do
      
      column%format = format
      call column%set_width(width)

      column%data_column = data_column

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


   end function new_MemoryTextColumn

 

   subroutine get_header(this, header)
      class (MemoryTextColumn), intent(in) :: this
      character(:), allocatable, intent(out) :: header(:)
      integer :: w, n
      integer :: i

      w = this%get_width()
      n = this%get_num_rows_header()
      allocate(character(w) :: header(n))
      do i = 1, size(this%header)
         header(i)(:) = this%header(i)%string
      end do
      call this%get_separator(header(size(this%header)+1), n - size(this%header))
      call this%center(header)

   end subroutine get_header


   integer function get_num_rows_header(this) result(num_rows)
      class(MemoryTextColumn), intent(in) :: this
      num_rows = size(this%header) + this%get_num_rows_separator()
   end function get_num_rows_header


   subroutine get_rows(this, node, rows)
      use MAPL_AbstractMeterNode
      class (MemoryTextColumn), intent(in) :: this
      class (AbstractMeterNode), target, intent(in) :: node
      character(:), allocatable, intent(out) :: rows(:)

      integer :: n, i
      character(2) :: suffix
      real(kind=REAL64) :: x
      type (UnlimitedVector) :: values

      n = this%get_width()

      values = this%data_column%get_rows(node)
      allocate(character(n) :: rows(values%size()))

      do i = 1, values%size()
         select type (v => values%at(i))
         type is (integer)
            x = real(v, kind=REAL64)
            suffix = get_suffix(x)
            write(rows(i),this%format) convert(x), suffix
         type is (real(kind=REAL64))
            suffix = get_suffix(v)
            write(rows(i),this%format) convert(v), suffix
         end select
      end do

   contains


      function get_suffix(x) result(suffix)
         character(2) :: suffix
         real(kind=REAL64), intent(in) :: x

         integer(kind=INT64) :: ix
         integer(kind=INT64) :: KB = 1024

         ix = ceiling(abs(x),kind=INT64)
         if (ix < KB) then
            suffix = ' B'
         elseif (ix < KB**2) then
            suffix = 'KB'
         elseif (ix < KB**3) then
            suffix = 'MB'
         elseif (ix < KB**4) then
            suffix = 'GB'
         else
            suffix = 'TB'
         end if

      end function get_suffix

      function convert(x) result(ix)
         integer(kind=INT64) :: ix
         real(kind=REAL64), intent(in) :: x


         integer(kind=INT64) :: KB = 1024

         ix = ceiling(abs(x), kind=INT64)
         if (ix < KB) then
            ix = ix
         elseif (ix < KB**2) then
            ix = ix / KB
         elseif (ix < KB**3) then
            ix = ix / KB**2
         elseif (ix < KB**4) then
            ix = ix / KB**3
         else
            ix = ix / KB**4
         end if

         ix = sign(1.d0, x) * ix
         
      end function convert
         
   end subroutine get_rows
   

end module MAPL_MemoryTextColumn