Skip to content

Commit f172622

Browse files
committed
Add instances for (:~~:)
1 parent 6efbd3b commit f172622

File tree

2 files changed

+40
-2
lines changed

2 files changed

+40
-2
lines changed

src/Data/GADT/DeepSeq.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,8 @@ import Data.Functor.Sum (Sum (..))
2020
import Data.Type.Equality ((:~:) (..))
2121

2222
#if MIN_VERSION_base(4,10,0)
23+
import Data.Type.Equality ((:~~:) (..))
24+
2325
import qualified Type.Reflection as TR
2426
#endif
2527

@@ -46,6 +48,10 @@ instance GNFData ((:~:) a) where
4648
grnf Refl = ()
4749

4850
#if MIN_VERSION_base(4,10,0)
51+
-- | @since 1.0.4
52+
instance GNFData ((:~~:) a) where
53+
grnf HRefl = ()
54+
4955
-- | @since 1.0.3
5056
instance GNFData TR.TypeRep where
5157
grnf = TR.rnfTypeRep

src/Data/GADT/Internal.hs

Lines changed: 34 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,9 @@
1313
#if __GLASGOW_HASKELL__ >= 810
1414
{-# LANGUAGE StandaloneKindSignatures #-}
1515
#endif
16+
#if __GLASGOW_HASKELL__ >= 802 && __GLASGOW_HASKELL__ < 805
17+
{-# LANGUAGE TypeInType #-}
18+
#endif
1619
#if (__GLASGOW_HASKELL__ >= 704 && __GLASGOW_HASKELL__ < 707) || __GLASGOW_HASKELL__ >= 801
1720
{-# LANGUAGE Safe #-}
1821
#elif __GLASGOW_HASKELL__ >= 702
@@ -33,12 +36,16 @@ import Data.Typeable (Typeable)
3336
#endif
3437

3538
#if MIN_VERSION_base(4,10,0)
36-
import Data.Type.Equality (testEquality)
39+
import Data.Type.Equality ((:~~:) (..), testEquality)
3740
import qualified Type.Reflection as TR
3841
#endif
3942

43+
#if __GLASGOW_HASKELL__ >= 800
44+
import Data.Kind (Type)
45+
#endif
46+
4047
#if __GLASGOW_HASKELL__ >= 810
41-
import Data.Kind (Type, Constraint)
48+
import Data.Kind (Constraint)
4249
#endif
4350

4451
-- $setup
@@ -65,6 +72,10 @@ instance GShow ((:~:) a) where
6572
gshowsPrec _ Refl = showString "Refl"
6673

6774
#if MIN_VERSION_base(4,10,0)
75+
-- | @since 1.0.4
76+
instance GShow ((:~~:) a) where
77+
gshowsPrec _ HRefl = showString "HRefl"
78+
6879
instance GShow TR.TypeRep where
6980
gshowsPrec = showsPrec
7081
#endif
@@ -135,6 +146,17 @@ instance GRead ((:~:) a) where
135146
f :: forall x. (x :~: x, String) -> [(Some ((:~:) x), String)]
136147
f (Refl, rest) = return (mkSome Refl, rest)
137148

149+
#if MIN_VERSION_base(4,10,0)
150+
-- | @since 1.0.4
151+
instance forall k1 k2 (a :: k1). k1 ~ k2 => GRead ((:~~:) a :: k2 -> Type) where
152+
greadsPrec p s = readsPrec p s >>= f
153+
where
154+
f :: forall k (x :: k)
155+
. (x :~~: x, String)
156+
-> [(Some ((:~~:) x :: k -> Type), String)]
157+
f (HRefl, rest) = return (mkSome (HRefl :: x :~~: x), rest)
158+
#endif
159+
138160
instance (GRead a, GRead b) => GRead (Sum a b) where
139161
greadsPrec d s =
140162
readParen (d > 10)
@@ -188,6 +210,12 @@ defaultNeq x y = isNothing (geq x y)
188210
instance GEq ((:~:) a) where
189211
geq (Refl :: a :~: b) (Refl :: a :~: c) = Just (Refl :: b :~: c)
190212

213+
#if MIN_VERSION_base(4,10,0)
214+
-- | @since 1.0.4
215+
instance GEq ((:~~:) a) where
216+
geq (HRefl :: a :~~: b) (HRefl :: a :~~: c) = Just (Refl :: b :~: c)
217+
#endif
218+
191219
instance (GEq a, GEq b) => GEq (Sum a b) where
192220
geq (InL x) (InL y) = geq x y
193221
geq (InR x) (InR y) = geq x y
@@ -290,6 +318,10 @@ instance GCompare ((:~:) a) where
290318
gcompare Refl Refl = GEQ
291319

292320
#if MIN_VERSION_base(4,10,0)
321+
-- | @since 1.0.4
322+
instance GCompare ((:~~:) a) where
323+
gcompare HRefl HRefl = GEQ
324+
293325
instance GCompare TR.TypeRep where
294326
gcompare t1 t2 =
295327
case testEquality t1 t2 of

0 commit comments

Comments
 (0)