Iface representation of synonym family instances
[ghc-hetmet.git] / compiler / iface / TcIface.lhs
index a90d069..c887e02 100644 (file)
@@ -8,8 +8,8 @@ Type checking of type signatures in interface files
 \begin{code}
 module TcIface ( 
        tcImportDecl, checkWiredInTyCon, tcHiBootIface, typecheckIface, 
-       tcIfaceDecl, tcIfaceInst, tcIfaceFamInst, tcIfaceRules, tcIfaceGlobal, 
-       tcExtCoreBindings
+       tcIfaceDecl, tcIfaceInst, tcIfaceFamInst, tcIfaceRules,
+       tcIfaceVectInfo, tcIfaceGlobal, tcExtCoreBindings
  ) where
 
 #include "HsVersions.h"
@@ -38,9 +38,9 @@ import DataCon
 import TysWiredIn
 import Var              ( TyVar )
 import qualified Var
+import VarEnv
 import Name
 import NameEnv
-import NameSet
 import OccName
 import Module
 import UniqFM
@@ -200,8 +200,8 @@ typecheckIface iface
        ; rules     <- tcIfaceRules ignore_prags (mi_rules iface)
 
                 -- Vectorisation information
-        ; let vect_info = VectInfo 
-                           (mkNameSet (ifaceVectInfoCCVar (mi_vect_info iface)))
+        ; vect_info <- tcIfaceVectInfo (mi_module iface) type_env 
+                                       (mi_vect_info iface)
 
                -- Exports
        ; exports <- ifaceExportNames (mi_exports iface)
@@ -383,14 +383,21 @@ tcIfaceDecl ignore_prags
 
 tcIfaceDecl ignore_prags 
            (IfaceSyn {ifName = occ_name, ifTyVars = tv_bndrs, 
-                      ifOpenSyn = isOpen, ifSynRhs = rdr_rhs_ty})
+                      ifOpenSyn = isOpen, ifSynRhs = rdr_rhs_ty,
+                      ifFamInst = mb_family})
    = bindIfaceTyVars tv_bndrs $ \ tyvars -> do
      { tc_name <- lookupIfaceTop occ_name
      ; rhs_tyki <- tcIfaceType rdr_rhs_ty
      ; let rhs = if isOpen then OpenSynTyCon rhs_tyki Nothing
                           else SynonymTyCon rhs_tyki
-     -- !!!TODO: read mb_family info from iface and pass as last argument
-     ; tycon <- buildSynTyCon tc_name tyvars rhs Nothing
+     ; famInst <- case mb_family of
+                   Nothing         -> return Nothing
+                   Just (fam, tys) -> 
+                     do { famTyCon <- tcIfaceTyCon fam
+                        ; insttys <- mapM tcIfaceType tys
+                        ; return $ Just (famTyCon, insttys)
+                        }
+     ; tycon <- buildSynTyCon tc_name tyvars rhs famInst
      ; return $ ATyCon tycon
      }
 
@@ -447,7 +454,6 @@ tcIfaceDataCons tycon_name tycon tc_tyvars if_cons
   = case if_cons of
        IfAbstractTyCon  -> return mkAbstractTyConRhs
        IfOpenDataTyCon  -> return mkOpenDataTyConRhs
-       IfOpenNewTyCon   -> return mkOpenNewTyConRhs
        IfDataTyCon cons -> do  { data_cons <- mappM tc_con_decl cons
                                ; return (mkDataTyConRhs data_cons) }
        IfNewTyCon con   -> do  { data_con <- tc_con_decl con
@@ -578,6 +584,34 @@ tcIfaceRule (IfaceRule {ifRuleName = name, ifActivation = act, ifRuleBndrs = bnd
 
 %************************************************************************
 %*                                                                     *
+               Vectorisation information
+%*                                                                     *
+%************************************************************************
+
+\begin{code}
+tcIfaceVectInfo :: Module -> TypeEnv  -> IfaceVectInfo -> IfL VectInfo
+tcIfaceVectInfo mod typeEnv (IfaceVectInfo names)
+  = do { ccVars <- mapM ccMapping names
+       ; return $ VectInfo (mkVarEnv ccVars)
+       }
+  where
+    ccMapping name 
+      = do { ccName <- lookupOrig mod (mkCloOcc (nameOccName name))
+           ; let { var   = lookup name
+                 ; ccVar = lookup ccName
+                 }
+           ; return (var, (var, ccVar))
+           }
+    lookup name = case lookupTypeEnv typeEnv name of
+                    Just (AnId var) -> var
+                    Just _          -> 
+                      panic "TcIface.tcIfaceVectInfo: wrong TyThing"
+                    Nothing         ->
+                      panic "TcIface.tcIfaceVectInfo: unknown name"
+\end{code}
+
+%************************************************************************
+%*                                                                     *
                        Types
 %*                                                                     *
 %************************************************************************
@@ -1004,7 +1038,7 @@ tcIfaceLetBndr (IfLetBndr fs ty info)
 newExtCoreBndr :: IfaceLetBndr -> IfL Id
 newExtCoreBndr (IfLetBndr var ty _)    -- Ignoring IdInfo for now
   = do { mod <- getIfModule
-       ; name <- newGlobalBinder mod (mkVarOccFS var) noSrcLoc
+       ; name <- newGlobalBinder mod (mkVarOccFS var) noSrcSpan
        ; ty' <- tcIfaceType ty
        ; return (mkLocalId name ty') }