generalized_equality.F90 Source File


Files dependent on this one

sourcefile~~generalized_equality.f90~~AfferentGraph sourcefile~generalized_equality.f90 generalized_equality.F90 sourcefile~hconfig_get_private.f90 hconfig_get_private.F90 sourcefile~hconfig_get_private.f90->sourcefile~generalized_equality.f90 sourcefile~hconfig_get.f90 hconfig_get.F90 sourcefile~hconfig_get.f90->sourcefile~hconfig_get_private.f90 sourcefile~test_hconfig_get_private.pf Test_hconfig_get_private.pf sourcefile~test_hconfig_get_private.pf->sourcefile~hconfig_get_private.f90 sourcefile~hconfig3g.f90 HConfig3G.F90 sourcefile~hconfig3g.f90->sourcefile~hconfig_get.f90 sourcefile~mapl_generic.f90~2 MAPL_Generic.F90 sourcefile~mapl_generic.f90~2->sourcefile~hconfig_get.f90 sourcefile~generic3g.f90 Generic3g.F90 sourcefile~generic3g.f90->sourcefile~mapl_generic.f90~2 sourcefile~mapl3_deprecated.f90 MAPL3_Deprecated.F90 sourcefile~mapl3_deprecated.f90->sourcefile~mapl_generic.f90~2 sourcefile~protoextdatagc.f90 ProtoExtDataGC.F90 sourcefile~protoextdatagc.f90->sourcefile~mapl_generic.f90~2 sourcefile~simpleleafgridcomp.f90 SimpleLeafGridComp.F90 sourcefile~simpleleafgridcomp.f90->sourcefile~mapl_generic.f90~2 sourcefile~simpleparentgridcomp.f90 SimpleParentGridComp.F90 sourcefile~simpleparentgridcomp.f90->sourcefile~mapl_generic.f90~2 sourcefile~test_runchild.pf Test_RunChild.pf sourcefile~test_runchild.pf->sourcefile~mapl_generic.f90~2 sourcefile~test_scenarios.pf Test_Scenarios.pf sourcefile~test_scenarios.pf->sourcefile~mapl_generic.f90~2 sourcefile~test_simpleleafgridcomp.pf Test_SimpleLeafGridComp.pf sourcefile~test_simpleleafgridcomp.pf->sourcefile~mapl_generic.f90~2 sourcefile~test_simpleparentgridcomp.pf Test_SimpleParentGridComp.pf sourcefile~test_simpleparentgridcomp.pf->sourcefile~mapl_generic.f90~2

Source Code

module mapl3g_generalized_equality

   use :: esmf, only: ESMF_KIND_R4, ESMF_KIND_R8, ESMF_KIND_I4, ESMF_KIND_I8
   implicit none
   private

   public :: are_equal

   interface are_equal
      procedure :: equals_i4_scalar
      procedure :: equals_i8_scalar
      procedure :: equals_r4_scalar
      procedure :: equals_r8_scalar
      procedure :: equals_l_scalar
      procedure :: equals_string
      procedure :: equals_i4_array
      procedure :: equals_i8_array
      procedure :: equals_r4_array
      procedure :: equals_r8_array
      procedure :: equals_l_array
   end interface

contains

   logical function equals_i4_scalar(u, v) result(lval)
      integer(kind=ESMF_KIND_I4), intent(in) :: u, v

      lval = (u == v)

   end function equals_i4_scalar

   logical function equals_i8_scalar(u, v) result(lval)
      integer(kind=ESMF_KIND_I8), intent(in) :: u, v

      lval = (u == v)

   end function equals_i8_scalar

   logical function equals_r4_scalar(u, v) result(lval)
      real(kind=ESMF_KIND_R4), intent(in) :: u, v

      lval = (u == v)

   end function equals_r4_scalar

   logical function equals_r8_scalar(u, v) result(lval)
      real(kind=ESMF_KIND_R8), intent(in) :: u, v

      lval = (u == v)

   end function equals_r8_scalar

   logical function equals_l_scalar(u, v) result(lval)
      logical, intent(in) :: u, v

      lval = (u .eqv. v)

   end function equals_l_scalar

   logical function equals_string(u, v) result(lval)
      character(len=:), allocatable, intent(in) :: u
      character(len=*), intent(in) :: v

      lval = (u == v)

   end function equals_string

   logical function equals_i4_array(u, v) result(lval)
      integer(kind=ESMF_KIND_I4), allocatable, intent(in) :: u(:)
      integer(kind=ESMF_KIND_I4), intent(in) :: v(:)

      lval = all(u == v)

   end function equals_i4_array

   logical function equals_i8_array(u, v) result(lval)
      integer(kind=ESMF_KIND_I8), allocatable, intent(in) :: u(:)
      integer(kind=ESMF_KIND_I8), intent(in) :: v(:)

      lval = all(u == v)

   end function equals_i8_array

   logical function equals_r4_array(u, v) result(lval)
      real(kind=ESMF_KIND_R4), allocatable, intent(in) :: u(:)
      real(kind=ESMF_KIND_R4), intent(in) :: v(:)

      lval = all(u == v)

   end function equals_r4_array

   logical function equals_r8_array(u, v) result(lval)
      real(kind=ESMF_KIND_R8), allocatable, intent(in) :: u(:)
      real(kind=ESMF_KIND_R8), intent(in) :: v(:)

      lval = all(u == v)

   end function equals_r8_array

   logical function equals_l_array(u, v) result(lval)
      logical, allocatable, intent(in) :: u(:)
      logical, intent(in) :: v(:)

      lval = all(u .eqv. v)

   end function equals_l_array

end module mapl3g_generalized_equality