diff --git a/compiler/typecheck/TcGadt.lhs b/compiler/typecheck/TcGadt.lhs
index 3761c68fada484fa600e215005bb306fbcaf7f36..4cd7e004b2a210efede13796de9c0e85d2446c97 100644
--- a/compiler/typecheck/TcGadt.lhs
+++ b/compiler/typecheck/TcGadt.lhs
@@ -14,7 +14,6 @@ module TcGadt (
 	Refinement, emptyRefinement, isEmptyRefinement, 
 	gadtRefine, 
 	refineType, refinePred, refineResType,
-	dataConCanMatch,
 	tcUnifyTys, BindFlag(..)
   ) where
 
@@ -241,30 +240,11 @@ fixTvSubstEnv in_scope env
   where
     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 tv_set tv | tv `elemVarSet` tv_set = BindMe
 		    | otherwise	             = AvoidMe
 
-
 \end{code}
 
 
diff --git a/compiler/types/TyCon.lhs b/compiler/types/TyCon.lhs
index 50d76cf63c248034440368dd6b70d7c5ff035488..90ac71c8abc070dd7863ea28edb4d691090ff63f 100644
--- a/compiler/types/TyCon.lhs
+++ b/compiler/types/TyCon.lhs
@@ -616,9 +616,14 @@ isDataTyCon :: TyCon -> Bool
 --	True for all @data@ types
 --	False for newtypes
 --		  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})  
   = case rhs of
-        OpenTyCon {}  -> not (otIsNewtype rhs)
+        OpenTyCon {}  -> False
 	DataTyCon {}  -> True
 	NewTyCon {}   -> False
 	AbstractTyCon -> False	 -- We don't know, so return False