[commit: ghc] wip/ttypeable: Various fixes (2f2e044)
git at git.haskell.org
git at git.haskell.org
Sat Oct 1 21:33:39 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/ttypeable
Link : http://ghc.haskell.org/trac/ghc/changeset/2f2e044b3d3e06fb0527292302b8079a0468e88e/ghc
>---------------------------------------------------------------
commit 2f2e044b3d3e06fb0527292302b8079a0468e88e
Author: Ben Gamari <ben at smart-cactus.org>
Date: Fri Mar 11 19:16:55 2016 +0100
Various fixes
>---------------------------------------------------------------
2f2e044b3d3e06fb0527292302b8079a0468e88e
compiler/utils/Binary.hs | 6 +++---
libraries/ghci/GHCi/TH/Binary.hs | 14 +++++++-------
2 files changed, 10 insertions(+), 10 deletions(-)
diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs
index db70b04..92997b9 100644
--- a/compiler/utils/Binary.hs
+++ b/compiler/utils/Binary.hs
@@ -81,7 +81,7 @@ import Data.Time
#if MIN_VERSION_base(4,9,0)
import Type.Reflection
import Type.Reflection.Unsafe
-import GHC.Exts ( TYPE, Levity(..) )
+import Data.Kind (Type)
#else
import Data.Typeable
#endif
@@ -605,7 +605,7 @@ getTypeRepX bh = do
case tag of
0 -> do con <- get bh
TypeRepX rep_k <- getTypeRepX bh
- Just HRefl <- pure $ eqTypeRep rep_k (typeRep :: TypeRep (TYPE 'Lifted))
+ Just HRefl <- pure $ eqTypeRep rep_k (typeRep :: TypeRep Type)
pure $ TypeRepX $ mkTrCon con rep_k
1 -> do TypeRepX f <- getTypeRepX bh
TypeRepX x <- getTypeRepX bh
@@ -619,7 +619,7 @@ instance Typeable a => Binary (TypeRep (a :: k)) where
put_ = putTypeRep
get bh = do
TypeRepX rep <- getTypeRepX bh
- case rep `eqTypeRep` typeRep of
+ case rep `eqTypeRep` (typeRep :: TypeRep a) of
Just HRefl -> pure rep
Nothing -> fail "Binary: Type mismatch"
diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs
index 7851e33..2a8432b 100644
--- a/libraries/ghci/GHCi/TH/Binary.hs
+++ b/libraries/ghci/GHCi/TH/Binary.hs
@@ -14,10 +14,10 @@ import qualified Data.ByteString as B
import Control.Monad (when)
import Type.Reflection
import Type.Reflection.Unsafe
+import Data.Kind (Type)
#else
import Data.Typeable
#endif
-import GHC.Exts (TYPE, Levity(..))
import GHC.Serialized
import qualified Language.Haskell.TH as TH
import qualified Language.Haskell.TH.Syntax as TH
@@ -97,11 +97,11 @@ getTypeRepX = do
tag <- get :: Get Word8
case tag of
0 -> do con <- get :: Get TyCon
- TypeRep rep_k <- getTypeRepX
- Just HRefl <- pure $ eqTypeRep rep_k (typeRep :: TypeRep (TYPE 'Lifted))
+ TypeRepX rep_k <- getTypeRepX
+ Just HRefl <- pure $ eqTypeRep rep_k (typeRep :: TypeRep Type)
pure $ TypeRepX $ mkTrCon con rep_k
- 1 -> do TypeRep f <- getTypeRepX
- TypeRep x <- getTypeRepX
+ 1 -> do TypeRepX f <- getTypeRepX
+ TypeRepX x <- getTypeRepX
case typeRepKind f of
TRFun arg _ -> do
Just HRefl <- pure $ eqTypeRep arg x
@@ -112,13 +112,13 @@ instance Typeable a => Binary (TypeRep (a :: k)) where
put = putTypeRep
get = do
TypeRepX rep <- getTypeRepX
- case rep `eqTypeRep` typeRef of
+ case rep `eqTypeRep` (typeRep :: TypeRep a) of
Just HRefl -> pure rep
Nothing -> fail "Binary: Type mismatch"
instance Binary TypeRepX where
put (TypeRepX rep) = putTypeRep rep
- get = getTypeRep
+ get = getTypeRepX
#else
instance Binary TyCon where
put tc = put (tyConPackage tc) >> put (tyConModule tc) >> put (tyConName tc)
More information about the ghc-commits
mailing list