StringVectorUtil.F90 Source File


This file depends on

sourcefile~~stringvectorutil.f90~~EfferentGraph sourcefile~stringvectorutil.f90 StringVectorUtil.F90 sourcefile~attribute.f90 Attribute.F90 sourcefile~stringvectorutil.f90->sourcefile~attribute.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~stringvectorutil.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~pfio_utilities.f90 pFIO_Utilities.F90 sourcefile~stringvectorutil.f90->sourcefile~pfio_utilities.f90 sourcefile~attribute.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~attribute.f90->sourcefile~pfio_utilities.f90 sourcefile~unlimitedentity.f90 UnlimitedEntity.F90 sourcefile~attribute.f90->sourcefile~unlimitedentity.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 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~~stringvectorutil.f90~~AfferentGraph sourcefile~stringvectorutil.f90 StringVectorUtil.F90 sourcefile~extdatagridcompng.f90 ExtDataGridCompNG.F90 sourcefile~extdatagridcompng.f90->sourcefile~stringvectorutil.f90 sourcefile~filemetadata.f90 FileMetadata.F90 sourcefile~filemetadata.f90->sourcefile~stringvectorutil.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~pfio.f90->sourcefile~stringvectorutil.f90 sourcefile~variable.f90 Variable.F90 sourcefile~variable.f90->sourcefile~stringvectorutil.f90

Source Code

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

module pFIO_StringVectorUtilMod
   use pFIO_UtilitiesMod
   use pFIO_AttributeMod
   use gFTL2_StringVector
   use MAPL_ExceptionHandling
   implicit none
   private
   public :: StringVector_serialize
   public :: StringVector_deserialize
   public :: string_in_stringVector

contains

   subroutine StringVector_serialize(strVec,buffer)
       type (StringVector) ,intent(in):: strVec
       integer, allocatable,intent(inout) :: buffer(:)
       type (StringVectorIterator) :: iter
       character(len=:),pointer :: str
       integer :: length
      
       if (allocated(buffer)) deallocate(buffer)
       allocate(buffer(0))
       iter = strVec%begin()
       do while (iter /= strVec%end())
          str => iter%of()
          buffer=[buffer,serialize_intrinsic(str)]
          call iter%next()
       enddo
       length = serialize_buffer_length(length) + size(buffer)
       buffer = [serialize_intrinsic(length),buffer]
    end subroutine StringVector_serialize

    subroutine StringVector_deserialize(buffer, strVec, rc)
       integer, intent(in) :: buffer(:)
       type (StringVector), intent(inout) :: strVec
       integer, optional, intent(out) :: rc

       character(len=:),allocatable :: str
       integer :: length,n,n1,n0

       n = 1
       call deserialize_intrinsic(buffer(n:),length)
       n0 =  serialize_buffer_length(length)
       n = n + n0
       length = length - n0
       strVec = StringVector() 
       do while (length > 0)
          call deserialize_intrinsic(buffer(n:),str)
          call strVec%push_back(str)
          n1 = serialize_buffer_length(str)
          n = n + n1
          length = length - n1
          deallocate(str)
       enddo
       _RETURN(_SUCCESS)
   end subroutine StringVector_deserialize

   function string_in_stringVector(target_string,string_vector) result(in_vector)
      logical :: in_vector
      character(len=*), intent(in) :: target_string
      type(StringVector), intent(in) :: string_vector

      type(StringVectorIterator) :: iter

      in_vector = .false.
      iter = string_vector%begin()
      do while(iter /= string_vector%end())
         if (trim(target_string) == iter%of()) in_vector = .true.
         call iter%next()
      enddo
   end function string_in_stringVector

end module pFIO_StringVectorUtilMod