ForwardDataMessage.F90 Source File


This file depends on

sourcefile~~forwarddatamessage.f90~~EfferentGraph sourcefile~forwarddatamessage.f90 ForwardDataMessage.F90 sourcefile~abstractdatamessage.f90 AbstractDataMessage.F90 sourcefile~forwarddatamessage.f90->sourcefile~abstractdatamessage.f90 sourcefile~abstractdatareference.f90 AbstractDataReference.F90 sourcefile~forwarddatamessage.f90->sourcefile~abstractdatareference.f90 sourcefile~abstractmessage.f90 AbstractMessage.F90 sourcefile~forwarddatamessage.f90->sourcefile~abstractmessage.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~forwarddatamessage.f90->sourcefile~keywordenforcer.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~forwarddatamessage.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~pfio_utilities.f90 pFIO_Utilities.F90 sourcefile~forwarddatamessage.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~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~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

sourcefile~~forwarddatamessage.f90~~AfferentGraph sourcefile~forwarddatamessage.f90 ForwardDataMessage.F90 sourcefile~multicommserver.f90 MultiCommServer.F90 sourcefile~multicommserver.f90->sourcefile~forwarddatamessage.f90 sourcefile~multilayerserver.f90 MultiLayerServer.F90 sourcefile~multilayerserver.f90->sourcefile~forwarddatamessage.f90 sourcefile~pfio_writer.f90 pfio_writer.F90 sourcefile~pfio_writer.f90->sourcefile~forwarddatamessage.f90 sourcefile~protocolparser.f90 ProtocolParser.F90 sourcefile~protocolparser.f90->sourcefile~forwarddatamessage.f90 sourcefile~directoryservice.f90 DirectoryService.F90 sourcefile~directoryservice.f90->sourcefile~protocolparser.f90 sourcefile~messagevector.f90 MessageVector.F90 sourcefile~messagevector.f90->sourcefile~protocolparser.f90 sourcefile~mpisocket.f90 MpiSocket.F90 sourcefile~mpisocket.f90->sourcefile~protocolparser.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~pfio.f90->sourcefile~multicommserver.f90 sourcefile~pfio.f90->sourcefile~multilayerserver.f90 sourcefile~test_mpisocket.pf Test_MpiSocket.pf sourcefile~test_mpisocket.pf->sourcefile~protocolparser.f90 sourcefile~test_protocolparser.pf Test_ProtocolParser.pf sourcefile~test_protocolparser.pf->sourcefile~protocolparser.f90

Source Code

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

module pFIO_ForwardDataMessageMod
   use mpi
   use MAPL_ExceptionHandling
   use pFIO_AbstractMessageMod
   use pFIO_UtilitiesMod
   use pFIO_AbstractDataReferenceMod
   use mapl_KeywordEnforcerMod
   use pFIO_AbstractDataMessageMod
   implicit none
   private

   public :: ForwardDataMessage

   type, extends(AbstractMessage) :: ForwardDataMessage
      integer :: request_id
      integer :: collection_id
      character(len=:), allocatable :: file_name
      character(len=:), allocatable :: var_name
      integer :: type_kind
      integer, allocatable :: count(:)
      integer(kind=MPI_ADDRESS_KIND) :: offset 
   contains
      procedure, nopass :: get_type_id
      procedure :: get_length
      procedure :: serialize
      procedure :: deserialize
   end type ForwardDataMessage

   interface ForwardDataMessage
      module procedure new_ForwardDataMessage
   end interface ForwardDataMessage

contains

   integer function get_type_id() result(type_id)
      type_id = ForwardData_ID
   end function get_type_id

   function new_ForwardDataMessage( &
        & request_id, collection_id, file_name, var_name, &
        & type_kind, count, offset) result(message)
      type (ForwardDataMessage) :: message
      integer, intent(in) :: request_id
      integer, intent(in) :: collection_id
      character(len=*), intent(in) :: file_name
      character(len=*), intent(in) :: var_name
      integer :: type_kind
      integer, intent(in) :: count(:)
      integer(kind=MPI_ADDRESS_KIND), intent(in) :: offset 

      message%request_id    = request_id
      message%collection_id = collection_id
      message%file_name = file_name
      message%var_name  = var_name
      message%type_kind = type_kind

      message%count = count
      message%offset = offset

   end function new_ForwardDataMessage

   integer function get_length(this) result(length)
      class (ForwardDataMessage), intent(in) :: this

      length = &
           & serialize_buffer_length(this%request_id) + &
           & serialize_buffer_length(this%collection_id) + &
           & serialize_buffer_length(this%file_name) + &
           & serialize_buffer_length(this%var_name) + &
           & serialize_buffer_length(this%type_kind) + &
           & serialize_buffer_length(this%count) + &
           & serialize_buffer_length(this%offset)
   end function get_length

   subroutine serialize(this, buffer, rc)
      class (ForwardDataMessage), intent(in) :: this
      integer, intent(inout) :: buffer(:)
      integer, optional, intent(out) :: rc

      buffer = [ &
           & serialize_intrinsic(this%request_id), &
           & serialize_intrinsic(this%collection_id), &
           & serialize_intrinsic(this%file_name), &
           & serialize_intrinsic(this%var_name), &
           & serialize_intrinsic(this%type_kind), &
           & serialize_intrinsic(this%count), &
           & serialize_intrinsic(this%offset)]
      _RETURN(_SUCCESS)
   end subroutine serialize

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

      integer :: n

      n = 1
      call deserialize_intrinsic(buffer(n:), this%request_id)
      n = n + serialize_buffer_length(this%request_id)
      call deserialize_intrinsic(buffer(n:), this%collection_id)
      n = n + serialize_buffer_length(this%collection_id)
      call deserialize_intrinsic(buffer(n:), this%file_name)
      n = n + serialize_buffer_length(this%file_name)
      call deserialize_intrinsic(buffer(n:),this%var_name)
      n = n + serialize_buffer_length(this%var_name)
      call deserialize_intrinsic(buffer(n:), this%type_kind)
      n = n + serialize_buffer_length(this%type_kind)
      call deserialize_intrinsic(buffer(n:), this%count)
      n = n + serialize_buffer_length(this%count)
      call deserialize_intrinsic(buffer(n:), this%offset)
      n = n + serialize_buffer_length(this%offset)
      _RETURN(_SUCCESS)
   end subroutine deserialize

end module pFIO_ForwardDataMessageMod