@@ -27,6 +27,9 @@ import Data.Maybe (isJust, isNothing)
2727import Data.Monoid (Monoid (.. ))
2828import Data.Semigroup (Semigroup (.. ))
2929import Data.Type.Equality ((:~:) (.. ))
30+ #if MIN_VERSION_base(4,6,0)
31+ import GHC.Generics ((:+:) (.. ), (:*:) (.. ))
32+ #endif
3033
3134#if __GLASGOW_HASKELL__ >=708
3235import Data.Typeable (Typeable )
@@ -86,6 +89,24 @@ instance (GShow a, GShow b) => GShow (Product a b) where
8689 . showChar ' '
8790 . gshowsPrec 11 y
8891
92+ #if MIN_VERSION_base(4,6,0)
93+ --
94+ -- | >>> gshow (L1 Refl :: ((:~:) Int :+: (:~:) Bool) Int)
95+ -- "L1 Refl"
96+ instance (GShow a , GShow b ) => GShow (a :+: b ) where
97+ gshowsPrec d = \ s -> case s of
98+ L1 x -> showParen (d > 10 ) (showString " L1 " . gshowsPrec 11 x)
99+ R1 x -> showParen (d > 10 ) (showString " R1 " . gshowsPrec 11 x)
100+
101+ -- | >>> gshow (Pair Refl Refl :: Product ((:~:) Int) ((:~:) Int) Int)
102+ -- "Refl :*: Refl"
103+ instance (GShow a , GShow b ) => GShow (a :*: b ) where
104+ gshowsPrec d (x :*: y) = showParen (d > 6 )
105+ $ gshowsPrec 6 x
106+ . showString " :*: "
107+ . gshowsPrec 6 y
108+ #endif
109+
89110-- | @GReadS t@ is equivalent to @ReadS (forall b. (forall a. t a -> b) -> b)@, which is
90111-- in turn equivalent to @ReadS (Exists t)@ (with @data Exists t where Exists :: t a -> Exists t@)
91112#if __GLASGOW_HASKELL__ >= 810
@@ -121,6 +142,11 @@ gread s g = withSome (hd [f | (f, "") <- greads s]) g where
121142-- >>> greadMaybe "InL Refl" mkSome :: Maybe (Some (Sum ((:~:) Int) ((:~:) Bool)))
122143-- Just (mkSome (InL Refl))
123144--
145+ #if MIN_VERSION_base(4,6,0)
146+ -- >>> greadMaybe "L1 Refl" mkSome :: Maybe (Some ((:~:) Int :+: (:~:) Bool))
147+ -- Just (mkSome (L1 Refl))
148+ --
149+ #endif
124150-- >>> greadMaybe "garbage" mkSome :: Maybe (Some ((:~:) Int))
125151-- Nothing
126152--
@@ -147,6 +173,20 @@ instance (GRead a, GRead b) => GRead (Sum a b) where
147173 | (" InR" , s2) <- lex s1
148174 , (r, t) <- greadsPrec 11 s2 ]) s
149175
176+ #if MIN_VERSION_base(4,6,0)
177+ instance (GRead a , GRead b ) => GRead (a :+: b ) where
178+ greadsPrec d s =
179+ readParen (d > 10 )
180+ (\ s1 -> [ (S $ \ k -> withSome r (k . L1 ), t)
181+ | (" L1" , s2) <- lex s1
182+ , (r, t) <- greadsPrec 11 s2 ]) s
183+ ++
184+ readParen (d > 10 )
185+ (\ s1 -> [ (S $ \ k -> withSome r (k . R1 ), t)
186+ | (" R1" , s2) <- lex s1
187+ , (r, t) <- greadsPrec 11 s2 ]) s
188+ #endif
189+
150190-------------------------------------------------------------------------------
151191-- GEq
152192-------------------------------------------------------------------------------
@@ -199,6 +239,19 @@ instance (GEq a, GEq b) => GEq (Product a b) where
199239 Refl <- geq y y'
200240 return Refl
201241
242+ #if MIN_VERSION_base(4,6,0)
243+ instance (GEq f , GEq g ) => GEq (f :+: g ) where
244+ geq (L1 x) (L1 y) = geq x y
245+ geq (R1 x) (R1 y) = geq x y
246+ geq _ _ = Nothing
247+
248+ instance (GEq a , GEq b ) => GEq (a :*: b ) where
249+ geq (x :*: y) (x' :*: y') = do
250+ Refl <- geq x x'
251+ Refl <- geq y y'
252+ return Refl
253+ #endif
254+
202255#if MIN_VERSION_base(4,10,0)
203256instance GEq TR. TypeRep where
204257 geq = testEquality
@@ -321,6 +374,23 @@ instance (GCompare a, GCompare b) => GCompare (Product a b) where
321374 GEQ -> GEQ
322375 GGT -> GGT
323376
377+ #if MIN_VERSION_base(4,6,0)
378+ instance (GCompare f , GCompare g ) => GCompare (f :+: g ) where
379+ gcompare (L1 x) (L1 y) = gcompare x y
380+ gcompare (L1 _) (R1 _) = GLT
381+ gcompare (R1 _) (L1 _) = GGT
382+ gcompare (R1 x) (R1 y) = gcompare x y
383+
384+ instance (GCompare a , GCompare b ) => GCompare (a :*: b ) where
385+ gcompare (x :*: y) (x' :*: y') = case gcompare x x' of
386+ GLT -> GLT
387+ GGT -> GGT
388+ GEQ -> case gcompare y y' of
389+ GLT -> GLT
390+ GEQ -> GEQ
391+ GGT -> GGT
392+ #endif
393+
324394-------------------------------------------------------------------------------
325395-- Some
326396-------------------------------------------------------------------------------
0 commit comments