ForwardDataAndMessage.F90 Source File


This file depends on

sourcefile~~forwarddataandmessage.f90~~EfferentGraph sourcefile~forwarddataandmessage.f90 ForwardDataAndMessage.F90 sourcefile~abstractdatamessage.f90 AbstractDataMessage.F90 sourcefile~forwarddataandmessage.f90->sourcefile~abstractdatamessage.f90 sourcefile~abstractdatareference.f90 AbstractDataReference.F90 sourcefile~forwarddataandmessage.f90->sourcefile~abstractdatareference.f90 sourcefile~abstractmessage.f90 AbstractMessage.F90 sourcefile~forwarddataandmessage.f90->sourcefile~abstractmessage.f90 sourcefile~filemetadata.f90 FileMetadata.F90 sourcefile~forwarddataandmessage.f90->sourcefile~filemetadata.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~forwarddataandmessage.f90->sourcefile~keywordenforcer.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~forwarddataandmessage.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~messagevector.f90 MessageVector.F90 sourcefile~forwarddataandmessage.f90->sourcefile~messagevector.f90 sourcefile~pfio_utilities.f90 pFIO_Utilities.F90 sourcefile~forwarddataandmessage.f90->sourcefile~pfio_utilities.f90 sourcefile~abstractdatamessage.f90->sourcefile~abstractdatareference.f90 sourcefile~abstractdatamessage.f90->sourcefile~abstractmessage.f90 sourcefile~abstractdatamessage.f90->sourcefile~keywordenforcer.f90 sourcefile~abstractdatamessage.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~abstractdatamessage.f90->sourcefile~pfio_utilities.f90 sourcefile~abstractdatareference.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~abstractdatareference.f90->sourcefile~pfio_utilities.f90 sourcefile~pfio_constants.f90 pFIO_Constants.F90 sourcefile~abstractdatareference.f90->sourcefile~pfio_constants.f90 sourcefile~abstractmessage.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~filemetadata.f90->sourcefile~keywordenforcer.f90 sourcefile~filemetadata.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~filemetadata.f90->sourcefile~pfio_utilities.f90 sourcefile~attribute.f90 Attribute.F90 sourcefile~filemetadata.f90->sourcefile~attribute.f90 sourcefile~coordinatevariable.f90 CoordinateVariable.F90 sourcefile~filemetadata.f90->sourcefile~coordinatevariable.f90 sourcefile~filemetadata.f90->sourcefile~pfio_constants.f90 sourcefile~stringintegermaputil.f90 StringIntegerMapUtil.F90 sourcefile~filemetadata.f90->sourcefile~stringintegermaputil.f90 sourcefile~stringvariablemap.f90 StringVariableMap.F90 sourcefile~filemetadata.f90->sourcefile~stringvariablemap.f90 sourcefile~stringvectorutil.f90 StringVectorUtil.F90 sourcefile~filemetadata.f90->sourcefile~stringvectorutil.f90 sourcefile~unlimitedentity.f90 UnlimitedEntity.F90 sourcefile~filemetadata.f90->sourcefile~unlimitedentity.f90 sourcefile~variable.f90 Variable.F90 sourcefile~filemetadata.f90->sourcefile~variable.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~messagevector.f90->sourcefile~abstractmessage.f90 sourcefile~messagevector.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~collectivestagedatamessage.f90 CollectiveStageDataMessage.F90 sourcefile~messagevector.f90->sourcefile~collectivestagedatamessage.f90 sourcefile~protocolparser.f90 ProtocolParser.F90 sourcefile~messagevector.f90->sourcefile~protocolparser.f90 sourcefile~pfio_utilities.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~pfio_utilities.f90->sourcefile~pfio_constants.f90

Files dependent on this one

sourcefile~~forwarddataandmessage.f90~~AfferentGraph sourcefile~forwarddataandmessage.f90 ForwardDataAndMessage.F90 sourcefile~multigroupserver.f90 MultiGroupServer.F90 sourcefile~multigroupserver.f90->sourcefile~forwarddataandmessage.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~pfio.f90->sourcefile~multigroupserver.f90

