, TypeFamilies
, UnicodeSyntax
#-}
--- |FIXME: doc
+-- |Indirect equality comparison.
module Data.Eq.Indirect
( Eq'(..)
, (==:)
where
import Prelude.Unicode
-infix 4 ==:{-, /=:, ≡:, ≢:, ≠:-}
+infix 4 ==:, /=:, ≡:, ≢:, ≠:
--- |FIXME: doc
+-- |Type class for indirectly equality-comparable types. That is, any
+-- @α@ of @'Eq'' α@ has a monomorphism to some
+-- equality-comparable type @γ@ while @α@ itself isn't
+-- necessarily an instance of 'Eq'. This way we can generalise the
+-- '==' operator so that it can take two different types as long as
+-- they both have monomorphisms to the same 'Eq' type @γ@.
+--
+-- Minimal complete definition: 'Unified' and 'unify'.
class Eq (Unified α) ⇒ Eq' α where
- -- |FIXME: doc
+ -- |The said equality-comparable type @γ@.
type Unified α
- -- |FIXME: doc
+ -- |Monomorphism from @α@ to @γ@.
unify ∷ α → Unified α
-- |FIXME: doc
fromStatusCode ∷ sc → SomeStatusCode
fromStatusCode = SomeStatusCode
--- |Equivalence of 'StatusCode's. Two 'StatusCode's @a@ and @b@ are
--- said to be equivalent iff @'numericCode' a '==' 'numericCode' b@.
+-- |Equivalence of 'StatusCode's. Two 'StatusCode's @α@ and
+-- @β@ are said to be equivalent iff @'numericCode' α '=='
+-- 'numericCode' β@.
instance StatusCode sc ⇒ Eq' sc where
type Unified sc = Int
{-# INLINE CONLIKE unify #-}