{-# LANGUAGE GADTs, TypeOperators, RankNTypes, TypeFamilies, FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-deprecated-flags #-}
module Data.GADT.Compare
( module Data.GADT.Compare
, (:~:)(Refl)
) where
import Data.Maybe
import Data.GADT.Show
import Data.Type.Equality ((:~:) (..))
import Data.Typeable
import Data.Functor.Sum (Sum (..))
import Data.Functor.Product (Product (..))
#if MIN_VERSION_base(4,10,0)
import qualified Type.Reflection as TR
import Data.Type.Equality (testEquality)
#endif
{-# DEPRECATED (:=) "use '(:~:)' from 'Data.Type,Equality'." #-}
type (:=) = (:~:)
class GEq f where
geq :: f a -> f b -> Maybe (a :~: b)
defaultEq :: GEq f => f a -> f b -> Bool
defaultEq x y = isJust (geq x y)
defaultNeq :: GEq f => f a -> f b -> Bool
defaultNeq x y = isNothing (geq x y)
instance GEq ((:~:) a) where
geq (Refl :: a :~: b) (Refl :: a :~: c) = Just (Refl :: b :~: c)
instance (GEq a, GEq b) => GEq (Sum a b) where
geq (InL x) (InL y) = geq x y
geq (InR x) (InR y) = geq x y
geq _ _ = Nothing
instance (GEq a, GEq b) => GEq (Product a b) where
geq (Pair x y) (Pair x' y') = do
Refl <- geq x x'
Refl <- geq y y'
return Refl
#if MIN_VERSION_base(4,10,0)
instance GEq TR.TypeRep where
geq = testEquality
#endif
data GOrdering a b where
GLT :: GOrdering a b
GEQ :: GOrdering t t
GGT :: GOrdering a b
deriving Typeable
weakenOrdering :: GOrdering a b -> Ordering
weakenOrdering GLT = LT
weakenOrdering GEQ = EQ
weakenOrdering GGT = GT
instance Eq (GOrdering a b) where
x == y =
weakenOrdering x == weakenOrdering y
instance Ord (GOrdering a b) where
compare x y = compare (weakenOrdering x) (weakenOrdering y)
instance Show (GOrdering a b) where
showsPrec _ GGT = showString "GGT"
showsPrec _ GEQ = showString "GEQ"
showsPrec _ GLT = showString "GLT"
instance GShow (GOrdering a) where
gshowsPrec = showsPrec
instance GRead (GOrdering a) where
greadsPrec _ s = case con of
"GGT" -> [(GReadResult (\x -> x GGT), rest)]
"GEQ" -> [(GReadResult (\x -> x GEQ), rest)]
"GLT" -> [(GReadResult (\x -> x GLT), rest)]
_ -> []
where (con, rest) = splitAt 3 s
class GEq f => GCompare f where
gcompare :: f a -> f b -> GOrdering a b
instance GCompare ((:~:) a) where
gcompare Refl Refl = GEQ
#if MIN_VERSION_base(4,10,0)
instance GCompare TR.TypeRep where
gcompare t1 t2 =
case testEquality t1 t2 of
Just Refl -> GEQ
Nothing ->
case compare (TR.SomeTypeRep t1) (TR.SomeTypeRep t2) of
LT -> GLT
GT -> GGT
EQ -> error "impossible: 'testEquality' and 'compare' \
\are inconsistent for TypeRep; report this \
\as a GHC bug"
#endif
defaultCompare :: GCompare f => f a -> f b -> Ordering
defaultCompare x y = weakenOrdering (gcompare x y)
instance (GCompare a, GCompare b) => GCompare (Sum a b) where
gcompare (InL x) (InL y) = gcompare x y
gcompare (InL _) (InR _) = GLT
gcompare (InR _) (InL _) = GGT
gcompare (InR x) (InR y) = gcompare x y
instance (GCompare a, GCompare b) => GCompare (Product a b) where
gcompare (Pair x y) (Pair x' y') = case gcompare x x' of
GLT -> GLT
GGT -> GGT
GEQ -> case gcompare y y' of
GLT -> GLT
GEQ -> GEQ
GGT -> GGT