StringVariableMap.F90 Source File


This file depends on

sourcefile~~stringvariablemap.f90~~EfferentGraph sourcefile~stringvariablemap.f90 StringVariableMap.F90 sourcefile~coordinatevariable.f90 CoordinateVariable.F90 sourcefile~stringvariablemap.f90->sourcefile~coordinatevariable.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~stringvariablemap.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~pfio_utilities.f90 pFIO_Utilities.F90 sourcefile~stringvariablemap.f90->sourcefile~pfio_utilities.f90 sourcefile~variable.f90 Variable.F90 sourcefile~stringvariablemap.f90->sourcefile~variable.f90 sourcefile~coordinatevariable.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~coordinatevariable.f90->sourcefile~pfio_utilities.f90 sourcefile~coordinatevariable.f90->sourcefile~variable.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~coordinatevariable.f90->sourcefile~keywordenforcer.f90 sourcefile~pfio_constants.f90 pFIO_Constants.F90 sourcefile~coordinatevariable.f90->sourcefile~pfio_constants.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~errorhandling.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~mapl_throw.f90 sourcefile~pfio_utilities.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~pfio_utilities.f90->sourcefile~pfio_constants.f90 sourcefile~variable.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~variable.f90->sourcefile~pfio_utilities.f90 sourcefile~attribute.f90 Attribute.F90 sourcefile~variable.f90->sourcefile~attribute.f90 sourcefile~variable.f90->sourcefile~keywordenforcer.f90 sourcefile~variable.f90->sourcefile~pfio_constants.f90 sourcefile~stringvectorutil.f90 StringVectorUtil.F90 sourcefile~variable.f90->sourcefile~stringvectorutil.f90 sourcefile~unlimitedentity.f90 UnlimitedEntity.F90 sourcefile~variable.f90->sourcefile~unlimitedentity.f90 sourcefile~attribute.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~attribute.f90->sourcefile~pfio_utilities.f90 sourcefile~attribute.f90->sourcefile~unlimitedentity.f90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~stringvectorutil.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~stringvectorutil.f90->sourcefile~pfio_utilities.f90 sourcefile~stringvectorutil.f90->sourcefile~attribute.f90 sourcefile~unlimitedentity.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~unlimitedentity.f90->sourcefile~pfio_utilities.f90 sourcefile~unlimitedentity.f90->sourcefile~pfio_constants.f90

Files dependent on this one

sourcefile~~stringvariablemap.f90~~AfferentGraph sourcefile~stringvariablemap.f90 StringVariableMap.F90 sourcefile~clientmanager.f90 ClientManager.F90 sourcefile~clientmanager.f90->sourcefile~stringvariablemap.f90 sourcefile~clientthread.f90 ClientThread.F90 sourcefile~clientthread.f90->sourcefile~stringvariablemap.f90 sourcefile~filemetadata.f90 FileMetadata.F90 sourcefile~filemetadata.f90->sourcefile~stringvariablemap.f90 sourcefile~historycollection.f90 HistoryCollection.F90 sourcefile~historycollection.f90->sourcefile~stringvariablemap.f90 sourcefile~mockclientthread.f90 MockClientThread.F90 sourcefile~mockclientthread.f90->sourcefile~stringvariablemap.f90 sourcefile~modifymetadatamessage.f90 ModifyMetadataMessage.F90 sourcefile~modifymetadatamessage.f90->sourcefile~stringvariablemap.f90 sourcefile~netcdf4_fileformatter.f90 NetCDF4_FileFormatter.F90 sourcefile~netcdf4_fileformatter.f90->sourcefile~stringvariablemap.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~pfio.f90->sourcefile~stringvariablemap.f90 sourcefile~replacemetadatamessage.f90 ReplaceMetadataMessage.F90 sourcefile~replacemetadatamessage.f90->sourcefile~stringvariablemap.f90

Source Code

#include "MAPL_ErrLog.h"
#include "unused_dummy.H"

