[commit: ghc] master: Remove unused tyConsOfDataCon (030abf9)
git at git.haskell.org
git at git.haskell.org
Thu Nov 6 15:42:34 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/030abf9e059cb1382df14c878a74e6709d744c17/ghc
>---------------------------------------------------------------
commit 030abf9e059cb1382df14c878a74e6709d744c17
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Nov 6 13:16:20 2014 +0000
Remove unused tyConsOfDataCon
>---------------------------------------------------------------
030abf9e059cb1382df14c878a74e6709d744c17
compiler/basicTypes/DataCon.lhs | 14 --------------
compiler/vectorise/Vectorise/Type/Classify.hs | 2 +-
2 files changed, 1 insertion(+), 15 deletions(-)
diff --git a/compiler/basicTypes/DataCon.lhs b/compiler/basicTypes/DataCon.lhs
index fa9e2e9..95969df 100644
--- a/compiler/basicTypes/DataCon.lhs
+++ b/compiler/basicTypes/DataCon.lhs
@@ -34,8 +34,6 @@ module DataCon (
splitDataProductType_maybe,
- tyConsOfTyCon,
-
-- ** Predicates on DataCons
isNullarySrcDataCon, isNullaryRepDataCon, isTupleDataCon, isUnboxedTupleCon,
isVanillaDataCon, classDataCon, dataConCannotMatch,
@@ -67,7 +65,6 @@ import BasicTypes
import FastString
import Module
import VarEnv
-import NameEnv
import qualified Data.Data as Data
import qualified Data.Typeable
@@ -1126,15 +1123,4 @@ splitDataProductType_maybe ty
= Just (tycon, ty_args, con, dataConInstArgTys con ty_args)
| otherwise
= Nothing
-
--- | All type constructors used in the definition of this type constructor,
--- recursively. This is used to find out all the type constructors whose data
--- constructors need to be in scope to be allowed to safely coerce under this
--- type constructor in Safe Haskell mode.
-tyConsOfTyCon :: TyCon -> [TyCon]
-tyConsOfTyCon tc = nameEnvElts (add tc emptyNameEnv)
- where
- go env tc = foldr add env (tyConDataCons tc >>= dataConOrigArgTys >>= tyConsOfType)
- add tc env | tyConName tc `elemNameEnv` env = env
- | otherwise = go (extendNameEnv env (tyConName tc) tc) tc
\end{code}
diff --git a/compiler/vectorise/Vectorise/Type/Classify.hs b/compiler/vectorise/Vectorise/Type/Classify.hs
index 56b8da5..dcc41dd 100644
--- a/compiler/vectorise/Vectorise/Type/Classify.hs
+++ b/compiler/vectorise/Vectorise/Type/Classify.hs
@@ -21,7 +21,7 @@ where
import NameSet
import UniqSet
import UniqFM
-import DataCon hiding (tyConsOfTyCon)
+import DataCon
import TyCon
import TypeRep
import Type hiding (tyConsOfType)
More information about the ghc-commits
mailing list