FieldBundleType_Flag.F90 Source File


Files dependent on this one

sourcefile~~fieldbundletype_flag.f90~~AfferentGraph sourcefile~fieldbundletype_flag.f90 FieldBundleType_Flag.F90 sourcefile~fieldbundledelta.f90 FieldBundleDelta.F90 sourcefile~fieldbundledelta.f90->sourcefile~fieldbundletype_flag.f90 sourcefile~fieldbundleget.f90 FieldBundleGet.F90 sourcefile~fieldbundledelta.f90->sourcefile~fieldbundleget.f90 sourcefile~fieldbundleget.f90->sourcefile~fieldbundletype_flag.f90 sourcefile~fieldbundleinfo.f90 FieldBundleInfo.F90 sourcefile~fieldbundleget.f90->sourcefile~fieldbundleinfo.f90 sourcefile~fieldbundleinfo.f90->sourcefile~fieldbundletype_flag.f90 sourcefile~sharedio.f90 SharedIO.F90 sourcefile~sharedio.f90->sourcefile~fieldbundleget.f90 sourcefile~test_fieldbundledelta.pf Test_FieldBundleDelta.pf sourcefile~test_fieldbundledelta.pf->sourcefile~fieldbundledelta.f90 sourcefile~test_fieldbundledelta.pf->sourcefile~fieldbundleget.f90 sourcefile~test_timeinterpolateaction.pf Test_TimeInterpolateAction.pf sourcefile~test_timeinterpolateaction.pf->sourcefile~fieldbundleget.f90 sourcefile~timeinterpolateaction.f90 TimeInterpolateAction.F90 sourcefile~test_timeinterpolateaction.pf->sourcefile~timeinterpolateaction.f90 sourcefile~timeinterpolateaction.f90->sourcefile~fieldbundleget.f90 sourcefile~geom_pfio.f90 Geom_PFIO.F90 sourcefile~geom_pfio.f90->sourcefile~sharedio.f90 sourcefile~geomio.f90 GeomIO.F90 sourcefile~geomio.f90->sourcefile~sharedio.f90 sourcefile~geomio.f90->sourcefile~geom_pfio.f90 sourcefile~grid_pfio.f90 Grid_PFIO.F90 sourcefile~grid_pfio.f90->sourcefile~sharedio.f90 sourcefile~grid_pfio.f90->sourcefile~geom_pfio.f90 sourcefile~restarthandler.f90 RestartHandler.F90 sourcefile~restarthandler.f90->sourcefile~sharedio.f90 sourcefile~restarthandler.f90->sourcefile~geomio.f90 sourcefile~test_sharedio.pf Test_SharedIO.pf sourcefile~test_sharedio.pf->sourcefile~sharedio.f90 sourcefile~geomcatagorizer.f90 GeomCatagorizer.F90 sourcefile~geomcatagorizer.f90->sourcefile~geom_pfio.f90 sourcefile~geomcatagorizer.f90->sourcefile~grid_pfio.f90 sourcefile~historycollectiongridcomp.f90 HistoryCollectionGridComp.F90 sourcefile~historycollectiongridcomp.f90->sourcefile~geomio.f90 sourcefile~read_restart.f90~2 read_restart.F90 sourcefile~read_restart.f90~2->sourcefile~restarthandler.f90 sourcefile~write_restart.f90 write_restart.F90 sourcefile~write_restart.f90->sourcefile~restarthandler.f90

Source Code

module mapl3g_FieldBundleType_Flag
   implicit none
   private

   public :: FieldBundleType_Flag
   public :: FIELDBUNDLETYPE_BASIC
   public :: FIELDBUNDLETYPE_BRACKET
   public :: FIELDBUNDLETYPE_INVALID

   public :: operator(==)
   public :: operator(/=)

   type :: FieldBundleType_Flag
      private
      integer :: id = -1
      character(32) :: name = "FIELDBUNDLETYPE_INVALID"
   contains
      procedure :: to_string
   end type Fieldbundletype_Flag

   interface FieldBundleType_Flag
      procedure new_FieldBundleType_Flag
   end interface FieldBundleType_Flag

   interface operator(==)
      procedure equal_to
   end interface operator(==)

   interface operator(/=)
      procedure not_equal_to
   end interface operator(/=)

   type(FieldBundleType_Flag), parameter :: FIELDBUNDLETYPE_BASIC = FieldBundleType_Flag(1, "FIELDBUNDLETYPE_BASIC")
   type(FieldBundleType_Flag), parameter :: FIELDBUNDLETYPE_BRACKET = FieldBundleType_Flag(2, "FIELDBUNDLETYPE_BRACKET")
   type(FieldBundleType_Flag), parameter :: FIELDBUNDLETYPE_INVALID = FieldBundleType_Flag(-1, "FIELDBUNDLETYPE_INVALID")

contains

   function new_FieldBundleType_Flag(name) result (type_flag)
      character(*), intent(in) :: name
      type(FieldBundleType_Flag) :: type_flag

      select case (name)
      case ("FIELDBUNDLETYPE_BASIC")
         type_flag = FIELDBUNDLETYPE_BASIC
      case ("FIELDBUNDLETYPE_BRACKET")
         type_flag = FIELDBUNDLETYPE_BRACKET
      case default
         type_flag = FIELDBUNDLETYPE_INVALID
      end select

   end function new_FieldBundleType_Flag

   function to_string(this) result(s)
      character(:), allocatable :: s
      class(FieldBundleType_Flag), intent(in) :: this

      s = trim(this%name)

   end function to_string


   elemental logical function equal_to(a,b)
      type(FieldBundleType_Flag), intent(in) :: a,b
      equal_to = a%id == b%id
   end function equal_to

   elemental logical function not_equal_to(a,b)
      type(FieldBundleType_Flag), intent(in) :: a,b
      not_equal_to = .not. (a%id == b%id)
   end function not_equal_to
   
end module mapl3g_FieldBundleType_Flag