[commit: ghc] master: More allDistinctTyVars from TcDeriv to Type (0451f91)
git at git.haskell.org
git at git.haskell.org
Fri Jun 27 08:19:15 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/0451f9137a73777170cd797406a1afb67cfb8916/ghc
>---------------------------------------------------------------
commit 0451f9137a73777170cd797406a1afb67cfb8916
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Jun 24 22:19:24 2014 +0100
More allDistinctTyVars from TcDeriv to Type
Just a minor refactoring
>---------------------------------------------------------------
0451f9137a73777170cd797406a1afb67cfb8916
compiler/typecheck/TcDeriv.lhs | 10 ----------
compiler/types/Type.lhs | 13 +++++++++++--
2 files changed, 11 insertions(+), 12 deletions(-)
diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs
index 492a99e..1d7936d 100644
--- a/compiler/typecheck/TcDeriv.lhs
+++ b/compiler/typecheck/TcDeriv.lhs
@@ -1444,16 +1444,6 @@ cond_functorOK allowFunctions (_, rep_tc, _)
functions = ptext (sLit "must not contain function types")
wrong_arg = ptext (sLit "must use the type variable only as the last argument of a data type")
-allDistinctTyVars :: [KindOrType] -> Bool
-allDistinctTyVars tkvs = go emptyVarSet tkvs
- where
- go _ [] = True
- go so_far (ty : tys)
- = case getTyVar_maybe ty of
- Nothing -> False
- Just tv | tv `elemVarSet` so_far -> False
- | otherwise -> go (so_far `extendVarSet` tv) tys
-
checkFlag :: ExtensionFlag -> Condition
checkFlag flag (dflags, _, _)
| xopt flag dflags = Nothing
diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs
index 808216f..55df6432 100644
--- a/compiler/types/Type.lhs
+++ b/compiler/types/Type.lhs
@@ -36,7 +36,7 @@ module Type (
mkForAllTy, mkForAllTys, splitForAllTy_maybe, splitForAllTys,
mkPiKinds, mkPiType, mkPiTypes,
- applyTy, applyTys, applyTysD, isForAllTy, dropForAlls,
+ applyTy, applyTys, applyTysD, dropForAlls,
mkNumLitTy, isNumLitTy,
mkStrLitTy, isStrLitTy,
@@ -63,7 +63,7 @@ module Type (
funTyCon,
-- ** Predicates on types
- isTypeVar, isKindVar,
+ isTypeVar, isKindVar, allDistinctTyVars, isForAllTy,
isTyVarTy, isFunTy, isDictTy, isPredTy, isVoidTy,
-- (Lifting and boxity)
@@ -323,6 +323,15 @@ getTyVar_maybe ty | Just ty' <- coreView ty = getTyVar_maybe ty'
getTyVar_maybe (TyVarTy tv) = Just tv
getTyVar_maybe _ = Nothing
+allDistinctTyVars :: [KindOrType] -> Bool
+allDistinctTyVars tkvs = go emptyVarSet tkvs
+ where
+ go _ [] = True
+ go so_far (ty : tys)
+ = case getTyVar_maybe ty of
+ Nothing -> False
+ Just tv | tv `elemVarSet` so_far -> False
+ | otherwise -> go (so_far `extendVarSet` tv) tys
\end{code}
More information about the ghc-commits
mailing list