[commit: ghc] wip/T9858-typeable-ben2: Fixes (d90b9f3)
git at git.haskell.org
git at git.haskell.org
Sun Sep 13 04:20:13 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T9858-typeable-ben2
Link : http://ghc.haskell.org/trac/ghc/changeset/d90b9f37281048a1bdc5f3e959d6243d4275dd37/ghc
>---------------------------------------------------------------
commit d90b9f37281048a1bdc5f3e959d6243d4275dd37
Author: Ben Gamari <ben at smart-cactus.org>
Date: Wed Sep 2 17:39:16 2015 +0200
Fixes
>---------------------------------------------------------------
d90b9f37281048a1bdc5f3e959d6243d4275dd37
compiler/prelude/PrelNames.hs | 6 ++----
compiler/prelude/TysWiredIn.hs | 1 +
compiler/typecheck/TcInteract.hs | 4 ++--
libraries/ghc-prim/GHC/Types.hs | 4 ++--
utils/haddock | 2 +-
5 files changed, 8 insertions(+), 9 deletions(-)
diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs
index 6dc4b9d..d7eec94 100644
--- a/compiler/prelude/PrelNames.hs
+++ b/compiler/prelude/PrelNames.hs
@@ -206,11 +206,9 @@ basicKnownKeyNames
-- Typeable
typeableClassName,
typeRepTyConName,
- mkTyConName,
mkPolyTyConAppName,
mkAppTyName,
- typeNatTypeRepName,
- typeSymbolTypeRepName,
+ typeLitTypeRepName,
-- Dynamic
toDynName,
@@ -1926,7 +1924,7 @@ mkTyConKey = mkPreludeMiscIdUnique 503
mkPolyTyConAppKey = mkPreludeMiscIdUnique 504
mkAppTyKey = mkPreludeMiscIdUnique 505
typeLitTypeRepKey = mkPreludeMiscIdUnique 506
-typeRepIdKey = mkPreludeMiscIdUnique 508
+typeRepIdKey = mkPreludeMiscIdUnique 508
-- Dynamic
toDynIdKey :: Unique
diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs
index 4c8a641..cbea073 100644
--- a/compiler/prelude/TysWiredIn.hs
+++ b/compiler/prelude/TysWiredIn.hs
@@ -984,6 +984,7 @@ ipCoName = mkWiredInCoAxiomName BuiltInSyntax gHC_CLASSES (fsLit "NTCo:IP")
-- See Note [The Implicit Parameter class]
ipTyCon :: TyCon
ipTyCon = mkClassTyCon ipTyConName kind [ip,a] [] rhs ipClass NonRecursive
+ (mkPrelTyConRepName ipTyConName)
where
kind = mkArrowKinds [typeSymbolKind, liftedTypeKind] constraintKind
[ip,a] = mkTemplateTyVars [typeSymbolKind, liftedTypeKind]
diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs
index 1d9b737..00c6090 100644
--- a/compiler/typecheck/TcInteract.hs
+++ b/compiler/typecheck/TcInteract.hs
@@ -23,7 +23,7 @@ import TcType
import Name
import PrelNames ( knownNatClassName, knownSymbolClassName,
callStackTyConKey, typeableClassName )
-import TysWiredIn ( ipClass, typeNatKind, typeSymbolKind )
+import TysWiredIn ( ipClass )
import Id( idType )
import Class
import TyCon
@@ -771,7 +771,7 @@ interactGivenIP _ wi = pprPanic "interactGivenIP" (ppr wi)
-- i.e. (IP "name" CallStack)
isCallStackIP :: CtLoc -> Class -> [Type] -> Maybe (EvTerm -> EvCallStack)
isCallStackIP loc cls tys
- | cls `hasKey` ipClassNameKey
+ | cls == ipClass
, [_ip_name, ty] <- tys
, Just (tc, _) <- splitTyConApp_maybe ty
, tc `hasKey` callStackTyConKey
diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs
index 9452556..fe76819 100644
--- a/libraries/ghc-prim/GHC/Types.hs
+++ b/libraries/ghc-prim/GHC/Types.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE MagicHash, NoImplicitPrelude, TypeFamilies, UnboxedTuples,
- MultiParamTypeClasses, RoleAnnotations #-}
+ MultiParamTypeClasses, RoleAnnotations, CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : GHC.Types
@@ -30,7 +30,7 @@ module GHC.Types (
SPEC(..),
Nat, Symbol,
Coercible,
- SrcLoc(..), CallStack(..)
+ SrcLoc(..), CallStack(..),
TyCon(..), TrName(..), Module(..)
) where
diff --git a/utils/haddock b/utils/haddock
index 7570ed8..a66185c 160000
--- a/utils/haddock
+++ b/utils/haddock
@@ -1 +1 @@
-Subproject commit 7570ed8595402bcd354b7b24de1f4b0e3e527a58
+Subproject commit a66185c01b5d7911f0c15eea2434c5e1302fc6be
More information about the ghc-commits
mailing list