[commit: ghc] wip/ttypeable: Debug (05c1608)

git at git.haskell.org git at git.haskell.org
Sat Oct 1 21:36:03 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/ttypeable
Link       : http://ghc.haskell.org/trac/ghc/changeset/05c160895638238189d44cc6ed23b5451d2c1a54/ghc

>---------------------------------------------------------------

commit 05c160895638238189d44cc6ed23b5451d2c1a54
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Mon Sep 5 21:51:34 2016 -0400

    Debug


>---------------------------------------------------------------

05c160895638238189d44cc6ed23b5451d2c1a54
 libraries/base/Data/Typeable/Internal.hs | 17 ++++++++++-------
 1 file changed, 10 insertions(+), 7 deletions(-)

diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index bc10e36..870189a 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -338,14 +338,18 @@ typeRepXFingerprint (TypeRepX t) = typeRepFingerprint t
 instance Show (TypeRep (a :: k)) where
     showsPrec = showTypeable
 
+fpr _ = id
+--fpr rep = showString " (" . shows (typeRepFingerprint rep) . showString ")"
+
 showTypeable :: Int -> TypeRep (a :: k) -> ShowS
 showTypeable p rep
   | Just HRefl <- star `eqTypeRep` typeRepKind rep =
-    showTypeable' 9 rep
+    showParen True $
+    showTypeable' 1 rep . fpr (typeRepKind rep) . fpr rep
 
   | otherwise =
-    showParen (p > 9) $
-    showTypeable' 9 rep . showString " :: " . showTypeable' 8 (typeRepKind rep)
+    showParen (p > 1) $
+    showTypeable' 1 rep . showString " :: " . showParen True (showTypeable' 0 (typeRepKind rep) . fpr (typeRepKind rep)) . fpr rep
 
 showTypeable' :: Int -> TypeRep (a :: k) -> ShowS
 showTypeable' _ rep
@@ -356,10 +360,9 @@ showTypeable' _ rep
   | isTupleTyCon tc =
     showChar '(' . showArgs (showChar ',') tys . showChar ')'
   where (tc, tys) = splitApps rep
-showTypeable' p (TrTyCon _ tycon _) = showsPrec p tycon
---showTypeable' p (TRFun x r) =
---      showParen (p > 8) $
---      showsPrec 9 x . showString " -> " . showsPrec 8 r
+showTypeable' p (TrTyCon _ tycon _) =
+    showParen (p > 9) $
+    showsPrec p tycon
 showTypeable' p (TrApp _ (TrApp _ (TrTyCon _ tycon _) x) r)
   | isArrowTyCon tycon =
     showParen (p > 8) $



More information about the ghc-commits mailing list