Keep track of family instance modules
[ghc-hetmet.git] / compiler / typecheck / FamInst.lhs
index 68c4096..41f22be 100644 (file)
@@ -1,4 +1,4 @@
-\section[FamInst]{The @FamInst@ type: family instance heads}
+The @FamInst@ type: family instance heads
 
 \begin{code}
 module FamInst ( 
@@ -7,17 +7,18 @@ module FamInst (
 
 #include "HsVersions.h"
 
-import FamInstEnv ( FamInstEnv, FamInst(..), famInstTyCon, extendFamInstEnv,
-                   pprFamInst, pprFamInsts )
-import TcMType   ( tcInstSkolType )
-import TcType    ( SkolemInfo(..), tcSplitTyConApp )
-import TcRnMonad  ( TcM, TcGblEnv(..), setGblEnv, getGblEnv, foldlM,
-                   setSrcSpan, addErr )
-import TyCon      ( tyConFamInst_maybe )
-import Type      ( mkTyConApp )
-import Name      ( getSrcLoc )
-import SrcLoc    ( mkSrcSpan )
+import HscTypes
+import FamInstEnv
+import TcMType
+import TcType
+import TcRnMonad
+import TyCon
+import Type
+import Name
+import SrcLoc
 import Outputable
+
+import Monad
 \end{code}
 
 
@@ -34,7 +35,8 @@ tcExtendLocalFamInstEnv :: [FamInst] -> TcM a -> TcM a
 tcExtendLocalFamInstEnv fam_insts thing_inside
  = do { env <- getGblEnv
       ; inst_env' <- foldlM addLocalFamInst (tcg_fam_inst_env env) fam_insts
-      ; let env' = env { tcg_fam_inst_env = inst_env' }
+      ; let env' = env { tcg_fam_insts    = fam_insts ++ tcg_fam_insts env,
+                        tcg_fam_inst_env = inst_env' }
       ; setGblEnv env' thing_inside }
 
 
@@ -42,7 +44,7 @@ tcExtendLocalFamInstEnv fam_insts thing_inside
 -- and then add it to the home inst env
 addLocalFamInst :: FamInstEnv -> FamInst -> TcM FamInstEnv
 addLocalFamInst home_fie famInst
-  = do {       -- Instantiate the family instance type extend the instance
+  = do {       -- To instantiate the family instance type, extend the instance
                -- envt with completely fresh template variables
                -- This is important because the template variables must
                -- not overlap with anything in the things being looked up
@@ -53,36 +55,39 @@ addLocalFamInst home_fie famInst
              ty    = case tyConFamInst_maybe tycon of
                        Nothing        -> panic "FamInst.addLocalFamInst"
                        Just (tc, tys) -> tc `mkTyConApp` tys
-       ; (tvs', theta', tau') <- tcInstSkolType (FamInstSkol tycon) ty
+       ; (tvs', _, tau') <- tcInstSkolType (FamInstSkol tycon) ty
 
-       ; let   (fam, tys') = tcSplitTyConApp tau'
+       ; let (fam, tys') = tcSplitTyConApp tau'
 
-{- !!!TODO: Need to complete this:
                -- Load imported instances, so that we report
                -- overlaps correctly
        ; eps <- getEps
        ; let inst_envs = (eps_fam_inst_env eps, home_fie)
 
-               -- Check for overlapping instance decls
-       ; let { (matches, _) = lookupFamInstEnv inst_envs fam tys'
-             ; dup_ispecs = [ dup_ispec   --!!!adapt
-                            | (_, dup_ispec) <- matches
-                            , let (_,_,_,dup_tys) = instanceHead dup_ispec
-                            , isJust (tcMatchTys (mkVarSet tvs') tys' dup_tys)] }
-               -- Find memebers of the match list which ispec itself matches.
-               -- If the match is 2-way, it's a duplicate
-       ; case dup_ispecs of
-           dup_ispec : _ -> dupInstErr famInst dup_ispec
-           []            -> return ()
- -}
+               -- Check for conflicting instance decls
+       ; let { matches   = lookupFamInstEnvUnify inst_envs fam tys'
+             ; conflicts = [ conflictingFamInst
+                           | match@(_, conflictingFamInst) <- matches
+                           , conflicting fam tys' tycon match 
+                           ]
+              }
+       ; unless (null conflicts) $
+           conflictInstErr famInst (head conflicts)
 
                -- OK, now extend the envt
-       ; return (extendFamInstEnv home_fie famInst) }
+       ; return (extendFamInstEnv home_fie famInst) 
+        }
+  where
+    -- In the case of data/newtype instances, any overlap is a conflicts (as
+    -- these instances imply injective type mappings).
+    conflicting _   _    tycon _                 | isAlgTyCon tycon = True
+    conflicting fam tys' tycon (subst, cFamInst) | otherwise     =
+      panic "FamInst.addLocalFamInst: overlap check for indexed synonyms is still missing"
 
-overlapErr famInst dupFamInst
+conflictInstErr famInst conflictingFamInst
   = addFamInstLoc famInst $
-    addErr (hang (ptext SLIT("Overlapping family instance declarations:"))
-              2 (pprFamInsts [famInst, dupFamInst]))
+    addErr (hang (ptext SLIT("Conflicting family instance declarations:"))
+              2 (pprFamInsts [famInst, conflictingFamInst]))
 
 addFamInstLoc famInst thing_inside
   = setSrcSpan (mkSrcSpan loc loc) thing_inside