{-# LANGUAGE GADTs, TypeOperators, RankNTypes, TypeFamilies, FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# OPTIONS_GHC -fno-warn-deprecated-flags #-}
{-# LANGUAGE CPP #-}
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE PolyKinds #-}
#endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Safe #-}
#endif
{-# LANGUAGE ScopedTypeVariables #-}
module Data.GADT.Compare
( module Data.GADT.Compare
#if MIN_VERSION_base(4,7,0)
, (:~:)(Refl)
#endif
) where
import Data.Maybe
import Data.GADT.Show
import Data.Typeable
#if MIN_VERSION_base(4,10,0)
import qualified Type.Reflection as TR
import Data.Type.Equality (testEquality)
#endif
#if MIN_VERSION_base(4,7,0)
type (:=) = (:~:)
#else
data a := b where
Refl :: a := a
deriving Typeable
instance Eq (a := b) where
Refl == Refl = True
instance Ord (a := b) where
compare Refl Refl = EQ
instance Show (a := b) where
showsPrec _ Refl = showString "Refl"
instance Read (a := a) where
readsPrec _ s = case con of
"Refl" -> [(Refl, rest)]
_ -> []
where (con,rest) = splitAt 4 s
#endif
instance GShow ((:=) a) where
gshowsPrec _ Refl = showString "Refl"
instance GRead ((:=) a) where
greadsPrec p s = readsPrec p s >>= f
where
f :: forall x. (x := x, String) -> [(GReadResult ((:=) x), String)]
f (Refl, rest) = return (GReadResult (\x -> x Refl) , rest)
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)
#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)