[commit: ghc] wip/t11715: Use mkCastTy in subst_ty (07a1c1b)
git at git.haskell.org
git at git.haskell.org
Thu Feb 9 03:06:25 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/t11715
Link : http://ghc.haskell.org/trac/ghc/changeset/07a1c1b4d97e689a59b90b4095a977afe4638bbb/ghc
>---------------------------------------------------------------
commit 07a1c1b4d97e689a59b90b4095a977afe4638bbb
Author: Richard Eisenberg <rae at cs.brynmawr.edu>
Date: Sun Jan 29 00:11:15 2017 -0500
Use mkCastTy in subst_ty
>---------------------------------------------------------------
07a1c1b4d97e689a59b90b4095a977afe4638bbb
compiler/types/TyCoRep.hs | 6 ++++--
compiler/types/Type.hs-boot | 3 ++-
2 files changed, 6 insertions(+), 3 deletions(-)
diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs
index 85a1df8..696cd42 100644
--- a/compiler/types/TyCoRep.hs
+++ b/compiler/types/TyCoRep.hs
@@ -138,7 +138,7 @@ import {-# SOURCE #-} DataCon( dataConFullSig
, DataCon, filterEqSpec )
import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy
, tyCoVarsOfTypesWellScoped
- , coreView, typeKind )
+ , coreView, typeKind, mkCastTy )
-- Transitively pulls in a LOT of stuff, better to break the loop
import {-# SOURCE #-} Coercion
@@ -2180,7 +2180,9 @@ 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)
+ -- NB: mkCastTy, not CastTy. The subst_co might make something
+ -- reflexive
go (CoercionTy co) = CoercionTy $! (subst_co subst co)
substTyVar :: TCvSubst -> TyVar -> Type
diff --git a/compiler/types/Type.hs-boot b/compiler/types/Type.hs-boot
index 78c6681..39a4c80 100644
--- a/compiler/types/Type.hs-boot
+++ b/compiler/types/Type.hs-boot
@@ -1,12 +1,13 @@
module Type where
import TyCon
import Var ( TyVar )
-import {-# SOURCE #-} TyCoRep( Type, Kind )
+import {-# SOURCE #-} TyCoRep( Type, Kind, Coercion )
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