[commit: ghc] wip/ttypeable: Break recursive loop in serialization (2671802)
git at git.haskell.org
git at git.haskell.org
Sun Jan 29 20:18:25 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/ttypeable
Link : http://ghc.haskell.org/trac/ghc/changeset/267180280d98b8a5188c6d4b05a6597b242ca503/ghc
>---------------------------------------------------------------
commit 267180280d98b8a5188c6d4b05a6597b242ca503
Author: Ben Gamari <ben at smart-cactus.org>
Date: Wed Mar 16 13:01:45 2016 +0100
Break recursive loop in serialization
>---------------------------------------------------------------
267180280d98b8a5188c6d4b05a6597b242ca503
compiler/utils/Binary.hs | 18 ++++++++++++++----
libraries/ghci/GHCi/TH/Binary.hs | 18 ++++++++++++++----
2 files changed, 28 insertions(+), 8 deletions(-)
diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs
index 88ea8cd..9f3fb8d 100644
--- a/compiler/utils/Binary.hs
+++ b/compiler/utils/Binary.hs
@@ -80,6 +80,7 @@ import Data.Time
import Type.Reflection
import Type.Reflection.Unsafe
import Data.Kind (Type)
+import GHC.Exts (RuntimeRep)
#else
import Data.Typeable
#endif
@@ -582,12 +583,19 @@ instance Binary TyCon where
#if MIN_VERSION_base(4,9,0)
putTypeRep :: BinHandle -> TypeRep a -> IO ()
+-- Special handling for Type and RuntimeRep due to recursive kind relations.
+-- See Note [Mutually recursive representations of primitive types]
+putTypeRep bh rep
+ | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type)
+ = put_ bh (0 :: Word8)
+ | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep)
+ = put_ bh (1 :: Word8)
putTypeRep bh rep@(TRCon con) = do
- put_ bh (0 :: Word8)
+ put_ bh (2 :: Word8)
put_ bh con
putTypeRep bh (typeRepKind rep)
putTypeRep bh (TRApp f x) = do
- put_ bh (1 :: Word8)
+ put_ bh (3 :: Word8)
putTypeRep bh f
putTypeRep bh x
putTypeRep _ _ = fail "putTypeRep: Impossible"
@@ -596,13 +604,15 @@ getTypeRepX :: BinHandle -> IO TypeRepX
getTypeRepX bh = do
tag <- get bh :: IO Word8
case tag of
- 0 -> do con <- get bh :: IO TyCon
+ 0 -> return $ TypeRepX (typeRep :: TypeRep Type)
+ 1 -> return $ TypeRepX (typeRep :: TypeRep RuntimeRep)
+ 2 -> do con <- get bh :: IO TyCon
TypeRepX rep_k <- getTypeRepX bh
case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of
Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k
Nothing -> fail "getTypeRepX: Kind mismatch"
- 1 -> do TypeRepX f <- getTypeRepX bh
+ 3 -> do TypeRepX f <- getTypeRepX bh
TypeRepX x <- getTypeRepX bh
case typeRepKind f of
TRFun arg _ ->
diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs
index 5dd6fa8..ea0809f 100644
--- a/libraries/ghci/GHCi/TH/Binary.hs
+++ b/libraries/ghci/GHCi/TH/Binary.hs
@@ -14,6 +14,7 @@ import qualified Data.ByteString as B
import Type.Reflection
import Type.Reflection.Unsafe
import Data.Kind (Type)
+import GHC.Exts (RuntimeRep)
#else
import Data.Typeable
#endif
@@ -84,12 +85,19 @@ instance Binary TyCon where
get = mkTyCon <$> get <*> get <*> get
putTypeRep :: TypeRep a -> Put
+-- Special handling for Type and RuntimeRep due to recursive kind relations.
+-- See Note [Mutually recursive representations of primitive types]
+putTypeRep rep
+ | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type)
+ = put (0 :: Word8)
+ | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep)
+ = put (1 :: Word8)
putTypeRep rep@(TRCon con) = do
- put (0 :: Word8)
+ put (2 :: Word8)
put con
putTypeRep (typeRepKind rep)
putTypeRep (TRApp f x) = do
- put (1 :: Word8)
+ put (3 :: Word8)
putTypeRep f
putTypeRep x
putTypeRep _ = fail "putTypeRep: Impossible"
@@ -98,13 +106,15 @@ getTypeRepX :: Get TypeRepX
getTypeRepX = do
tag <- get :: Get Word8
case tag of
- 0 -> do con <- get :: Get TyCon
+ 0 -> return $ TypeRepX (typeRep :: TypeRep Type)
+ 1 -> return $ TypeRepX (typeRep :: TypeRep RuntimeRep)
+ 2 -> do con <- get :: Get TyCon
TypeRepX rep_k <- getTypeRepX
case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of
Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k
Nothing -> fail "getTypeRepX: Kind mismatch"
- 1 -> do TypeRepX f <- getTypeRepX
+ 3 -> do TypeRepX f <- getTypeRepX
TypeRepX x <- getTypeRepX
case typeRepKind f of
TRFun arg _ ->
More information about the ghc-commits
mailing list