module pFIO_StringVariableMapMod
   use pFIO_VariableMod
   use pFIO_CoordinateVariableMod

   ! Create a map (associative array) between names and pFIO_Variables.

#define Key __CHARACTER_DEFERRED
#define T Variable
#define T_polymorphic
#define Map StringVariableMap
#define MapIterator StringVariableMapIterator
#define MapPair StringVariableMapPair

#include "map/template.inc"

#undef MapPair
#undef MapIterator
#undef Map
#undef T_polymorphic
#undef T
#undef Key

end module pFIO_StringVariableMapMod

module pFIO_StringVariableMapUtilMod
   use MAPL_ExceptionHandling
   use pFIO_UtilitiesMod
   use pFIO_VariableMod
   use pFIO_CoordinateVariableMod
   use pFIO_StringVariableMapMod
   implicit none
   private
   public :: StringVariableMap_get_length
   public :: StringVariableMap_serialize
   public :: StringVariableMap_deserialize

contains

    integer function StringVariableMap_get_length(this) result(length)
      type (StringVariableMap), intent(in) :: this
      integer, allocatable :: buffer(:)

      call StringVariableMap_serialize(this, buffer)
      length = size(buffer)

    end function StringVariableMap_get_length

    subroutine StringVariableMap_serialize(map, buffer, rc)
       type (StringVariableMap), target, intent(in):: map
       integer, allocatable, intent(inout) :: buffer(:)
       integer, optional, intent(out) :: rc

       type (StringVariableMapIterator) :: iter
       character(len=:),pointer :: key
       class(Variable),pointer :: var_ptr
       integer :: length, status
       integer, allocatable :: tmp_buffer(:)

       if (allocated(buffer)) deallocate(buffer)
       allocate(buffer(0))
       iter = map%ftn_begin()
       do while (iter /= map%ftn_end())
          call iter%next()
          key => iter%first()
          buffer=[buffer,serialize_intrinsic(key)]
          var_ptr => iter%second()
          call var_ptr%serialize(tmp_buffer, status)
          _VERIFY(status)
          buffer = [buffer, tmp_buffer]
          deallocate(tmp_buffer)
       enddo
       length = serialize_buffer_length(length)+size(buffer)
       buffer = [serialize_intrinsic(length),buffer]
       _RETURN(_SUCCESS)
    end subroutine StringVariableMap_serialize

    subroutine StringVariableMap_deserialize(buffer, map, rc)
       integer, intent(in) :: buffer(:)
       type (StringVariableMap), intent(inout) :: map
       integer, optional, intent(out) :: rc

       character(len=:),allocatable :: key
       integer :: length,n,n0,n1,n2, v_type
       type (Variable) :: v
       type (CoordinateVariable) :: c
       integer :: status

       n = 1
       call deserialize_intrinsic(buffer(n:),length)
       _ASSERT(length <= size(buffer), "stringVarmap length does not match")

       n0 = serialize_buffer_length(length)
       n = n + n0
       length = length - n0
       map = StringVariableMap()
       do while (length > 0)
          call deserialize_intrinsic(buffer(n:),key)
          n1 = serialize_buffer_length(key)
          n = n + n1

          ! the first one is length, the second one is type
          call deserialize_intrinsic(buffer(n:),n2)
          call deserialize_intrinsic(buffer(n+1:),v_type)

          if (v_type == Variable_SERIALIZE_TYPE) then
             call Variable_deserialize(buffer(n:n+n2-1),v, status)
             _VERIFY(status)
             call map%insert(key,v)
          else if (v_type == Coord_SERIALIZE_TYPE) then
             call CoordinateVariable_deserialize(buffer(n:n+n2-1),c, status)
             _VERIFY(status)
             call map%insert(key,c)
          endif

          n = n + n2
          length = length - n1 - n2
          deallocate(key)
       enddo
       _RETURN(_SUCCESS)
    end subroutine StringVariableMap_deserialize

end module pFIO_StringVariableMapUtilMod