Source Code

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

module pFIO_ForwardDataAndMessageMod
   use mpi
   use MAPL_ExceptionHandling
   use pFIO_AbstractMessageMod
   use pFIO_UtilitiesMod
   use pFIO_AbstractDataReferenceMod
   use mapl_KeywordEnforcerMod
   use pFIO_AbstractDataMessageMod
   use pFIO_FileMetaDataMod
   use pFIO_MessageVectorMod
   use pFIO_MessageVectorUtilMod
   use, intrinsic :: iso_fortran_env, only: INT64

   implicit none
   private

   public :: ForwardDataAndMessage

   type :: ForwardDataAndMessage
      type (MessageVector) :: msg_vec
      integer, allocatable :: idata(:)
   contains
      procedure :: add_data_message
      procedure :: serialize
      procedure :: deserialize
      procedure :: destroy
   end type ForwardDataAndMessage

   interface ForwardDataAndMessage
      module procedure new_ForwardDataAndMessage
   end interface ForwardDataAndMessage

contains

   function new_ForwardDataAndMessage() result(message)
      type (ForwardDataAndMessage) :: message
      message%msg_vec = MessageVector()
   end function new_ForwardDataAndMessage

   subroutine serialize(this, buffer, rc)
      class (ForwardDataAndMessage), intent(in) :: this
      integer, allocatable, intent(inout) :: buffer(:)
      integer, optional, intent(out) :: rc
      integer :: i,k
      integer, allocatable :: buff_tmp(:)


      if (allocated(buffer)) deallocate(buffer)
      k = 0
      if (allocated(this%idata)) k = size(this%idata)
      call serialize_message_vector(this%msg_vec, buff_tmp)

      if ( k > 0 ) then
         i = k + 1
         buffer =[buff_tmp, i, this%idata]
      else
         buffer = buff_tmp
      endif
      if ( size(buffer, kind=INT64) > huge(0)) then
        _FAIL("need to increase oserver's number of front cores (nfront)")
      endif
      _RETURN(_SUCCESS)

   end subroutine serialize

   subroutine deserialize(this, buffer, rc)
      class (ForwardDataAndMessage), intent(inout) :: this
      integer, intent(in) :: buffer(:)
      integer, optional, intent(out) :: rc

      integer :: n
      !integer :: k
      
      call deserialize_message_vector(buffer,this%msg_vec)
      n = 1 + buffer(1)
      !k = 0
      if (size(buffer) > n) then
         allocate(this%idata(buffer(n)-1))
         this%idata(:) = buffer(n+1:)
         !k = buffer(n)
      endif
      !_ASSERT(size(buffer) == buffer(1)+ k,"buffer size does not match")
      _RETURN(_SUCCESS)
   end subroutine deserialize

   subroutine add_data_message(this, msg, i_ptr, rc)
      class (ForwardDataAndMessage), intent(inout) :: this
      class (AbstractMessage) :: msg
      integer, intent(in) :: i_ptr(:)
      integer, optional, intent(out) :: rc
     
      call this%msg_vec%push_back(msg)
      if (size(i_ptr) ==0 ) then
         _RETURN(_SUCCESS)
      endif
      if (.not. allocated(this%idata)) then
         this%idata = [i_ptr]
      else
         this%idata = [this%idata, i_ptr]
      endif

      _RETURN(_SUCCESS)
   end subroutine

   subroutine destroy(this, rc)
      class (ForwardDataAndMessage), intent(inout) :: this
      integer, optional, intent(out) :: rc
      type (MessageVectorIterator) :: iter

      if (allocated(this%idata)) deallocate(this%idata)
      iter = this%msg_vec%begin()
      do while (iter /= this%msg_vec%end())
        call this%msg_vec%erase(iter)
        iter = this%msg_vec%begin()
     enddo
      _RETURN(_SUCCESS)
   end subroutine

end module pFIO_ForwardDataAndMessageMod