GeomSpec.F90 Source File


Files dependent on this one

sourcefile~~geomspec.f90~~AfferentGraph sourcefile~geomspec.f90 GeomSpec.F90 sourcefile~create_basic_grid.f90 create_basic_grid.F90 sourcefile~create_basic_grid.f90->sourcefile~geomspec.f90 sourcefile~cubedspheregeomfactory.f90 CubedSphereGeomFactory.F90 sourcefile~cubedspheregeomfactory.f90->sourcefile~geomspec.f90 sourcefile~cubedspheregeomfactory_smod.f90 CubedSphereGeomFactory_smod.F90 sourcefile~cubedspheregeomfactory_smod.f90->sourcefile~geomspec.f90 sourcefile~cubedspheregeomspec.f90 CubedSphereGeomSpec.F90 sourcefile~cubedspheregeomspec.f90->sourcefile~geomspec.f90 sourcefile~cubedspheregeomspec_smod.f90 CubedSphereGeomSpec_smod.F90 sourcefile~cubedspheregeomspec_smod.f90->sourcefile~geomspec.f90 sourcefile~equal_to.f90~2 equal_to.F90 sourcefile~equal_to.f90~2->sourcefile~geomspec.f90 sourcefile~fill_coordinates.f90 fill_coordinates.F90 sourcefile~fill_coordinates.f90->sourcefile~geomspec.f90 sourcefile~geom_mgr.f90 geom_mgr.F90 sourcefile~geom_mgr.f90->sourcefile~geomspec.f90 sourcefile~geomspecvector.f90 GeomSpecVector.F90 sourcefile~geomspecvector.f90->sourcefile~geomspec.f90 sourcefile~latlongeomfactory.f90 LatLonGeomFactory.F90 sourcefile~latlongeomfactory.f90->sourcefile~geomspec.f90 sourcefile~latlongeomspec.f90 LatLonGeomSpec.F90 sourcefile~latlongeomspec.f90->sourcefile~geomspec.f90 sourcefile~make_decomposition.f90 make_decomposition.F90 sourcefile~make_decomposition.f90->sourcefile~geomspec.f90 sourcefile~make_distribution.f90 make_distribution.F90 sourcefile~make_distribution.f90->sourcefile~geomspec.f90 sourcefile~make_file_metadata.f90 make_file_metadata.F90 sourcefile~make_file_metadata.f90->sourcefile~geomspec.f90 sourcefile~make_geom.f90 make_geom.F90 sourcefile~make_geom.f90->sourcefile~geomspec.f90 sourcefile~make_gridded_dims.f90 make_gridded_dims.F90 sourcefile~make_gridded_dims.f90->sourcefile~geomspec.f90 sourcefile~make_latlongeomspec_from_hconfig.f90 make_LatLonGeomSpec_from_hconfig.F90 sourcefile~make_latlongeomspec_from_hconfig.f90->sourcefile~geomspec.f90 sourcefile~make_latlongeomspec_from_metadata.f90 make_LatLonGeomSpec_from_metadata.F90 sourcefile~make_latlongeomspec_from_metadata.f90->sourcefile~geomspec.f90 sourcefile~nullgeomspec.f90 NullGeomSpec.F90 sourcefile~nullgeomspec.f90->sourcefile~geomspec.f90 sourcefile~supports_hconfig.f90~2 supports_hconfig.F90 sourcefile~supports_hconfig.f90~2->sourcefile~geomspec.f90 sourcefile~supports_metadata.f90~2 supports_metadata.F90 sourcefile~supports_metadata.f90~2->sourcefile~geomspec.f90 sourcefile~test_cubedspheregeomfactory.pf Test_CubedSphereGeomFactory.pf sourcefile~test_cubedspheregeomfactory.pf->sourcefile~geomspec.f90 sourcefile~test_latlongeomfactory.pf Test_LatLonGeomFactory.pf sourcefile~test_latlongeomfactory.pf->sourcefile~geomspec.f90 sourcefile~typesafe_make_file_metadata.f90 typesafe_make_file_metadata.F90 sourcefile~typesafe_make_file_metadata.f90->sourcefile~geomspec.f90 sourcefile~typesafe_make_geom.f90 typesafe_make_geom.F90 sourcefile~typesafe_make_geom.f90->sourcefile~geomspec.f90

Source Code

#include "MAPL_Generic.h"

module mapl3g_GeomSpec
   use esmf
   implicit none
   private

   public :: GeomSpec
   public :: NULL_GEOM_SPEC

   type, abstract :: GeomSpec
      private
   contains
      procedure(I_equal_to), deferred :: equal_to
      generic :: operator(==) => equal_to
   end type GeomSpec


   abstract interface
      logical function I_equal_to(a, b)
         import GeomSpec
         class(GeomSpec), intent(in) :: a
         class(GeomSpec), intent(in) :: b
      end function I_equal_to
   end interface


   type, extends(GeomSpec) :: NullGeomSpec
   contains
      procedure :: equal_to => false
   end type NullGeomSpec

   type(NullGeomSpec) :: NULL_GEOM_SPEC

contains

   logical function false(a,b)
      class(NullGeomSpec), intent(in) :: a
      class(GeomSpec), intent(in) :: b
      false = .false.
   end function false
   
end module mapl3g_GeomSpec