SplitCommunicator.F90 Source File


Files dependent on this one

sourcefile~~splitcommunicator.f90~~AfferentGraph sourcefile~splitcommunicator.f90 SplitCommunicator.F90 sourcefile~base.f90 Base.F90 sourcefile~base.f90->sourcefile~splitcommunicator.f90 sourcefile~servermanager.f90 ServerManager.F90 sourcefile~base.f90->sourcefile~servermanager.f90 sourcefile~simplecommsplitter.f90 SimpleCommSplitter.F90 sourcefile~base.f90->sourcefile~simplecommsplitter.f90 sourcefile~mapl_cap.f90 MAPL_Cap.F90 sourcefile~mapl_cap.f90->sourcefile~splitcommunicator.f90 sourcefile~mapl_cap.f90->sourcefile~servermanager.f90 sourcefile~mapl_cap.f90->sourcefile~simplecommsplitter.f90 sourcefile~maplshared.f90 MaplShared.F90 sourcefile~maplshared.f90->sourcefile~splitcommunicator.f90 sourcefile~maplshared.f90->sourcefile~simplecommsplitter.f90 sourcefile~multicommserver.f90 MultiCommServer.F90 sourcefile~multicommserver.f90->sourcefile~splitcommunicator.f90 sourcefile~multicommserver.f90->sourcefile~simplecommsplitter.f90 sourcefile~multigroupserver.f90 MultiGroupServer.F90 sourcefile~multigroupserver.f90->sourcefile~splitcommunicator.f90 sourcefile~multigroupserver.f90->sourcefile~simplecommsplitter.f90 sourcefile~servermanager.f90->sourcefile~splitcommunicator.f90 sourcefile~servermanager.f90->sourcefile~simplecommsplitter.f90 sourcefile~simplecommsplitter.f90->sourcefile~splitcommunicator.f90 sourcefile~componentdriver.f90 ComponentDriver.F90 sourcefile~componentdriver.f90->sourcefile~maplshared.f90 sourcefile~cubedspheregeomspec_smod.f90 CubedSphereGeomSpec_smod.F90 sourcefile~cubedspheregeomspec_smod.f90->sourcefile~base.f90 sourcefile~equal_to.f90~2 equal_to.F90 sourcefile~equal_to.f90~2->sourcefile~base.f90 sourcefile~extdatadrivermod.f90 ExtDataDriverMod.F90 sourcefile~extdatadrivermod.f90->sourcefile~servermanager.f90 sourcefile~extdataroot_gridcomp.f90 ExtDataRoot_GridComp.F90 sourcefile~extdataroot_gridcomp.f90->sourcefile~maplshared.f90 sourcefile~fieldunits.f90 FieldUnits.F90 sourcefile~fieldunits.f90->sourcefile~maplshared.f90 sourcefile~make_decomposition.f90 make_decomposition.F90 sourcefile~make_decomposition.f90->sourcefile~base.f90 sourcefile~make_distribution.f90 make_distribution.F90 sourcefile~make_distribution.f90->sourcefile~base.f90 sourcefile~make_latlongeomspec_from_hconfig.f90 make_LatLonGeomSpec_from_hconfig.F90 sourcefile~make_latlongeomspec_from_hconfig.f90->sourcefile~base.f90 sourcefile~make_latlongeomspec_from_metadata.f90 make_LatLonGeomSpec_from_metadata.F90 sourcefile~make_latlongeomspec_from_metadata.f90->sourcefile~base.f90 sourcefile~mapl.f90 MAPL.F90 sourcefile~mapl.f90->sourcefile~base.f90 sourcefile~mapl_bundleio_test.f90 mapl_bundleio_test.F90 sourcefile~mapl_bundleio_test.f90->sourcefile~servermanager.f90 sourcefile~mapl_generic.f90 MAPL_Generic.F90 sourcefile~mapl_generic.f90->sourcefile~maplshared.f90 sourcefile~mapl_gridcomps.f90 MAPL_GridComps.F90 sourcefile~mapl_gridcomps.f90->sourcefile~mapl_cap.f90 sourcefile~mapl_nuopcwrappermod.f90 MAPL_NUOPCWrapperMod.F90 sourcefile~mapl_nuopcwrappermod.f90->sourcefile~base.f90 sourcefile~mapl_nuopcwrappermod.f90->sourcefile~mapl_cap.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~pfio.f90->sourcefile~multicommserver.f90 sourcefile~pfio.f90->sourcefile~multigroupserver.f90 sourcefile~pfio_mapl_demo.f90 pfio_MAPL_demo.F90 sourcefile~pfio_mapl_demo.f90->sourcefile~simplecommsplitter.f90 sourcefile~regrid_util.f90 Regrid_Util.F90 sourcefile~regrid_util.f90->sourcefile~servermanager.f90 sourcefile~supports_hconfig.f90~2 supports_hconfig.F90 sourcefile~supports_hconfig.f90~2->sourcefile~base.f90 sourcefile~supports_metadata.f90~2 supports_metadata.F90 sourcefile~supports_metadata.f90~2->sourcefile~base.f90 sourcefile~test_cfio_bundle.pf Test_CFIO_Bundle.pf sourcefile~test_cfio_bundle.pf->sourcefile~base.f90 sourcefile~tstqsat.f90 tstqsat.F90 sourcefile~tstqsat.f90->sourcefile~base.f90 sourcefile~ut_extdata.f90 ut_ExtData.F90 sourcefile~ut_extdata.f90->sourcefile~base.f90 sourcefile~utcfio_bundle.f90 utCFIO_Bundle.F90 sourcefile~utcfio_bundle.f90->sourcefile~base.f90

Source Code

module MAPL_SplitCommunicatorMod
   implicit none
   private

   public :: SplitCommunicator
   public :: NULL_SUBCOMMUNICATOR_NAME

   type :: SplitCommunicator
      private
      integer :: subcommunicator
      integer :: color
      character(:), allocatable :: name
   contains
      procedure :: get_subcommunicator
      procedure :: get_color
      procedure :: get_name
   end type SplitCommunicator

   character(*), parameter :: NULL_SUBCOMMUNICATOR_NAME = 'NULL'

   interface SplitCommunicator
      module procedure new_SplitCommunicator
   end interface SplitCommunicator


contains


   function new_SplitCommunicator(subcommunicator, color, name) result(split)
      type (SplitCommunicator) :: split
      integer, intent(in) :: subcommunicator
      integer, intent(in) :: color
      character(*), intent(in) :: name

      split%subcommunicator = subcommunicator
      split%color = color
      split%name = name

   end function new_SplitCommunicator

   integer function get_subcommunicator(this) result(subcommunicator)
      class (SplitCommunicator), intent(in) :: this
      subcommunicator = this%subcommunicator
   end function get_subcommunicator
   
   integer function get_color(this) result(color)
      class (SplitCommunicator), intent(in) :: this
      color = this%color
   end function get_color
   
   function get_name(this) result(name)
      character(:), allocatable :: name
      class (SplitCommunicator), intent(in) :: this
      name = this%name
   end function get_name

   
end module MAPL_SplitCommunicatorMod