[commit: ghc] ghc-8.2: Use mkCastTy in subst_ty. (769bb2d)
git at git.haskell.org
git at git.haskell.org
Wed May 3 13:27:05 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.2
Link : http://ghc.haskell.org/trac/ghc/changeset/769bb2d1ce8885e4fa7c8151f5a2840770e628f8/ghc
>---------------------------------------------------------------
commit 769bb2d1ce8885e4fa7c8151f5a2840770e628f8
Author: Richard Eisenberg <rae at cs.brynmawr.edu>
Date: Fri Apr 7 11:39:51 2017 -0400
Use mkCastTy in subst_ty.
This allows mkCastTy to maintain invariants. Much like how
we use mkAppTy in subst_ty.
(cherry picked from commit 466803a0e9628ccd5feb55d062e141e0972fc19c)
>---------------------------------------------------------------
769bb2d1ce8885e4fa7c8151f5a2840770e628f8
compiler/types/TyCoRep.hs | 4 ++--
compiler/types/Type.hs | 11 -----------
compiler/types/Type.hs-boot | 3 ++-
3 files changed, 4 insertions(+), 14 deletions(-)
diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs
index 52a0f1d..300ef80 100644
--- a/compiler/types/TyCoRep.hs
+++ b/compiler/types/TyCoRep.hs
@@ -135,7 +135,7 @@ module TyCoRep (
import {-# SOURCE #-} DataCon( dataConFullSig
, dataConUnivTyVarBinders, dataConExTyVarBinders
, DataCon, filterEqSpec )
-import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy
+import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy, mkCastTy
, tyCoVarsOfTypesWellScoped
, tyCoVarsOfTypeWellScoped
, coreView, typeKind )
@@ -2186,7 +2186,7 @@ subst_ty subst ty
(ForAllTy $! ((TvBndr $! tv') vis)) $!
(subst_ty subst' ty)
go (LitTy n) = LitTy $! n
- go (CastTy ty co) = (CastTy $! (go ty)) $! (subst_co subst co)
+ go (CastTy ty co) = (mkCastTy $! (go ty)) $! (subst_co subst co)
go (CoercionTy co) = CoercionTy $! (subst_co subst co)
substTyVar :: TCvSubst -> TyVar -> Type
diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs
index 77e4499..2ff78b4 100644
--- a/compiler/types/Type.hs
+++ b/compiler/types/Type.hs
@@ -1222,10 +1222,6 @@ mkCastTy ty co | isReflexiveCo co = ty
mkCastTy (CastTy ty co1) co2 = mkCastTy ty (co1 `mkTransCo` co2)
mkCastTy ty co = CastTy ty co
-tyConTyBinders :: TyCon -> [TyBinder]
--- Return the tyConBinders in TyBinder form
-tyConTyBinders tycon = tyConBindersTyBinders (tyConBinders tycon)
-
tyConBindersTyBinders :: [TyConBinder] -> [TyBinder]
-- Return the tyConBinders in TyBinder form
tyConBindersTyBinders = map to_tyb
@@ -1529,13 +1525,6 @@ caseBinder :: TyBinder -- ^ binder to scrutinize
caseBinder (Named v) f _ = f v
caseBinder (Anon t) _ d = d t
--- | Create a TCvSubst combining the binders and types provided.
--- NB: It is specifically OK if the lists are of different lengths.
--- Barely used
-zipTyBinderSubst :: [TyBinder] -> [Type] -> TCvSubst
-zipTyBinderSubst bndrs tys
- = mkTvSubstPrs [ (tv, ty) | (Named (TvBndr tv _), ty) <- zip bndrs tys ]
-
-- | Manufacture a new 'TyConBinder' from a 'TyBinder'. Anonymous
-- 'TyBinder's are still assigned names as 'TyConBinder's, so we need
-- the extra gunk with which to construct a 'Name'. Used when producing
diff --git a/compiler/types/Type.hs-boot b/compiler/types/Type.hs-boot
index be7e4ed..2fc251a 100644
--- a/compiler/types/Type.hs-boot
+++ b/compiler/types/Type.hs-boot
@@ -3,13 +3,14 @@
module Type where
import TyCon
import Var ( TyVar )
-import {-# SOURCE #-} TyCoRep( Type, Kind )
+import {-# SOURCE #-} TyCoRep( Type, Coercion, Kind )
import Util
isPredTy :: Type -> Bool
isCoercionTy :: Type -> Bool
mkAppTy :: Type -> Type -> Type
+mkCastTy :: Type -> Coercion -> Type
piResultTy :: Type -> Type -> Type
typeKind :: Type -> Kind
More information about the ghc-commits
mailing list