[commit: ghc] master: A number of Typeable wibbles from review (27a2854)
git at git.haskell.org
git at git.haskell.org
Mon Feb 20 18:41:58 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/27a2854124cc1c101570104501beea234a4ee921/ghc
>---------------------------------------------------------------
commit 27a2854124cc1c101570104501beea234a4ee921
Author: Ben Gamari <ben at smart-cactus.org>
Date: Sun Feb 19 10:07:56 2017 -0500
A number of Typeable wibbles from review
I forgot to fold these in to the patch merged earlier.
>---------------------------------------------------------------
27a2854124cc1c101570104501beea234a4ee921
libraries/base/Data/Typeable/Internal.hs | 10 +++++-----
libraries/base/GHC/Show.hs | 2 +-
libraries/base/changelog.md | 8 ++++----
libraries/ghc-boot/GHC/Serialized.hs | 4 +---
4 files changed, 11 insertions(+), 13 deletions(-)
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index 800dc2a..c230d3a 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -77,7 +77,7 @@ import GHC.Base
import qualified GHC.Arr as A
import GHC.Types ( TYPE )
import Data.Type.Equality
-import GHC.List ( splitAt, foldl )
+import GHC.List ( splitAt, foldl' )
import GHC.Word
import GHC.Show
import GHC.TypeLits ( KnownSymbol, symbolVal' )
@@ -209,7 +209,7 @@ instance Ord (TypeRep a) where
-- | A non-indexed type representation.
data SomeTypeRep where
- SomeTypeRep :: forall k (a :: k). TypeRep a -> SomeTypeRep
+ SomeTypeRep :: forall k (a :: k). !(TypeRep a) -> SomeTypeRep
instance Eq SomeTypeRep where
SomeTypeRep a == SomeTypeRep b =
@@ -308,7 +308,7 @@ typeRepTyCon (TrFun _ _ _) = error "typeRepTyCon: FunTy" -- TODO
eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2).
TypeRep a -> TypeRep b -> Maybe (a :~~: b)
eqTypeRep a b
- | typeRepFingerprint a == typeRepFingerprint b = Just (unsafeCoerce# HRefl)
+ | typeRepFingerprint a == typeRepFingerprint b = Just (unsafeCoerce HRefl)
| otherwise = Nothing
@@ -349,7 +349,7 @@ instantiateKindRep vars = go
applyTy (SomeTypeRep acc) ty
| SomeTypeRep ty' <- go ty
= SomeTypeRep $ mkTrApp (unsafeCoerce acc) (unsafeCoerce ty')
- in foldl applyTy tycon_app ty_args
+ in foldl' applyTy tycon_app ty_args
go (KindRepVar var)
= vars A.! var
go (KindRepApp f a)
@@ -517,7 +517,7 @@ splitApps = go []
go xs (TrApp _ f x) = go (SomeTypeRep x : xs) f
go [] (TrFun _ a b) = (funTyCon, [SomeTypeRep a, SomeTypeRep b])
go _ (TrFun _ _ _) =
- error "Data.Typeable.Internal.splitApps: Impossible"
+ errorWithoutStackTrace "Data.Typeable.Internal.splitApps: Impossible"
funTyCon :: TyCon
funTyCon = typeRepTyCon (typeRep @(->))
diff --git a/libraries/base/GHC/Show.hs b/libraries/base/GHC/Show.hs
index 510c655..c52824b 100644
--- a/libraries/base/GHC/Show.hs
+++ b/libraries/base/GHC/Show.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, StandaloneDeriving,
- MagicHash, UnboxedTuples, PolyKinds #-}
+ MagicHash, UnboxedTuples #-}
{-# OPTIONS_HADDOCK hide #-}
#include "MachDeps.h"
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index fd8f188..68650e3 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -56,14 +56,14 @@
imported from `Control.Applicative`. It is likely to be added to the
`Prelude` in the future. (#13191)
- * A new module exposing GHC's new type-indexed type representation
- mechanism, `Type.Reflection`, is now provided.
+ * A new module, `Type.Reflection`, exposing GHC's new type-indexed type
+ representation mechanism is now provided.
* `Data.Dynamic` now exports the `Dyn` data constructor, enabled by the new
type-indexed type representation mechanism.
- * `Data.Type.Equality` now provides a kind heterogeneous type equality type,
- `(:~~:)`.
+ * `Data.Type.Equality` now provides a kind heterogeneous type equality
+ evidence type, `(:~~:)`.
## 4.9.0.0 *May 2016*
diff --git a/libraries/ghc-boot/GHC/Serialized.hs b/libraries/ghc-boot/GHC/Serialized.hs
index 42a9604..161bbb3 100644
--- a/libraries/ghc-boot/GHC/Serialized.hs
+++ b/libraries/ghc-boot/GHC/Serialized.hs
@@ -29,9 +29,7 @@ data Serialized = Serialized TypeRep [Word8]
-- | Put a Typeable value that we are able to actually turn into bytes into a 'Serialized' value ready for deserialization later
toSerialized :: forall a. Typeable a => (a -> [Word8]) -> a -> Serialized
-toSerialized serialize what = Serialized rep (serialize what)
- where
- rep = typeOf what
+toSerialized serialize what = Serialized (typeOf what) (serialize what)
-- | If the 'Serialized' value contains something of the given type, then use the specified deserializer to return @Just@ that.
-- Otherwise return @Nothing at .
More information about the ghc-commits
mailing list