CollectiveStageDoneMessage.F90 Source File


This file depends on

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

sourcefile~~collectivestagedonemessage.f90~~AfferentGraph sourcefile~collectivestagedonemessage.f90 CollectiveStageDoneMessage.F90 sourcefile~clientthread.f90 ClientThread.F90 sourcefile~clientthread.f90->sourcefile~collectivestagedonemessage.f90 sourcefile~messagevisitor.f90 MessageVisitor.F90 sourcefile~clientthread.f90->sourcefile~messagevisitor.f90 sourcefile~messagevisitor.f90->sourcefile~collectivestagedonemessage.f90 sourcefile~protocolparser.f90 ProtocolParser.F90 sourcefile~protocolparser.f90->sourcefile~collectivestagedonemessage.f90 sourcefile~serverthread.f90 ServerThread.F90 sourcefile~serverthread.f90->sourcefile~collectivestagedonemessage.f90 sourcefile~serverthread.f90->sourcefile~messagevisitor.f90 sourcefile~baseserver.f90 BaseServer.F90 sourcefile~baseserver.f90->sourcefile~serverthread.f90 sourcefile~basethread.f90 BaseThread.F90 sourcefile~basethread.f90->sourcefile~messagevisitor.f90 sourcefile~clientmanager.f90 ClientManager.F90 sourcefile~clientmanager.f90->sourcefile~clientthread.f90 sourcefile~clientthreadvector.f90 ClientThreadVector.F90 sourcefile~clientthreadvector.f90->sourcefile~clientthread.f90 sourcefile~directoryservice.f90 DirectoryService.F90 sourcefile~directoryservice.f90->sourcefile~clientthread.f90 sourcefile~directoryservice.f90->sourcefile~protocolparser.f90 sourcefile~directoryservice.f90->sourcefile~serverthread.f90 sourcefile~fastclientthread.f90 FastClientThread.F90 sourcefile~fastclientthread.f90->sourcefile~clientthread.f90 sourcefile~maplframework.f90 MaplFramework.F90 sourcefile~maplframework.f90->sourcefile~clientthread.f90 sourcefile~messagevector.f90 MessageVector.F90 sourcefile~messagevector.f90->sourcefile~protocolparser.f90 sourcefile~mockclient.f90 MockClient.F90 sourcefile~mockclient.f90->sourcefile~clientthread.f90 sourcefile~mockclientthread.f90 MockClientThread.F90 sourcefile~mockclientthread.f90->sourcefile~clientthread.f90 sourcefile~mockclientthread.f90->sourcefile~messagevisitor.f90 sourcefile~mockserverthread.f90 MockServerThread.F90 sourcefile~mockserverthread.f90->sourcefile~messagevisitor.f90 sourcefile~mockserverthread.f90->sourcefile~serverthread.f90 sourcefile~mpiserver.f90 MpiServer.F90 sourcefile~mpiserver.f90->sourcefile~serverthread.f90 sourcefile~mpisocket.f90 MpiSocket.F90 sourcefile~mpisocket.f90->sourcefile~protocolparser.f90 sourcefile~multicommserver.f90 MultiCommServer.F90 sourcefile~multicommserver.f90->sourcefile~serverthread.f90 sourcefile~multigroupserver.f90 MultiGroupServer.F90 sourcefile~multigroupserver.f90->sourcefile~serverthread.f90 sourcefile~multilayerserver.f90 MultiLayerServer.F90 sourcefile~multilayerserver.f90->sourcefile~serverthread.f90 sourcefile~openmpserver.f90 OpenMPServer.F90 sourcefile~openmpserver.f90->sourcefile~serverthread.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~pfio.f90->sourcefile~clientthread.f90 sourcefile~pfio.f90->sourcefile~serverthread.f90 sourcefile~serverthreadvector.f90 ServerThreadVector.F90 sourcefile~serverthreadvector.f90->sourcefile~serverthread.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 sourcefile~test_serverthread.pf Test_ServerThread.pf sourcefile~test_serverthread.pf->sourcefile~serverthread.f90 sourcefile~test_simplesocket.pf Test_SimpleSocket.pf sourcefile~test_simplesocket.pf->sourcefile~clientthread.f90 sourcefile~test_simplesocket.pf->sourcefile~serverthread.f90

Source Code

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

module pFIO_CollectiveStageDoneMessageMod
   use MAPL_ExceptionHandling
   use pFIO_AbstractMessageMod
   use, intrinsic :: iso_fortran_env, only: INT32
   implicit none
   private

   public :: CollectiveStageDoneMessage

   type, extends(AbstractMessage) :: CollectiveStageDoneMessage
   contains
      procedure, nopass :: get_type_id
      procedure :: get_length
      procedure :: serialize
      procedure :: deserialize
   end type CollectiveStageDoneMessage

   interface CollectiveStageDoneMessage
      module procedure new_CollectiveStageDoneMessage
   end interface

contains

   ! The Intel 17 compiler's default constructor for this class appears to be
   ! broken.   Possibly due to the extension of an abstract base class.
   function new_CollectiveStageDoneMessage() result(message)
      type (CollectiveStageDoneMessage) :: message
      return
      _UNUSED_DUMMY(message)
   end function new_CollectiveStageDoneMessage

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

   integer function get_length(this) result(length)
      class (CollectiveStageDoneMessage), intent(in) :: this
      length = 0
      return
      _UNUSED_DUMMY(this)
   end function get_length

   subroutine serialize(this, buffer, rc)
      class (CollectiveStageDoneMessage), intent(in) :: this
      integer(kind=INT32), intent(inout) :: buffer(:) 
      integer, optional, intent(out) :: rc
      integer :: empty(0)

      buffer = empty
      _RETURN(_SUCCESS)
      _UNUSED_DUMMY(this)
   end subroutine serialize

   subroutine deserialize(this, buffer, rc)
      class (CollectiveStageDoneMessage), intent(inout) :: this
      integer(kind=INT32), intent(in) :: buffer(:)
      integer, optional, intent(out) :: rc
      _RETURN(_SUCCESS)
      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(buffer)
   end subroutine deserialize
   
end module pFIO_CollectiveStageDoneMessageMod