AbstractMessage.F90 Source File


This file depends on

sourcefile~~abstractmessage.f90~~EfferentGraph sourcefile~abstractmessage.f90 AbstractMessage.F90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.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~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

AbstractMessage.F90wAbstractCollectiveDataMessage.F90
w
wAbstractDataMessage.F90
w
wAbstractServer.F90
w
wAddReadDataCollectionMessage.F90
w
wAddWriteDataCollectionMessage.F90
w
wBaseServer.F90
w
wClientThread.F90
w
wCollectivePrefetchDataMessage.F90
w
wCollectivePrefetchDoneMessage.F90
w
wCollectiveStageDataMessage.F90
w
wCollectiveStageDoneMessage.F90
w
wDoneMessage.F90
w
wDummyMessage.F90
w
wFastClientThread.F90
w
wForwardDataAndMessage.F90
w
wForwardDataMessage.F90
w
wHandShakeMessage.F90
w
wIDMessage.F90
w
wIntegerMessageMap.F90
w
wMessageVector.F90
w
wMessageVisitor.F90
w
wMockClientThread.F90
w
wMockServerThread.F90
w
wMockSocket.F90
w
wModifyMetadataMessage.F90
w
wMpiSocket.F90
w
wMultiCommServer.F90
w
wMultiGroupServer.F90
w
wMultiLayerServer.F90
w
wpfio_writer.F90
w
wPrefetchDataMessage.F90
w
wPrefetchDoneMessage.F90
w
wProtocolParser.F90
w
wReplaceMetadataMessage.F90
w
wServerThread.F90
w
wSimpleSocket.F90
w
wStageDataMessage.F90
w
wStageDoneMessage.F90
w
wTerminateMessage.F90
w
wTest_Client.pf
w
wTest_MpiSocket.pf
w
wTest_ProtocolParser.pf
w
wTest_ServerThread.pf
w
wTest_SimpleSocket.pf
w

Source Code

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

module pFIO_AbstractMessageMod
   use MAPL_ExceptionHandling
   implicit none
   private

   public :: AbstractMessage
   public :: SurrogateMessageVisitor

   public :: TERMINATE_ID
   public :: DONE_ID
   public :: PrefetchDone_ID
   public :: CollectivePrefetchDone_ID
   public :: StageDone_ID
   public :: CollectiveStageDone_ID
   public :: ADD_READATA_COLLECTION_ID
   public :: ADD_WRITEDATA_COLLECTION_ID
   public :: ID_ID
   public :: PrefetchData_ID
   public :: StageData_ID
   public :: COLLECTIVEPrefetchData_ID
   public :: COLLECTIVEStageData_ID
   public :: ModifyMetadata_ID
   public :: ReplaceMetadata_ID
   public :: HandShake_ID
   public :: DUMMY_ID
   public :: ForwardData_ID

   enum, bind(c)
      enumerator :: TERMINATE_ID = 1
      enumerator :: DONE_ID
      enumerator :: PrefetchDone_ID
      enumerator :: CollectivePrefetchDone_ID
      enumerator :: StageDone_ID
      enumerator :: CollectiveStageDone_ID
      enumerator :: ADD_READATA_COLLECTION_ID
      enumerator :: ADD_WRITEDATA_COLLECTION_ID
      enumerator :: ID_ID
      enumerator :: PrefetchData_ID
      enumerator :: COLLECTIVEPrefetchData_ID
      enumerator :: StageData_ID
      enumerator :: COLLECTIVEStageData_ID
      enumerator :: ModifyMetadata_ID
      enumerator :: ReplaceMetadata_ID
      enumerator :: HandShake_ID
      enumerator :: DUMMY_ID
      enumerator :: ForwardData_ID 
   end enum

   type, abstract :: AbstractMessage
   contains
      procedure (get_type_id), deferred, nopass :: get_type_id
      procedure (get_length),  deferred :: get_length
      procedure (serialize),   deferred :: serialize
      procedure (deserialize), deferred :: deserialize
      procedure :: dispatch
   end type AbstractMessage

   type, abstract :: SurrogateMessageVisitor
   contains
     procedure(handle), deferred :: handle
   end type SurrogateMessageVisitor

   abstract interface

     subroutine handle(this, Message, rc)
       import SurrogateMessageVisitor
       import AbstractMessage
       implicit none
       class (SurrogateMessageVisitor), target, intent(inout) :: this
       class (AbstractMessage), target, intent(in) :: message
       integer, optional, intent(out) :: rc
     end subroutine handle

     integer function get_type_id() result(type_id)
        implicit none
     end function get_type_id
      
     integer function get_length(this) result(length)
        import AbstractMessage
        implicit none
        class (AbstractMessage), intent(in) :: this
     end function get_length
      
     subroutine serialize(this, buffer, rc)
        import AbstractMessage
        implicit none
        class (AbstractMessage), intent(in) :: this
        integer, optional, intent(out) :: rc
        integer, intent(inout) :: buffer(:)
     end subroutine serialize
      
     subroutine deserialize(this, buffer, rc)
        import AbstractMessage
        implicit none
        class (AbstractMessage), intent(inout) :: this
        integer, intent(in) :: buffer(:)
        integer, optional, intent(out) :: rc
     end subroutine deserialize
      
   end interface

 contains

    recursive subroutine dispatch(this, visitor, rc)
       class (AbstractMessage), intent(in) :: this
       class (SurrogateMessageVisitor), target, intent(inout) :: visitor
       integer, optional, intent(out) :: rc
       integer :: status

       call visitor%handle(this, rc=status)
       _VERIFY(status)
       _RETURN(_SUCCESS)
    end subroutine dispatch

end module pFIO_AbstractMessageMod