X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fiface%2FTcIface.lhs;h=6f76ae116ea23197e32ec271857abf6e635f9fc8;hb=56acf24c6792ad5d6c0671b3ac534d685a4d37ca;hp=b6f1f484f24d13d3826061146086eed71edb3bcd;hpb=ec81fddea750b1ad21f63b7c4307c15f89f10dfd;p=ghc-hetmet.git diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index b6f1f48..6f76ae1 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -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,6 +38,7 @@ import DataCon import TysWiredIn import Var ( TyVar ) import qualified Var +import VarEnv import Name import NameEnv import OccName @@ -48,9 +49,7 @@ import Outputable import ErrUtils import Maybes import SrcLoc -import Util import DynFlags -import Breakpoints import Control.Monad import Data.List @@ -200,6 +199,10 @@ typecheckIface iface ; fam_insts <- mapM tcIfaceFamInst (mi_fam_insts iface) ; rules <- tcIfaceRules ignore_prags (mi_rules iface) + -- Vectorisation information + ; vect_info <- tcIfaceVectInfo (mi_module iface) type_env + (mi_vect_info iface) + -- Exports ; exports <- ifaceExportNames (mi_exports iface) @@ -210,8 +213,9 @@ typecheckIface iface , md_insts = insts , md_fam_insts = fam_insts , md_rules = rules + , md_vect_info = vect_info , md_exports = exports - , md_dbg_sites = noDbgSites + , md_modBreaks = emptyModBreaks } } \end{code} @@ -385,7 +389,9 @@ tcIfaceDecl ignore_prags ; rhs_tyki <- tcIfaceType rdr_rhs_ty ; let rhs = if isOpen then OpenSynTyCon rhs_tyki Nothing else SynonymTyCon rhs_tyki - ; return (ATyCon (buildSynTyCon tc_name tyvars rhs)) + -- !!!TODO: read mb_family info from iface and pass as last argument + ; tycon <- buildSynTyCon tc_name tyvars rhs Nothing + ; return $ ATyCon tycon } tcIfaceDecl ignore_prags @@ -572,6 +578,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 %* * %************************************************************************ @@ -668,16 +702,17 @@ tcIfaceExpr (IfaceCase scrut case_bndr ty alts) returnM (Case scrut' case_bndr' ty' alts') tcIfaceExpr (IfaceLet (IfaceNonRec bndr rhs) body) - = tcIfaceExpr rhs `thenM` \ rhs' -> - bindIfaceId bndr $ \ bndr' -> - tcIfaceExpr body `thenM` \ body' -> - returnM (Let (NonRec bndr' rhs') body') + = do { rhs' <- tcIfaceExpr rhs + ; id <- tcIfaceLetBndr bndr + ; body' <- extendIfaceIdEnv [id] (tcIfaceExpr body) + ; return (Let (NonRec id rhs') body') } tcIfaceExpr (IfaceLet (IfaceRec pairs) body) - = bindIfaceIds bndrs $ \ bndrs' -> - mappM tcIfaceExpr rhss `thenM` \ rhss' -> - tcIfaceExpr body `thenM` \ body' -> - returnM (Let (Rec (bndrs' `zip` rhss')) body') + = do { ids <- mapM tcIfaceLetBndr bndrs + ; extendIfaceIdEnv ids $ do + { rhss' <- mapM tcIfaceExpr rhss + ; body' <- tcIfaceExpr body + ; return (Let (Rec (ids `zip` rhss')) body') } } where (bndrs, rhss) = unzip pairs @@ -962,8 +997,11 @@ tcIfaceExtId name = do { thing <- tcIfaceGlobal name \begin{code} bindIfaceBndr :: IfaceBndr -> (CoreBndr -> IfL a) -> IfL a -bindIfaceBndr (IfaceIdBndr bndr) thing_inside - = bindIfaceId bndr thing_inside +bindIfaceBndr (IfaceIdBndr (fs, ty)) thing_inside + = do { name <- newIfaceName (mkVarOccFS fs) + ; ty' <- tcIfaceType ty + ; let id = mkLocalId name ty' + ; extendIfaceIdEnv [id] (thing_inside id) } bindIfaceBndr (IfaceTvBndr bndr) thing_inside = bindIfaceTyVar bndr thing_inside @@ -975,26 +1013,24 @@ bindIfaceBndrs (b:bs) thing_inside thing_inside (b':bs') ----------------------- -bindIfaceId :: IfaceIdBndr -> (Id -> IfL a) -> IfL a -bindIfaceId (occ, ty) thing_inside - = do { name <- newIfaceName (mkVarOccFS occ) +tcIfaceLetBndr (IfLetBndr fs ty info) + = do { name <- newIfaceName (mkVarOccFS fs) ; ty' <- tcIfaceType ty - ; let { id = mkLocalId name ty' } - ; extendIfaceIdEnv [id] (thing_inside id) } - -bindIfaceIds :: [IfaceIdBndr] -> ([Id] -> IfL a) -> IfL a -bindIfaceIds bndrs thing_inside - = do { names <- newIfaceNames (map mkVarOccFS occs) - ; tys' <- mappM tcIfaceType tys - ; let { ids = zipWithEqual "tcCoreValBndr" mkLocalId names tys' } - ; extendIfaceIdEnv ids (thing_inside ids) } + ; case info of + NoInfo -> return (mkLocalId name ty') + HasInfo i -> return (mkLocalIdWithInfo name ty' (tc_info i)) } where - (occs,tys) = unzip bndrs - + -- Similar to tcIdInfo, but much simpler + tc_info [] = vanillaIdInfo + tc_info (HsInline p : i) = tc_info i `setInlinePragInfo` p + tc_info (HsArity a : i) = tc_info i `setArityInfo` a + tc_info (HsStrictness s : i) = tc_info i `setAllStrictnessInfo` Just s + tc_info (other : i) = pprTrace "tcIfaceLetBndr: discarding unexpected IdInfo" + (ppr other) (tc_info i) ----------------------- -newExtCoreBndr :: IfaceIdBndr -> IfL Id -newExtCoreBndr (var, ty) +newExtCoreBndr :: IfaceLetBndr -> IfL Id +newExtCoreBndr (IfLetBndr var ty _) -- Ignoring IdInfo for now = do { mod <- getIfModule ; name <- newGlobalBinder mod (mkVarOccFS var) noSrcLoc ; ty' <- tcIfaceType ty