Skip to content
Snippets Groups Projects
Commit 71d2bf92 authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

isDataTyCon should be False for all type families, even data type families

isDataTyCon advertises that it's true of "data types that are
definitely represented by heap-allocated constructors.  These are
srcutinised by Core-level @case@ expressions, and they get info tables
allocated for them."

Type-family TyCons never have this property, not even data type families.
It's the *instance* TyCons that do.

I hope that this change does not break anything that somehow relied
on the old (wrong) semantics.
parent 59a4ad63
No related branches found
No related tags found
No related merge requests found
...@@ -14,7 +14,6 @@ module TcGadt ( ...@@ -14,7 +14,6 @@ module TcGadt (
Refinement, emptyRefinement, isEmptyRefinement, Refinement, emptyRefinement, isEmptyRefinement,
gadtRefine, gadtRefine,
refineType, refinePred, refineResType, refineType, refinePred, refineResType,
dataConCanMatch,
tcUnifyTys, BindFlag(..) tcUnifyTys, BindFlag(..)
) where ) where
...@@ -241,30 +240,11 @@ fixTvSubstEnv in_scope env ...@@ -241,30 +240,11 @@ fixTvSubstEnv in_scope env
where where
fixpt = mapVarEnv (substTy (mkTvSubst in_scope fixpt)) env fixpt = mapVarEnv (substTy (mkTvSubst in_scope fixpt)) env
----------------------------
dataConCanMatch :: [Type] -> DataCon -> Bool
-- Returns True iff the data con can match a scrutinee of type (T tys)
-- where T is the type constructor for the data con
--
-- Instantiate the equations and try to unify them
dataConCanMatch tys con
| null eq_spec = True -- Common
| all isTyVarTy tys = True -- Also common
| otherwise
= isJust (tcUnifyTys (\tv -> BindMe)
(map (substTyVar subst . fst) eq_spec)
(map snd eq_spec))
where
dc_tvs = dataConUnivTyVars con
eq_spec = dataConEqSpec con
subst = zipTopTvSubst dc_tvs tys
---------------------------- ----------------------------
tryToBind :: TyVarSet -> TyVar -> BindFlag tryToBind :: TyVarSet -> TyVar -> BindFlag
tryToBind tv_set tv | tv `elemVarSet` tv_set = BindMe tryToBind tv_set tv | tv `elemVarSet` tv_set = BindMe
| otherwise = AvoidMe | otherwise = AvoidMe
\end{code} \end{code}
......
...@@ -616,9 +616,14 @@ isDataTyCon :: TyCon -> Bool ...@@ -616,9 +616,14 @@ isDataTyCon :: TyCon -> Bool
-- True for all @data@ types -- True for all @data@ types
-- False for newtypes -- False for newtypes
-- unboxed tuples -- unboxed tuples
-- type families
--
-- NB: for a data type family, T, only the *instance* tycons are
-- get an info table etc. The family tycon does not.
-- Hence False for OpenTyCon
isDataTyCon tc@(AlgTyCon {algTcRhs = rhs}) isDataTyCon tc@(AlgTyCon {algTcRhs = rhs})
= case rhs of = case rhs of
OpenTyCon {} -> not (otIsNewtype rhs) OpenTyCon {} -> False
DataTyCon {} -> True DataTyCon {} -> True
NewTyCon {} -> False NewTyCon {} -> False
AbstractTyCon -> False -- We don't know, so return False AbstractTyCon -> False -- We don't know, so return False
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment