StringIntegerMapUtil.F90 Source File


This file depends on

sourcefile~~stringintegermaputil.f90~~EfferentGraph sourcefile~stringintegermaputil.f90 StringIntegerMapUtil.F90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~stringintegermaputil.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~pfio_utilities.f90 pFIO_Utilities.F90 sourcefile~stringintegermaputil.f90->sourcefile~pfio_utilities.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_constants.f90 pFIO_Constants.F90 sourcefile~pfio_utilities.f90->sourcefile~pfio_constants.f90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

sourcefile~~stringintegermaputil.f90~~AfferentGraph sourcefile~stringintegermaputil.f90 StringIntegerMapUtil.F90 sourcefile~filemetadata.f90 FileMetadata.F90 sourcefile~filemetadata.f90->sourcefile~stringintegermaputil.f90 sourcefile~addwritedatacollectionmessage.f90 AddWriteDataCollectionMessage.F90 sourcefile~addwritedatacollectionmessage.f90->sourcefile~filemetadata.f90 sourcefile~clientmanager.f90 ClientManager.F90 sourcefile~clientmanager.f90->sourcefile~filemetadata.f90 sourcefile~clientthread.f90 ClientThread.F90 sourcefile~clientthread.f90->sourcefile~filemetadata.f90 sourcefile~extdatafilestream.f90 ExtDataFileStream.F90 sourcefile~extdatafilestream.f90->sourcefile~filemetadata.f90 sourcefile~extdatagridcompmod.f90 ExtDataGridCompMod.F90 sourcefile~extdatagridcompmod.f90->sourcefile~filemetadata.f90 sourcefile~filemetadatavector.f90 FileMetadataVector.F90 sourcefile~filemetadatavector.f90->sourcefile~filemetadata.f90 sourcefile~forwarddataandmessage.f90 ForwardDataAndMessage.F90 sourcefile~forwarddataandmessage.f90->sourcefile~filemetadata.f90 sourcefile~historycollection.f90 HistoryCollection.F90 sourcefile~historycollection.f90->sourcefile~filemetadata.f90 sourcefile~mapl_geosatmaskmod.f90 MAPL_GeosatMaskMod.F90 sourcefile~mapl_geosatmaskmod.f90->sourcefile~filemetadata.f90 sourcefile~mapl_obsutil.f90 MAPL_ObsUtil.F90 sourcefile~mapl_obsutil.f90->sourcefile~filemetadata.f90 sourcefile~mapl_trajectorymod.f90 MAPL_TrajectoryMod.F90 sourcefile~mapl_trajectorymod.f90->sourcefile~filemetadata.f90 sourcefile~mockclientthread.f90 MockClientThread.F90 sourcefile~mockclientthread.f90->sourcefile~filemetadata.f90 sourcefile~multigroupserver.f90 MultiGroupServer.F90 sourcefile~multigroupserver.f90->sourcefile~filemetadata.f90 sourcefile~netcdf4_fileformatter.f90 NetCDF4_FileFormatter.F90 sourcefile~netcdf4_fileformatter.f90->sourcefile~filemetadata.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~pfio.f90->sourcefile~filemetadata.f90 sourcefile~protocolparser.f90 ProtocolParser.F90 sourcefile~protocolparser.f90->sourcefile~filemetadata.f90 sourcefile~replacemetadatamessage.f90 ReplaceMetadataMessage.F90 sourcefile~replacemetadatamessage.f90->sourcefile~filemetadata.f90 sourcefile~serverthread.f90 ServerThread.F90 sourcefile~serverthread.f90->sourcefile~filemetadata.f90 sourcefile~test_filemetadata.pf Test_FileMetadata.pf sourcefile~test_filemetadata.pf->sourcefile~filemetadata.f90 sourcefile~test_netcdf4_fileformatter.pf Test_NetCDF4_FileFormatter.pf sourcefile~test_netcdf4_fileformatter.pf->sourcefile~filemetadata.f90

Source Code

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

module pFIO_StringIntegerMapUtilMod
   use pFIO_UtilitiesMod
   use gFTL2_StringIntegerMap
   use MAPL_ExceptionHandling
   implicit none
   private
   public :: StringIntegerMap_serialize
   public :: StringIntegerMap_deserialize

contains

    subroutine StringIntegerMap_serialize(map,buffer)
       type (StringIntegerMap), target, intent(in):: map
       integer, allocatable,intent(inout) :: buffer(:)
       type (StringIntegerMapIterator) :: iter
       character(len=:),pointer :: key
       integer,pointer :: value
       integer :: length
 
       if (allocated(buffer)) deallocate(buffer)
       allocate(buffer(0))
       iter = map%begin()
       do while (iter /= map%end())
          key => iter%first()
          buffer=[buffer,serialize_intrinsic(key)]
          value => iter%second()
          buffer = [buffer, serialize_intrinsic(value)]
          call iter%next() 
       enddo
       length = serialize_buffer_length(length) + size(buffer)
       buffer = [serialize_intrinsic(length),buffer]

    end subroutine StringIntegerMap_serialize  

    subroutine StringIntegerMap_deserialize(buffer, map, rc)
       integer, intent(in) :: buffer(:)
       type (StringIntegerMap), intent(inout) :: map
       integer, optional, intent(out) :: rc

       character(len=:),allocatable :: key
       integer :: value,length,n,n0,n1,n2

       n = 1
       call deserialize_intrinsic(buffer(n:),length)
       n0 = serialize_buffer_length(length)
       n = n + n0
       length = length - n0
       map = StringIntegerMap()
       do while (length > 0)
          call deserialize_intrinsic(buffer(n:),key)
          n1 = serialize_buffer_length(key)
          n = n + n1
          call deserialize_intrinsic(buffer(n:),value)
          n2 = serialize_buffer_length(value)
          n = n + n2
          length = length - n1 - n2
          call map%insert(key,value)
          deallocate(key)
       enddo
       _RETURN(_SUCCESS)
    end subroutine StringIntegerMap_deserialize

end module pFIO_StringIntegerMapUtilMod