[commit: ghc] wip/gadtpm: remove unused stuff (b36ad5a)
git at git.haskell.org
git at git.haskell.org
Fri Nov 20 15:33:06 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/gadtpm
Link : http://ghc.haskell.org/trac/ghc/changeset/b36ad5a26d40fd7596ea7ea82c41e8e1f4d5e219/ghc
>---------------------------------------------------------------
commit b36ad5a26d40fd7596ea7ea82c41e8e1f4d5e219
Author: George Karachalias <george.karachalias at gmail.com>
Date: Fri Nov 20 16:31:05 2015 +0100
remove unused stuff
>---------------------------------------------------------------
b36ad5a26d40fd7596ea7ea82c41e8e1f4d5e219
compiler/basicTypes/Var.hs | 4 +---
compiler/typecheck/TcMType.hs | 1 -
compiler/typecheck/TcRnTypes.hs | 13 -------------
3 files changed, 1 insertion(+), 17 deletions(-)
diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs
index 2b22f36..925ffe3 100644
--- a/compiler/basicTypes/Var.hs
+++ b/compiler/basicTypes/Var.hs
@@ -205,7 +205,6 @@ After CoreTidy, top-level LocalIds are turned into GlobalIds
-}
instance Outputable Var where
- -- ppr var = parens (ppr (varName var) <+> dcolon <+> ppr (varType var)) <> getPprStyle (ppr_debug var)
ppr var = ppr (varName var) <> getPprStyle (ppr_debug var)
ppr_debug :: Var -> PprStyle -> SDoc
@@ -308,8 +307,7 @@ mkTcTyVar name kind details
tcTyVarDetails :: TyVar -> TcTyVarDetails
tcTyVarDetails (TcTyVar { tc_tv_details = details }) = details
-tcTyVarDetails tv@(TyVar {}) = pprPanic "tcTyVarDetails" (ptext (sLit "TyVar") $$ ppr tv)
-tcTyVarDetails tv@(Id {}) = pprPanic "tcTyVarDetails" (ptext (sLit "Id") $$ ppr tv)
+tcTyVarDetails var = pprPanic "tcTyVarDetails" (ppr var)
setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVar
setTcTyVarDetails tv details = tv { tc_tv_details = details }
diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs
index 6276b92..2f118fc 100644
--- a/compiler/typecheck/TcMType.hs
+++ b/compiler/typecheck/TcMType.hs
@@ -87,7 +87,6 @@ import Outputable
import FastString
import SrcLoc
import Bag
-import UniqSupply (UniqSupply, splitUniqSupply, uniqFromSupply)
import Control.Monad
import Data.List ( partition, mapAccumL )
diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs
index 32d78ad..49a35c6 100644
--- a/compiler/typecheck/TcRnTypes.hs
+++ b/compiler/typecheck/TcRnTypes.hs
@@ -91,9 +91,6 @@ module TcRnTypes(
pprEvVars, pprEvVarWithType,
pprArising, pprArisingAt,
- -- Debugging
- pprInTcRnIf,
-
-- Misc other types
TcId, TcIdSet, HoleSort(..)
@@ -151,10 +148,6 @@ import Data.Typeable ( TypeRep )
import qualified Language.Haskell.TH as TH
#endif
--- still debugging
-import System.IO.Unsafe (unsafePerformIO)
-
-
{-
************************************************************************
* *
@@ -2237,9 +2230,3 @@ data TcPluginResult
-- These are removed from the inert set,
-- and the evidence for them is recorded.
-- The second field contains new work, that should be processed by
-
---- - CHECKING MY PRINTING
-pprInTcRnIf :: SDoc -> TcRnIf gbl lcl ()
-pprInTcRnIf doc = do
- dflags <- getDynFlags
- liftIO (putStrLn (showSDoc dflags doc))
More information about the ghc-commits
mailing list