13
13
#if __GLASGOW_HASKELL__ >= 810
14
14
{-# LANGUAGE StandaloneKindSignatures #-}
15
15
#endif
16
+ #if __GLASGOW_HASKELL__ >= 802 && __GLASGOW_HASKELL__ < 805
17
+ {-# LANGUAGE TypeInType #-}
18
+ #endif
16
19
#if (__GLASGOW_HASKELL__ >= 704 && __GLASGOW_HASKELL__ < 707) || __GLASGOW_HASKELL__ >= 801
17
20
{-# LANGUAGE Safe #-}
18
21
#elif __GLASGOW_HASKELL__ >= 702
@@ -33,12 +36,16 @@ import Data.Typeable (Typeable)
33
36
#endif
34
37
35
38
#if MIN_VERSION_base(4,10,0)
36
- import Data.Type.Equality (testEquality )
39
+ import Data.Type.Equality ((:~~:) ( .. ), testEquality )
37
40
import qualified Type.Reflection as TR
38
41
#endif
39
42
43
+ #if __GLASGOW_HASKELL__ >= 800
44
+ import Data.Kind (Type )
45
+ #endif
46
+
40
47
#if __GLASGOW_HASKELL__ >= 810
41
- import Data.Kind (Type , Constraint )
48
+ import Data.Kind (Constraint )
42
49
#endif
43
50
44
51
-- $setup
@@ -65,6 +72,10 @@ instance GShow ((:~:) a) where
65
72
gshowsPrec _ Refl = showString " Refl"
66
73
67
74
#if MIN_VERSION_base(4,10,0)
75
+ -- | @since 1.0.4
76
+ instance GShow ((:~~: ) a ) where
77
+ gshowsPrec _ HRefl = showString " HRefl"
78
+
68
79
instance GShow TR. TypeRep where
69
80
gshowsPrec = showsPrec
70
81
#endif
@@ -135,6 +146,17 @@ instance GRead ((:~:) a) where
135
146
f :: forall x . (x :~: x , String ) -> [(Some ((:~: ) x ), String )]
136
147
f (Refl , rest) = return (mkSome Refl , rest)
137
148
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
+
138
160
instance (GRead a , GRead b ) => GRead (Sum a b ) where
139
161
greadsPrec d s =
140
162
readParen (d > 10 )
@@ -188,6 +210,12 @@ defaultNeq x y = isNothing (geq x y)
188
210
instance GEq ((:~: ) a ) where
189
211
geq (Refl :: a :~: b ) (Refl :: a :~: c ) = Just (Refl :: b :~: c )
190
212
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
+
191
219
instance (GEq a , GEq b ) => GEq (Sum a b ) where
192
220
geq (InL x) (InL y) = geq x y
193
221
geq (InR x) (InR y) = geq x y
@@ -290,6 +318,10 @@ instance GCompare ((:~:) a) where
290
318
gcompare Refl Refl = GEQ
291
319
292
320
#if MIN_VERSION_base(4,10,0)
321
+ -- | @since 1.0.4
322
+ instance GCompare ((:~~: ) a ) where
323
+ gcompare HRefl HRefl = GEQ
324
+
293
325
instance GCompare TR. TypeRep where
294
326
gcompare t1 t2 =
295
327
case testEquality t1 t2 of
0 commit comments