Skip to content

Commit a4b8a28

Browse files
committed
WIP: Add forall a. Show (t a) superclass to GShow
As `GShow` is isomorphic to this constraint, it's nice to add this super class. This reminds people that if they implement `GShow` they should also implement `forall a. Show (t a)`, as its both incredibly easy to do so and never (in practice) an additional dependency. Unforunately, this change doesn't yet type-check because the instances in base for `Sum` and `Product` are overly consersative: they assume there is a field with a type related to the GADT index. That should be fixed, and this PR can be pointed to as an example of why the problem isn't just theoretical.
1 parent 6784109 commit a4b8a28

File tree

1 file changed

+22
-3
lines changed

1 file changed

+22
-3
lines changed

src/Data/GADT/Internal.hs

Lines changed: 22 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,9 @@
44
#endif
55
{-# LANGUAGE DeriveDataTypeable #-}
66
{-# LANGUAGE GADTs #-}
7+
#if __GLASGOW_HASKELL__ >= 806
8+
{-# LANGUAGE QuantifiedConstraints #-}
9+
#endif
710
{-# LANGUAGE RankNTypes #-}
811
{-# LANGUAGE ScopedTypeVariables #-}
912
{-# LANGUAGE TypeOperators #-}
@@ -46,10 +49,16 @@ import qualified Type.Reflection as TR
4649
-- to write (or derive) an @instance Show (T a)@, and then simply say:
4750
--
4851
-- > instance GShow t where gshowsPrec = showsPrec
49-
class GShow t where
52+
class
53+
#if __GLASGOW_HASKELL__ >= 806
54+
(forall a. Show (t a)) =>
55+
#endif
56+
GShow t where
5057
gshowsPrec :: Int -> t a -> ShowS
5158
#if __GLASGOW_HASKELL__ >= 702
59+
# if __GLASGOW_HASKELL__ < 806
5260
default gshowsPrec :: Show (t a) => Int -> t a -> ShowS
61+
# endif
5362
gshowsPrec = showsPrec
5463
#endif
5564

@@ -70,14 +79,24 @@ instance GShow TR.TypeRep where
7079
--
7180
-- | >>> gshow (InL Refl :: Sum ((:~:) Int) ((:~:) Bool) Int)
7281
-- "InL Refl"
73-
instance (GShow a, GShow b) => GShow (Sum a b) where
82+
instance ( GShow a, GShow b
83+
#if __GLASGOW_HASKELL__ >= 806
84+
, forall x. Show (a x)
85+
, forall x. Show (b x)
86+
#endif
87+
) => GShow (Sum a b) where
7488
gshowsPrec d = \s -> case s of
7589
InL x -> showParen (d > 10) (showString "InL " . gshowsPrec 11 x)
7690
InR x -> showParen (d > 10) (showString "InR " . gshowsPrec 11 x)
7791

7892
-- | >>> gshow (Pair Refl Refl :: Product ((:~:) Int) ((:~:) Int) Int)
7993
-- "Pair Refl Refl"
80-
instance (GShow a, GShow b) => GShow (Product a b) where
94+
instance ( GShow a, GShow b
95+
#if __GLASGOW_HASKELL__ >= 806
96+
, forall x. Show (a x)
97+
, forall x. Show (b x)
98+
#endif
99+
) => GShow (Product a b) where
81100
gshowsPrec d (Pair x y) = showParen (d > 10)
82101
$ showString "Pair "
83102
. gshowsPrec 11 x

0 commit comments

Comments
 (0)