[commit: ghc] master: Dead code removal, export cleanup (195af2d)

git at git.haskell.org git at git.haskell.org
Fri Sep 11 23:22:49 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/195af2d5222e667f9b423ef43286540e6b4bc252/ghc

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

commit 195af2d5222e667f9b423ef43286540e6b4bc252
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date:   Fri Sep 11 23:55:52 2015 +0200

    Dead code removal, export cleanup


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

195af2d5222e667f9b423ef43286540e6b4bc252
 compiler/rename/RnTypes.hs       | 14 +-------------
 compiler/typecheck/FamInst.hs    |  4 +---
 compiler/typecheck/TcValidity.hs |  1 -
 compiler/utils/Outputable.hs     | 23 +----------------------
 4 files changed, 3 insertions(+), 39 deletions(-)

diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs
index 090ed64..8b709de 100644
--- a/compiler/rename/RnTypes.hs
+++ b/compiler/rename/RnTypes.hs
@@ -22,7 +22,7 @@ module RnTypes (
         -- Binding related stuff
         warnContextQuantification, warnUnusedForAlls,
         bindSigTyVarsFV, bindHsTyVars, rnHsBndrSig, rnLHsTyVarBndr,
-        extractHsTyRdrTyVars, extractHsTysRdrTyVars, extractTyVarBndrNames,
+        extractHsTyRdrTyVars, extractHsTysRdrTyVars,
         extractRdrKindSigVars, extractDataDefnKindVars,
         filterInScope
   ) where
@@ -48,7 +48,6 @@ import Outputable
 import FastString
 import Maybes
 import Data.List        ( nub, nubBy, deleteFirstsBy )
-import qualified Data.Set as Set
 import Control.Monad    ( unless, when )
 
 #if __GLASGOW_HASKELL__ < 709
@@ -1123,17 +1122,6 @@ extractHsTysRdrTyVars ty
   = case extract_ltys ty ([],[]) of
      (kvs, tvs) -> (nub kvs, nub tvs)
 
--- Extracts variable names used in a type variable binder. Note that HsType
--- represents data and type constructors as type variables and so this function
--- will also return data and type constructors.
-extractTyVarBndrNames :: LHsTyVarBndr RdrName -> Set.Set RdrName
-extractTyVarBndrNames (L _ (UserTyVar name))
-  = Set.singleton name
-extractTyVarBndrNames (L _ (KindedTyVar (L _ name) k))
-  = Set.singleton name `Set.union` (Set.fromList tvs)
-                       `Set.union` (Set.fromList kvs)
-    where (kvs, tvs) = extractHsTyRdrTyVars k
-
 extractRdrKindSigVars :: LFamilyResultSig RdrName -> [RdrName]
 extractRdrKindSigVars (L _ resultSig)
     | KindSig k                        <- resultSig = kindRdrNameFromSig k
diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs
index b598f2a..b7285a6 100644
--- a/compiler/typecheck/FamInst.hs
+++ b/compiler/typecheck/FamInst.hs
@@ -11,9 +11,7 @@ module FamInst (
         newFamInst,
 
         -- * Injectivity
-        makeInjectivityErrors,
-
-        tfHeadedErr, bareVariableInRHSErr
+        makeInjectivityErrors
     ) where
 
 import HscTypes
diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs
index c1b8a09..f9d9bf7 100644
--- a/compiler/typecheck/TcValidity.hs
+++ b/compiler/typecheck/TcValidity.hs
@@ -12,7 +12,6 @@ module TcValidity (
   checkValidInstance, validDerivPred,
   checkInstTermination,
   checkValidCoAxiom, checkValidCoAxBranch,
-  checkTyFamFreeness,
   checkConsistentFamInst,
   arityErr, badATErr
   ) where
diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs
index cb42d75..a4893b9 100644
--- a/compiler/utils/Outputable.hs
+++ b/compiler/utils/Outputable.hs
@@ -32,8 +32,7 @@ module Outputable (
         sep, cat,
         fsep, fcat,
         hang, punctuate, ppWhen, ppUnless,
-        speakNth, speakNTimes, speakN, speakNOf, plural,
-        thirdPerson, isOrAre, doOrDoes,
+        speakNth, speakN, speakNOf, plural, isOrAre, doOrDoes,
 
         coloured, PprColour, colType, colCoerc, colDataCon,
         colBinder, bold, keyword,
@@ -976,16 +975,6 @@ speakNOf 0 d = ptext (sLit "no") <+> d <> char 's'
 speakNOf 1 d = ptext (sLit "one") <+> d                 -- E.g. "one argument"
 speakNOf n d = speakN n <+> d <> char 's'               -- E.g. "three arguments"
 
--- | Converts a strictly positive integer into a number of times:
---
--- > speakNTimes 1 = text "once"
--- > speakNTimes 2 = text "twice"
--- > speakNTimes 4 = text "4 times"
-speakNTimes :: Int {- >=1 -} -> SDoc
-speakNTimes t | t == 1     = ptext (sLit "once")
-              | t == 2     = ptext (sLit "twice")
-              | otherwise  = speakN t <+> ptext (sLit "times")
-
 -- | Determines the pluralisation suffix appropriate for the length of a list:
 --
 -- > plural [] = char 's'
@@ -995,16 +984,6 @@ plural :: [a] -> SDoc
 plural [_] = empty  -- a bit frightening, but there you are
 plural _   = char 's'
 
--- | Determines the suffix to use in 3rd person singular depending on the length
--- of a list:
---
--- > thirdPerson [] = empty
--- > thirdPerson ["Hello"] = char 's'
--- > thirdPerson ["Hello", "World"] = empty
-thirdPerson :: [a] -> SDoc
-thirdPerson [_] = char 's'
-thirdPerson  _  = empty
-
 -- | Determines the form of to be appropriate for the length of a list:
 --
 -- > isOrAre [] = ptext (sLit "are")



More information about the ghc-commits mailing list