Skip to content

Commit 6570a3a

Browse files
committed
Create GCoercible class, analogous to GEq
It could be a superclass of `GEq`, but this would be a breaking change and interferes with Safe Haskell, so we refrained from making it one.
1 parent f172622 commit 6570a3a

File tree

3 files changed

+112
-26
lines changed

3 files changed

+112
-26
lines changed

some.cabal

+5
Original file line numberDiff line numberDiff line change
@@ -72,6 +72,11 @@ library
7272
Data.Some.GADT
7373
Data.Some.Newtype
7474

75+
-- Proxy for base >= 4.7.0
76+
if impl(ghc >= 7.8.2)
77+
exposed-modules:
78+
Data.GADT.Coerce
79+
7580
other-modules: Data.GADT.Internal
7681
build-depends:
7782
base >=4.3 && <4.17

src/Data/GADT/Coerce.hs

+107
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,107 @@
1+
{-# LANGUAGE CPP #-}
2+
{-# LANGUAGE GADTs #-}
3+
{-# LANGUAGE PolyKinds #-}
4+
#if __GLASGOW_HASKELL__ >= 810
5+
{-# LANGUAGE StandaloneKindSignatures #-}
6+
#endif
7+
module Data.GADT.Coerce (
8+
GCoercible (..),
9+
defaultGcoercible,
10+
) where
11+
12+
import Data.Functor.Product (Product (..))
13+
import Data.Functor.Sum (Sum (..))
14+
import Data.IORef (IORef)
15+
import Data.STRef (STRef)
16+
import Data.Type.Equality ((:~:) (..))
17+
import Data.Type.Coercion
18+
19+
import Unsafe.Coerce (unsafeCoerce)
20+
21+
import Data.GADT.Compare (GEq, geq)
22+
23+
#if MIN_VERSION_base(4,10,0)
24+
import Data.Type.Equality ((:~~:) (..))
25+
import qualified Type.Reflection as TR
26+
#endif
27+
28+
#if __GLASGOW_HASKELL__ >= 810
29+
import Data.Kind (Type, Constraint)
30+
#endif
31+
32+
-- |A class for type-contexts which contain enough information
33+
-- to (at least in some cases) decide the coercibility of types
34+
-- occurring within them.
35+
#if __GLASGOW_HASKELL__ >= 810
36+
type GCoercible :: (k -> Type) -> Constraint
37+
#endif
38+
class GCoercible f where
39+
gcoercible :: f a -> f b -> Maybe (Coercion a b)
40+
41+
-- |If 'f' has a 'GEq' instance, this function makes a suitable default
42+
-- implementation of 'gcoercible'.
43+
defaultGcoercible :: GEq f => f a -> f b -> Maybe (Coercion a b)
44+
defaultGcoercible x y = fmap repr $ geq x y
45+
46+
instance GCoercible ((:~:) a) where
47+
gcoercible = defaultGcoercible
48+
49+
#if MIN_VERSION_base(4,10,0)
50+
instance GCoercible ((:~~:) a) where
51+
gcoercible = defaultGcoercible
52+
53+
instance GCoercible TR.TypeRep where
54+
gcoercible = defaultGcoercible
55+
#endif
56+
57+
instance (GCoercible a, GCoercible b) => GCoercible (Sum a b) where
58+
gcoercible (InL x) (InL y) = gcoercible x y
59+
gcoercible (InR x) (InR y) = gcoercible x y
60+
gcoercible _ _ = Nothing
61+
62+
instance (GCoercible a, GCoercible b) => GCoercible (Product a b) where
63+
gcoercible (Pair x y) (Pair x' y') = do
64+
Coercion <- gcoercible x x'
65+
Coercion <- gcoercible y y'
66+
return Coercion
67+
68+
instance GCoercible IORef where
69+
gcoercible x y =
70+
if x == unsafeCoerce y
71+
then Just $ unsafeCoerce $ repr Refl
72+
else Nothing
73+
74+
instance GCoercible (STRef s) where
75+
gcoercible x y =
76+
if x == unsafeCoerce y
77+
then Just $ unsafeCoerce $ repr Refl
78+
else Nothing
79+
80+
-- This instance seems nice, but it's simply not right:
81+
--
82+
-- > instance GCoercible StableName where
83+
-- > gcoercible sn1 sn2
84+
-- > | sn1 == unsafeCoerce sn2
85+
-- > = Just (unsafeCoerce Refl)
86+
-- > | otherwise = Nothing
87+
--
88+
-- Proof:
89+
--
90+
-- > x <- makeStableName id :: IO (StableName (Int -> Int))
91+
-- > y <- makeStableName id :: IO (StableName ((Int -> Int) -> Int -> Int))
92+
-- >
93+
-- > let Just boom = gcoercible x y
94+
-- >
95+
-- > Data.Type.Coercion.coerceWith boom (const 0) id 0
96+
-- > let "Illegal Instruction" = "QED."
97+
--
98+
-- The core of the problem is that 'makeStableName' only knows the closure it is
99+
-- passed to, not any type information. Together with the fact that the same
100+
-- closure has the same 'StableName' each time 'makeStableName' is called on it,
101+
-- there is potential for abuse when a closure can be given many incompatible
102+
-- types.
103+
--
104+
-- 'GCoericble' gets us closer than GEq, but the problem is Coercions state that
105+
-- *all* values can be coerced, but due to polymophism it is quite easy to find
106+
-- situations where some values of a type are safe to coerce and others are not.
107+
-- We just need one such value to abuse 'GCoercible StableName'.

src/Data/GADT/Internal.hs

-26
Original file line numberDiff line numberDiff line change
@@ -236,32 +236,6 @@ instance GEq TR.TypeRep where
236236
-- GCompare
237237
-------------------------------------------------------------------------------
238238

239-
-- This instance seems nice, but it's simply not right:
240-
--
241-
-- > instance GEq StableName where
242-
-- > geq sn1 sn2
243-
-- > | sn1 == unsafeCoerce sn2
244-
-- > = Just (unsafeCoerce Refl)
245-
-- > | otherwise = Nothing
246-
--
247-
-- Proof:
248-
--
249-
-- > x <- makeStableName id :: IO (StableName (Int -> Int))
250-
-- > y <- makeStableName id :: IO (StableName ((Int -> Int) -> Int -> Int))
251-
-- >
252-
-- > let Just boom = geq x y
253-
-- > let coerce :: (a :~: b) -> a -> b; coerce Refl = id
254-
-- >
255-
-- > coerce boom (const 0) id 0
256-
-- > let "Illegal Instruction" = "QED."
257-
--
258-
-- The core of the problem is that 'makeStableName' only knows the closure
259-
-- it is passed to, not any type information. Together with the fact that
260-
-- the same closure has the same StableName each time 'makeStableName' is
261-
-- called on it, there is serious potential for abuse when a closure can
262-
-- be given many incompatible types.
263-
264-
265239
-- |A type for the result of comparing GADT constructors; the type parameters
266240
-- of the GADT values being compared are included so that in the case where
267241
-- they are equal their parameter types can be unified.

0 commit comments

Comments
 (0)