X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Ftypecheck%2FTcModule.lhs;h=7e63ec1f4a99684cf820fe97be7f4282a201d464;hb=01e0566e61e4222600c7ba0a2d35d6102fd1afb5;hp=850dc53fb1d0ce7e16543cb6c74aa1eb685afa6d;hpb=9bedea20f62a1da832c69833c39dd1d15e6ee9a3;p=ghc-hetmet.git diff --git a/ghc/compiler/typecheck/TcModule.lhs b/ghc/compiler/typecheck/TcModule.lhs index 850dc53..7e63ec1 100644 --- a/ghc/compiler/typecheck/TcModule.lhs +++ b/ghc/compiler/typecheck/TcModule.lhs @@ -12,28 +12,27 @@ module TcModule ( #include "HsVersions.h" import CmdLineOpts ( DynFlag(..), DynFlags, opt_PprStyle_Debug ) -import HsSyn ( HsModule(..), HsBinds(..), MonoBinds(..), HsDecl(..) ) +import HsSyn ( HsBinds(..), MonoBinds(..), HsDecl(..) ) import HsTypes ( toHsType ) -import RnHsSyn ( RenamedHsModule, RenamedHsDecl ) +import RnHsSyn ( RenamedHsDecl ) import TcHsSyn ( TypecheckedMonoBinds, TypecheckedForeignDecl, TypecheckedRuleDecl, zonkTopBinds, zonkForeignExports, zonkRules ) import TcMonad -import Inst ( emptyLIE, plusLIE ) +import Inst ( plusLIE ) import TcBinds ( tcTopBinds ) import TcClassDcl ( tcClassDecls2, mkImplicitClassBinds ) import TcDefaults ( tcDefaults ) -import TcEnv ( TcEnv, tcExtendGlobalValEnv, tcLookupGlobal_maybe, - tcEnvTyCons, tcEnvClasses, - tcSetEnv, tcSetInstEnv, initTcEnv, getTcGEnv +import TcEnv ( TcEnv, InstInfo(iDFunId), tcExtendGlobalValEnv, + tcEnvTyCons, tcEnvClasses, isLocalThing, + RecTcEnv, tcSetEnv, tcSetInstEnv, initTcEnv, getTcGEnv ) import TcRules ( tcRules ) import TcForeign ( tcForeignImports, tcForeignExports ) import TcIfaceSig ( tcInterfaceSigs ) import TcInstDcls ( tcInstDecls1, tcInstDecls2 ) -import TcInstUtil ( InstInfo(..) ) import TcSimplify ( tcSimplifyTop ) import TcTyClsDecls ( tcTyAndClassDecls ) import TcTyDecls ( mkImplicitDataBinds ) @@ -42,27 +41,21 @@ import CoreUnfold ( unfoldingTemplate ) import Type ( funResultTy, splitForAllTys ) import Bag ( isEmptyBag ) import ErrUtils ( printErrorsAndWarnings, dumpIfSet_dyn ) -import Id ( idType, idName, idUnfolding ) -import Module ( Module, moduleName, plusModuleEnv ) -import Name ( nameOccName, isLocallyDefined, isGlobalName, - toRdrName, nameEnvElts, emptyNameEnv - ) -import TyCon ( TyCon, isDataTyCon, tyConName, tyConGenInfo ) -import OccName ( isSysOcc ) -import TyCon ( TyCon, isClassTyCon ) -import Class ( Class ) -import PrelNames ( mAIN_Name, mainName ) -import UniqSupply ( UniqSupply ) -import Maybes ( maybeToBool ) +import Id ( idType, idUnfolding ) +import Module ( Module ) +import Name ( Name, isLocallyDefined, toRdrName ) +import Name ( nameEnvElts, lookupNameEnv ) +import TyCon ( tyConGenInfo ) +import Maybes ( thenMaybe ) import Util -import BasicTypes ( EP(..) ) -import Bag ( Bag, isEmptyBag ) +import BasicTypes ( EP(..), Fixity ) +import Bag ( isEmptyBag ) import Outputable -import HscTypes ( PersistentCompilerState(..), HomeSymbolTable, - PackageSymbolTable, DFunId, - TypeEnv, extendTypeEnv, - TyThing(..), groupTyThings ) -import FiniteMap ( FiniteMap, delFromFM, lookupWithDefaultFM ) +import HscTypes ( PersistentCompilerState(..), HomeSymbolTable, HomeIfaceTable, + PackageTypeEnv, DFunId, ModIface(..), + TypeEnv, extendTypeEnvList, lookupIface, + TyThing(..), mkTypeEnv ) +import List ( partition ) \end{code} Outside-world interface: @@ -73,9 +66,11 @@ data TcResults = TcResults { tc_pcs :: PersistentCompilerState, -- Augmented with imported information, -- (but not stuff from this module) - tc_env :: TypeEnv, -- The TypeEnv just for the stuff from this module - tc_insts :: [DFunId], -- Instances, just for this module - tc_binds :: TypecheckedMonoBinds, + + -- All these fields have info *just for this module* + tc_env :: TypeEnv, -- The top level TypeEnv + tc_insts :: [DFunId], -- Instances + tc_binds :: TypecheckedMonoBinds, -- Bindings tc_fords :: [TypecheckedForeignDecl], -- Foreign import & exports. tc_rules :: [TypecheckedRuleDecl] -- Transformation rules } @@ -85,65 +80,76 @@ typecheckModule :: DynFlags -> Module -> PersistentCompilerState - -> HomeSymbolTable - -> RenamedHsModule - -> IO (Maybe (TcEnv, TcResults)) - -typecheckModule dflags this_mod pcs hst (HsModule mod_name _ _ _ decls _ src_loc) - = do env <- initTcEnv global_symbol_table - (maybe_result, (errs,warns)) <- initTc dflags env src_loc tc_module - printErrorsAndWarnings (errs,warns) - printTcDump dflags maybe_result - if isEmptyBag errs then - return Nothing - else - return maybe_result + -> HomeSymbolTable -> HomeIfaceTable + -> [RenamedHsDecl] + -> IO (Maybe TcResults) + +typecheckModule dflags this_mod pcs hst hit decls + = do env <- initTcEnv hst (pcs_PTE pcs) + + (maybe_result, (warns,errs)) <- initTc dflags env tc_module + + let { maybe_tc_result :: Maybe TcResults ; + maybe_tc_result = case maybe_result of + Nothing -> Nothing + Just (_,r) -> Just r } + + printErrorsAndWarnings (errs,warns) + printTcDump dflags maybe_tc_result + + if isEmptyBag errs then + return maybe_tc_result + else + return Nothing where - global_symbol_table = pcs_PST pcs `plusModuleEnv` hst + tc_module :: TcM (RecTcEnv, TcResults) + tc_module = fixTc (\ ~(unf_env ,_) -> tcModule pcs hst get_fixity this_mod decls unf_env) - tc_module = fixTc (\ ~(unf_env ,_) -> tcModule pcs hst this_mod decls unf_env) + pit = pcs_PIT pcs + + get_fixity :: Name -> Maybe Fixity + get_fixity nm = lookupIface hit pit this_mod nm `thenMaybe` \ iface -> + lookupNameEnv (mi_fixities iface) nm \end{code} The internal monster: \begin{code} tcModule :: PersistentCompilerState -> HomeSymbolTable + -> (Name -> Maybe Fixity) -> Module -> [RenamedHsDecl] - -> TcEnv -- The knot-tied environment + -> RecTcEnv -- The knot-tied environment -> TcM (TcEnv, TcResults) - -- (unf_env :: TcEnv) is used for type-checking interface pragmas + -- (unf_env :: RecTcEnv) is used for type-checking interface pragmas -- which is done lazily [ie failure just drops the pragma -- without having any global-failure effect]. -- -- unf_env is also used to get the pragama info -- for imported dfuns and default methods -tcModule pcs hst this_mod decls unf_env +tcModule pcs hst get_fixity this_mod decls unf_env = -- Type-check the type and class decls + traceTc (text "Tc1") `thenTc_` tcTyAndClassDecls unf_env decls `thenTc` \ env -> tcSetEnv env $ let - classes = tcEnvClasses env - tycons = tcEnvTyCons env -- INCLUDES tycons derived from classes - local_classes = filter isLocallyDefined classes - local_tycons = [ tc | tc <- tycons, - isLocallyDefined tc, - not (isClassTyCon tc) - ] - -- For local_tycons, filter out the ones derived from classes - -- Otherwise the latter show up in interface files + classes = tcEnvClasses env + tycons = tcEnvTyCons env -- INCLUDES tycons derived from classes in -- Typecheck the instance decls, includes deriving - tcInstDecls1 pcs hst unf_env this_mod - local_tycons decls `thenTc` \ (pcs_with_insts, inst_env, inst_info, deriv_binds) -> + traceTc (text "Tc2") `thenTc_` + tcInstDecls1 (pcs_insts pcs) (pcs_PRS pcs) + hst unf_env get_fixity this_mod + tycons decls `thenTc` \ (new_pcs_insts, inst_env, local_inst_info, deriv_binds) -> tcSetInstEnv inst_env $ -- Default declarations - tcDefaults decls `thenTc` \ defaulting_tys -> - tcSetDefaultTys defaulting_tys $ + traceTc (text "Tc3") `thenTc_` + tcDefaults decls `thenTc` \ defaulting_tys -> + tcSetDefaultTys defaulting_tys $ -- Interface type signatures -- We tie a knot so that the Ids read out of interfaces are in scope @@ -154,16 +160,19 @@ tcModule pcs hst this_mod decls unf_env -- We must do this before mkImplicitDataBinds (which comes next), since -- the latter looks up unpackCStringId, for example, which is usually -- imported + traceTc (text "Tc3") `thenTc_` tcInterfaceSigs unf_env decls `thenTc` \ sig_ids -> + traceTc (text "Tc5") `thenTc_` ( tcExtendGlobalValEnv sig_ids $ + tcGetEnv `thenTc` \ unf_env -> -- Create any necessary record selector Ids and their bindings -- "Necessary" includes data and newtype declarations -- We don't create bindings for dictionary constructors; -- they are always fully applied, and the bindings are just there -- to support partial applications - mkImplicitDataBinds tycons `thenTc` \ (data_ids, imp_data_binds) -> - mkImplicitClassBinds classes `thenNF_Tc` \ (cls_ids, imp_cls_binds) -> + mkImplicitDataBinds this_mod tycons `thenTc` \ (data_ids, imp_data_binds) -> + mkImplicitClassBinds this_mod classes `thenNF_Tc` \ (cls_ids, imp_cls_binds) -> -- Extend the global value environment with -- (a) constructors @@ -176,22 +185,25 @@ tcModule pcs hst this_mod decls unf_env tcExtendGlobalValEnv cls_ids $ -- Foreign import declarations next + traceTc (text "Tc6") `thenTc_` tcForeignImports decls `thenTc` \ (fo_ids, foi_decls) -> tcExtendGlobalValEnv fo_ids $ -- Value declarations next. -- We also typecheck any extra binds that came out of the "deriving" process + traceTc (text "Tc7") `thenTc_` tcTopBinds (get_binds decls `ThenBinds` deriv_binds) `thenTc` \ ((val_binds, env), lie_valdecls) -> tcSetEnv env $ -- Foreign export declarations next + traceTc (text "Tc8") `thenTc_` tcForeignExports decls `thenTc` \ (lie_fodecls, foe_binds, foe_decls) -> -- Second pass over class and instance declarations, -- to compile the bindings themselves. - tcInstDecls2 inst_info `thenNF_Tc` \ (lie_instdecls, inst_binds) -> - tcClassDecls2 decls `thenNF_Tc` \ (lie_clasdecls, cls_dm_binds) -> - tcRules decls `thenNF_Tc` \ (lie_rules, rules) -> + tcInstDecls2 local_inst_info `thenNF_Tc` \ (lie_instdecls, inst_binds) -> + tcClassDecls2 this_mod decls `thenNF_Tc` \ (lie_clasdecls, cls_dm_binds) -> + tcRules (pcs_rules pcs) this_mod decls `thenNF_Tc` \ (new_pcs_rules, lie_rules, local_rules) -> -- Deal with constant or ambiguous InstIds. How could -- there be ambiguous ones? They can only arise if a @@ -208,9 +220,6 @@ tcModule pcs hst this_mod decls unf_env in tcSimplifyTop lie_alldecls `thenTc` \ const_inst_binds -> - -- Check that Main defines main - checkMain this_mod `thenTc_` - -- Backsubstitution. This must be done last. -- Even tcSimplifyTop may do some unification. let @@ -226,50 +235,38 @@ tcModule pcs hst this_mod decls unf_env tcSetEnv final_env $ -- zonkTopBinds puts all the top-level Ids into the tcGEnv zonkForeignExports foe_decls `thenNF_Tc` \ foe_decls' -> - zonkRules rules `thenNF_Tc` \ rules' -> + zonkRules local_rules `thenNF_Tc` \ local_rules' -> - let groups :: FiniteMap Module TypeEnv - groups = groupTyThings (nameEnvElts (getTcGEnv final_env)) - + let (local_things, imported_things) = partition (isLocalThing this_mod) + (nameEnvElts (getTcGEnv final_env)) + local_type_env :: TypeEnv - local_type_env = lookupWithDefaultFM groups emptyNameEnv this_mod + local_type_env = mkTypeEnv local_things - new_pst :: PackageSymbolTable - new_pst = extendTypeEnv (pcs_PST pcs) (delFromFM groups this_mod) + new_pte :: PackageTypeEnv + new_pte = extendTypeEnvList (pcs_PTE pcs) imported_things final_pcs :: PersistentCompilerState - final_pcs = pcs_with_insts {pcs_PST = new_pst} + final_pcs = pcs { pcs_PTE = new_pte, + pcs_insts = new_pcs_insts, + pcs_rules = new_pcs_rules + } in - returnTc (final_env, -- WAS: really_final_env, + returnTc (unf_env, TcResults { tc_pcs = final_pcs, tc_env = local_type_env, tc_binds = all_binds', - tc_insts = map iDFunId inst_info, + tc_insts = map iDFunId local_inst_info, tc_fords = foi_decls ++ foe_decls', - tc_rules = rules' + tc_rules = local_rules' }) + ) get_binds decls = foldr ThenBinds EmptyBinds [binds | ValD binds <- decls] \end{code} -\begin{code} -checkMain :: Module -> TcM () -checkMain this_mod - | moduleName this_mod == mAIN_Name - = tcLookupGlobal_maybe mainName `thenNF_Tc` \ maybe_main -> - case maybe_main of - Just (AnId _) -> returnTc () - other -> addErrTc noMainErr - - | otherwise = returnTc () - -noMainErr - = hsep [ptext SLIT("Module"), quotes (ppr mAIN_Name), - ptext SLIT("must include a definition for"), quotes (ptext SLIT("main"))] -\end{code} - %************************************************************************ %* * @@ -279,7 +276,7 @@ noMainErr \begin{code} printTcDump dflags Nothing = return () -printTcDump dflags (Just (_,results)) +printTcDump dflags (Just results) = do dumpIfSet_dyn dflags Opt_D_dump_types "Type signatures" (dump_sigs results) dumpIfSet_dyn dflags Opt_D_dump_tc @@ -287,8 +284,8 @@ printTcDump dflags (Just (_,results)) dump_tc results = vcat [ppr (tc_binds results), - pp_rules (tc_rules results) --, --- ppr_gen_tycons (tc_tycons results) + pp_rules (tc_rules results), + ppr_gen_tycons [tc | ATyCon tc <- nameEnvElts (tc_env results)] ] dump_sigs results -- Print type signatures @@ -304,11 +301,7 @@ dump_sigs results -- Print type signatures ppr_sig (n,t) = ppr n <+> dcolon <+> ppr t want_sig id | opt_PprStyle_Debug = True - | otherwise = isLocallyDefined n && - isGlobalName n && - not (isSysOcc (nameOccName n)) - where - n = idName id + | otherwise = isLocallyDefined id ppr_gen_tycons tcs = vcat [ptext SLIT("{-# Generic type constructor details"), vcat (map ppr_gen_tycon (filter isLocallyDefined tcs)),