]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/StatusCode/Internal.hs
Docs
[Lucu.git] / Network / HTTP / Lucu / StatusCode / Internal.hs
index 38188568de8646037ee84465cce740e2df68b8d3..e8785c3c106a49a5ba124edd188ddae90e8fc5fd 100644 (file)
@@ -4,6 +4,8 @@
   , MultiParamTypeClasses
   , OverlappingInstances
   , TemplateHaskell
+  , TypeFamilies
+  , UndecidableInstances
   , UnicodeSyntax
   , ViewPatterns
   #-}
@@ -11,8 +13,6 @@
 module Network.HTTP.Lucu.StatusCode.Internal
     ( StatusCode(..)
     , SomeStatusCode
-    , (≈)
-    , (≉)
     , statusCodes
     )
     where
@@ -25,6 +25,7 @@ import qualified Data.ByteString.Lazy.Char8 as Lazy
 import Data.Convertible.Base
 import Data.Convertible.Instances.Ascii ()
 import Data.Convertible.Utils
+import Data.Eq.Indirect
 import Data.List
 import Language.Haskell.TH.Lib
 import Language.Haskell.TH.Syntax
@@ -48,32 +49,25 @@ class (Eq sc, Show sc) ⇒ StatusCode sc where
     fromStatusCode ∷ sc → SomeStatusCode
     fromStatusCode = SomeStatusCode
 
+-- |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 #-}
+    unify = numericCode
+
 -- |Container type for the 'StatusCode' type class.
 data SomeStatusCode
     = ∀sc. StatusCode sc ⇒ SomeStatusCode sc
 
 instance Eq SomeStatusCode where
-    (==) = (≈)
+    {-# INLINE CONLIKE (==) #-}
+    (==) = (≡:)
 
 instance Show SomeStatusCode where
     show (SomeStatusCode sc) = show sc
 
-infix 4 ≈, ≉
--- |Equivalence of 'StatusCode's. Two 'StatusCode's @a@ and @b@ are
--- said to be equivalent iff @'numericCode' a '==' 'numericCode' b@.
---
--- U+2248, ALMOST EQUAL TO
-(≈) ∷ (StatusCode α, StatusCode β) ⇒ α → β → Bool
-{-# INLINE (≈) #-}
-α ≈ β = numericCode α ≡ numericCode β
-
--- |@(a ≉ b) '==' 'not' (a ≈ b)@
---
--- U+2249, NOT ALMOST EQUAL TO
-(≉) ∷ (StatusCode α, StatusCode β) ⇒ α → β → Bool
-{-# INLINE (≉) #-}
-(≉) = ((¬) ∘) ∘ (≈)
-
 instance StatusCode SomeStatusCode where
     numericCode   (SomeStatusCode sc) = numericCode   sc
     textualStatus (SomeStatusCode sc) = textualStatus sc