[commit: ghc] master: Remove references to SynTyCon. Fixes #9812 (668a137)
git at git.haskell.org
git at git.haskell.org
Tue Dec 2 13:10:52 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/668a1379778189495679840e0151dfceed4b8ef7/ghc
>---------------------------------------------------------------
commit 668a1379778189495679840e0151dfceed4b8ef7
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date: Tue Dec 2 13:57:46 2014 +0100
Remove references to SynTyCon. Fixes #9812
>---------------------------------------------------------------
668a1379778189495679840e0151dfceed4b8ef7
compiler/typecheck/TcTyDecls.lhs | 9 +++++----
compiler/types/TyCon.hs | 4 ++--
compiler/vectorise/Vectorise/Utils/Base.hs | 6 +++---
compiler/vectorise/Vectorise/Utils/PADict.hs | 3 ++-
4 files changed, 12 insertions(+), 10 deletions(-)
diff --git a/compiler/typecheck/TcTyDecls.lhs b/compiler/typecheck/TcTyDecls.lhs
index c998853..3f8b234 100644
--- a/compiler/typecheck/TcTyDecls.lhs
+++ b/compiler/typecheck/TcTyDecls.lhs
@@ -97,10 +97,10 @@ If we reverse this decision, this comment came from tcTyDecl1, and should
We'd also need to add back in this definition
-synTyConsOfType :: Type -> [TyCon]
+synonymTyConsOfType :: Type -> [TyCon]
-- Does not look through type synonyms at all
-- Return a list of synonym tycons
-synTyConsOfType ty
+synonymTyConsOfType ty
= nameEnvElts (go ty)
where
go :: Type -> NameEnv TyCon -- The NameEnv does duplicate elim
@@ -110,8 +110,9 @@ synTyConsOfType ty
go (FunTy a b) = go a `plusNameEnv` go b
go (ForAllTy _ ty) = go ty
- go_tc tc tys | isSynTyCon tc = extendNameEnv (go_s tys) (tyConName tc) tc
- | otherwise = go_s tys
+ go_tc tc tys | isTypeSynonymTyCon tc = extendNameEnv (go_s tys)
+ (tyConName tc) tc
+ | otherwise = go_s tys
go_s tys = foldr (plusNameEnv . go) emptyNameEnv tys
---------------------------------------- END NOTE ]
diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs
index 5a2b33e..4283545 100644
--- a/compiler/types/TyCon.hs
+++ b/compiler/types/TyCon.hs
@@ -140,14 +140,14 @@ Note [Type synonym families]
* Translation of type family decl:
type family F a :: *
translates to
- a SynTyCon 'F', whose SynTyConRhs is OpenSynFamilyTyCon
+ a FamilyTyCon 'F', whose FamTyConFlav is OpenSynFamilyTyCon
type family G a :: * where
G Int = Bool
G Bool = Char
G a = ()
translates to
- a SynTyCon 'G', whose SynTyConRhs is ClosedSynFamilyTyCon, with the
+ a FamilyTyCon 'G', whose FamTyConFlav is ClosedSynFamilyTyCon, with the
appropriate CoAxiom representing the equations
* In the future we might want to support
diff --git a/compiler/vectorise/Vectorise/Utils/Base.hs b/compiler/vectorise/Vectorise/Utils/Base.hs
index 7d4bae3..dc1f210 100644
--- a/compiler/vectorise/Vectorise/Utils/Base.hs
+++ b/compiler/vectorise/Vectorise/Utils/Base.hs
@@ -24,7 +24,7 @@ module Vectorise.Utils.Base
, pdatasReprTyConExact
, pdataUnwrapScrut
- , preprSynTyCon
+ , preprFamInst
) where
import Vectorise.Monad
@@ -258,5 +258,5 @@ pdataUnwrapScrut (ve, le)
-- |Get the representation tycon of the 'PRepr' type family for a given type.
--
-preprSynTyCon :: Type -> VM FamInstMatch
-preprSynTyCon ty = builtin preprTyCon >>= (`lookupFamInst` [ty])
+preprFamInst :: Type -> VM FamInstMatch
+preprFamInst ty = builtin preprTyCon >>= (`lookupFamInst` [ty])
diff --git a/compiler/vectorise/Vectorise/Utils/PADict.hs b/compiler/vectorise/Vectorise/Utils/PADict.hs
index 01fbede..c2ca20a 100644
--- a/compiler/vectorise/Vectorise/Utils/PADict.hs
+++ b/compiler/vectorise/Vectorise/Utils/PADict.hs
@@ -118,7 +118,8 @@ paMethod method _ ty
prDictOfPReprInst :: Type -> VM CoreExpr
prDictOfPReprInst ty
= do
- { (FamInstMatch { fim_instance = prepr_fam, fim_tys = prepr_args }) <- preprSynTyCon ty
+ { (FamInstMatch { fim_instance = prepr_fam, fim_tys = prepr_args })
+ <- preprFamInst ty
; prDictOfPReprInstTyCon ty (famInstAxiom prepr_fam) prepr_args
}
More information about the ghc-commits
mailing list