MAPL_MinMax.F90 Source File


Files dependent on this one

sourcefile~~mapl_minmax.f90~~AfferentGraph sourcefile~mapl_minmax.f90 MAPL_MinMax.F90 sourcefile~create_basic_grid.f90 create_basic_grid.F90 sourcefile~create_basic_grid.f90->sourcefile~mapl_minmax.f90 sourcefile~cubedspheregeomfactory_smod.f90 CubedSphereGeomFactory_smod.F90 sourcefile~cubedspheregeomfactory_smod.f90->sourcefile~mapl_minmax.f90 sourcefile~fill_coordinates.f90 fill_coordinates.F90 sourcefile~fill_coordinates.f90->sourcefile~mapl_minmax.f90 sourcefile~make_file_metadata.f90 make_file_metadata.F90 sourcefile~make_file_metadata.f90->sourcefile~mapl_minmax.f90 sourcefile~make_geom.f90 make_geom.F90 sourcefile~make_geom.f90->sourcefile~mapl_minmax.f90 sourcefile~make_gridded_dims.f90 make_gridded_dims.F90 sourcefile~make_gridded_dims.f90->sourcefile~mapl_minmax.f90 sourcefile~mapl_cubedspheregridfactory.f90 MAPL_CubedSphereGridFactory.F90 sourcefile~mapl_cubedspheregridfactory.f90->sourcefile~mapl_minmax.f90 sourcefile~mapl_externalgridfactory.f90 MAPL_ExternalGridFactory.F90 sourcefile~mapl_externalgridfactory.f90->sourcefile~mapl_minmax.f90 sourcefile~mapl_latlongridfactory.f90 MAPL_LatLonGridFactory.F90 sourcefile~mapl_latlongridfactory.f90->sourcefile~mapl_minmax.f90 sourcefile~mapl_swathgridfactory.f90 MAPL_SwathGridFactory.F90 sourcefile~mapl_swathgridfactory.f90->sourcefile~mapl_minmax.f90 sourcefile~maplshared.f90 MaplShared.F90 sourcefile~maplshared.f90->sourcefile~mapl_minmax.f90 sourcefile~test_latlon_corners.pf Test_LatLon_Corners.pf sourcefile~test_latlon_corners.pf->sourcefile~mapl_minmax.f90 sourcefile~test_latlon_corners.pf->sourcefile~mapl_latlongridfactory.f90 sourcefile~test_latlon_gridfactory.pf Test_LatLon_GridFactory.pf sourcefile~test_latlon_gridfactory.pf->sourcefile~mapl_minmax.f90 sourcefile~test_latlon_gridfactory.pf->sourcefile~mapl_latlongridfactory.f90 sourcefile~typesafe_make_file_metadata.f90 typesafe_make_file_metadata.F90 sourcefile~typesafe_make_file_metadata.f90->sourcefile~mapl_minmax.f90 sourcefile~typesafe_make_geom.f90 typesafe_make_geom.F90 sourcefile~typesafe_make_geom.f90->sourcefile~mapl_minmax.f90 sourcefile~base.f90 Base.F90 sourcefile~base.f90->sourcefile~mapl_cubedspheregridfactory.f90 sourcefile~base.f90->sourcefile~mapl_externalgridfactory.f90 sourcefile~base.f90->sourcefile~mapl_latlongridfactory.f90 sourcefile~componentdriver.f90 ComponentDriver.F90 sourcefile~componentdriver.f90->sourcefile~maplshared.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~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~mapl_externalgridfactory.f90 sourcefile~mapl_cfio.f90 MAPL_CFIO.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_latlongridfactory.f90 sourcefile~mapl_generic.f90 MAPL_Generic.F90 sourcefile~mapl_generic.f90->sourcefile~maplshared.f90 sourcefile~mapl_gridmanager.f90 MAPL_GridManager.F90 sourcefile~mapl_gridmanager.f90->sourcefile~mapl_cubedspheregridfactory.f90 sourcefile~mapl_gridmanager.f90->sourcefile~mapl_externalgridfactory.f90 sourcefile~mapl_gridmanager.f90->sourcefile~mapl_latlongridfactory.f90 sourcefile~mapl_gridmanager.f90->sourcefile~mapl_swathgridfactory.f90 sourcefile~regrid_util.f90 Regrid_Util.F90 sourcefile~regrid_util.f90->sourcefile~mapl_cubedspheregridfactory.f90 sourcefile~regrid_util.f90->sourcefile~mapl_latlongridfactory.f90 sourcefile~test_sphericaltocartesian.pf Test_SphericalToCartesian.pf sourcefile~test_sphericaltocartesian.pf->sourcefile~mapl_latlongridfactory.f90

Source Code

module MAPL_MinMaxMod
   use, intrinsic :: iso_fortran_env, only: REAL32, REAL64
   implicit none
   private

   public :: IntegerMinMax
   public :: RealMinMax
   public :: Real64MinMax

   type IntegerMinMax
      integer :: min
      integer :: max
    end type IntegerMinMax

   type RealMinMax
      real(kind=REAL32) :: min
      real(kind=REAL32) :: max
   contains
      procedure :: equal_real
      procedure :: not_equal_real
      generic :: operator(==) => equal_real
      generic :: operator(/=) => not_equal_real
    end type RealMinMax

   type Real64MinMax
      real(kind=REAL64) :: min
      real(kind=REAL64) :: max
    end type Real64MinMax

contains


   logical function equal_real(a, b)
      class (RealMinMax), intent(in) :: a
      type (RealMinMax), intent(in) :: b

      equal_real = (a%min == b%min) .and. (a%max == b%max)
   end function equal_real


   logical function not_equal_real(a, b)
      class (RealMinMax), intent(in) :: a
      type (RealMinMax), intent(in) :: b

      not_equal_real = .not. (a==b)

   end function not_equal_real

end module MAPL_MinMaxMod