[commit: ghc] wip/ttypeable: Kill debugShow (c3dc056)

git at git.haskell.org git at git.haskell.org
Mon Jun 6 11:12:18 UTC 2016


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

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

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

commit c3dc056a5da32f550d56d5619bd82527a504d015
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Wed Mar 16 22:08:49 2016 +0100

    Kill debugShow


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

c3dc056a5da32f550d56d5619bd82527a504d015
 libraries/base/Data/Typeable/Internal.hs | 18 ------------------
 libraries/base/Type/Reflection.hs        |  1 -
 2 files changed, 19 deletions(-)

diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index 7a2e914..09db187 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -71,8 +71,6 @@ module Data.Typeable.Internal (
     mkTrCon, mkTrApp, mkTyCon, mkTyCon#,
     typeSymbolTypeRep, typeNatTypeRep,
 
-    debugShow,
-
     -- * Representations for primitive types
     trTYPE,
     trTYPE'PtrRepLifted,
@@ -319,22 +317,6 @@ typeRepXFingerprint (TypeRepX t) = typeRepFingerprint t
 
 ----------------- Showing TypeReps --------------------
 
-debugShow :: TypeRep a -> String
-debugShow rep
-  | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type) = "Type"
-  | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep) = "RuntimeRep"
-  | (tc, _) <- splitApps rep
-  , isArrowTyCon tc = "Arrow"
-debugShow (TrApp _ f x) = "App ("++debugShow f++") ("++debugShow x++")"
-debugShow (TrTyCon _ x k)
-    | isArrowTyCon x = "Arrow"
-    | "->" <- show x = "Arrow #" ++ show ( tyConFingerprint x
-                                         , tyConFingerprint trArrowTyCon
-                                         , tyConFingerprint $ typeRepTyCon (typeRep :: TypeRep (->))
-                                         , typeRepTyCon (typeRep :: TypeRep (->))
-                                         )
-    | otherwise = show x++" :: "++debugShow k
-
 instance Show (TypeRep (a :: k)) where
   showsPrec _ rep
     | isListTyCon tc, [ty] <- tys =
diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs
index 480e148..8057a2e 100644
--- a/libraries/base/Type/Reflection.hs
+++ b/libraries/base/Type/Reflection.hs
@@ -37,7 +37,6 @@ module Type.Reflection
     , I.tyConModule
     , I.tyConName
     , I.rnfTyCon
-    , I.debugShow
     ) where
 
 import qualified Data.Typeable.Internal as I



More information about the ghc-commits mailing list