[commit: ghc] wip/ttypeable: Fix a few TTypeRep references (58b2cf7)
git at git.haskell.org
git at git.haskell.org
Mon Jun 6 11:12:37 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/ttypeable
Link : http://ghc.haskell.org/trac/ghc/changeset/58b2cf7b112c7638880bc225b4988112a18af8a2/ghc
>---------------------------------------------------------------
commit 58b2cf7b112c7638880bc225b4988112a18af8a2
Author: Ben Gamari <ben at smart-cactus.org>
Date: Wed Mar 16 11:51:00 2016 +0100
Fix a few TTypeRep references
>---------------------------------------------------------------
58b2cf7b112c7638880bc225b4988112a18af8a2
compiler/deSugar/DsBinds.hs | 12 ++++++------
1 file changed, 6 insertions(+), 6 deletions(-)
diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs
index c492074..8c8642e 100644
--- a/compiler/deSugar/DsBinds.hs
+++ b/compiler/deSugar/DsBinds.hs
@@ -1127,10 +1127,10 @@ type TypeRepExpr = CoreExpr
ds_ev_typeable :: Type -> EvTypeable -> DsM CoreExpr
ds_ev_typeable ty (EvTypeableTyCon tc kind_ev)
= do { mkTrCon <- dsLookupGlobalId mkTrConName
- -- mkTrCon :: forall k (a :: k). TyCon -> TTypeRep k -> TTypeRep a
+ -- mkTrCon :: forall k (a :: k). TyCon -> TypeRep k -> TypeRep a
; tc_rep <- tyConRep tc -- :: TyCon
- ; kind_rep <- getRep kind_ev (typeKind ty) -- :: TTypeRep k
+ ; kind_rep <- getRep kind_ev (typeKind ty) -- :: TypeRep k
-- Note that we use the kind of the type, not the TyCon from which it is
-- constructed since the latter may be kind polymorphic whereas the
@@ -1161,8 +1161,8 @@ ds_ev_typeable ty (EvTypeableTyLit ev)
ty_kind = typeKind ty
-- tr_fun is the Name of
- -- typeNatTypeRep :: KnownNat a => Proxy# a -> TTypeRep a
- -- of typeSymbolTypeRep :: KnownSymbol a => Proxy# a -> TTypeRep a
+ -- typeNatTypeRep :: KnownNat a => Proxy# a -> TypeRep a
+ -- of typeSymbolTypeRep :: KnownSymbol a => Proxy# a -> TypeRep a
tr_fun | ty_kind `eqType` typeNatKind = typeNatTypeRepName
| ty_kind `eqType` typeSymbolKind = typeSymbolTypeRepName
| otherwise = panic "dsEvTypeable: unknown type lit kind"
@@ -1176,10 +1176,10 @@ ds_ev_typeable ty ev
getRep :: EvTerm -- ^ EvTerm for @Typeable ty@
-> Type -- ^ The type @ty@
- -> DsM TypeRepExpr -- ^ Return @CoreExpr :: TTypeRep ty@
+ -> DsM TypeRepExpr -- ^ Return @CoreExpr :: TypeRep ty@
-- namely @typeRep# dict@
-- Remember that
--- typeRep# :: forall k (a::k). Typeable k a -> TTypeRep a
+-- typeRep# :: forall k (a::k). Typeable k a -> TypeRep a
getRep ev ty
= do { typeable_expr <- dsEvTerm ev
; typeRepId <- dsLookupGlobalId typeRepIdName
More information about the ghc-commits
mailing list