X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Ftypecheck%2FTcModule.lhs;h=28a6bd48cd1d012e415828c7e5664c72f9475c62;hb=06619533d2e402ec10eaec3752c76d310565d0fc;hp=18556729220ca63af7a8b4c554652360594f8c5b;hpb=9dd6e1c216993624a2cd74b62ca0f0569c02c26b;p=ghc-hetmet.git diff --git a/ghc/compiler/typecheck/TcModule.lhs b/ghc/compiler/typecheck/TcModule.lhs index 1855672..28a6bd4 100644 --- a/ghc/compiler/typecheck/TcModule.lhs +++ b/ghc/compiler/typecheck/TcModule.lhs @@ -1,124 +1,137 @@ % -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996 +% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % \section[TcModule]{Typechecking a whole module} \begin{code} module TcModule ( typecheckModule, - TcResults, - TcDDumpDeriv + TcResults(..) ) where #include "HsVersions.h" -import CmdLineOpts ( opt_D_dump_tc, opt_D_dump_deriv ) +import CmdLineOpts ( opt_D_dump_tc ) import HsSyn ( HsModule(..), HsBinds(..), MonoBinds(..), HsDecl(..) ) -import RnHsSyn ( RenamedHsModule, RenamedFixityDecl(..) ) -import TcHsSyn ( TypecheckedHsBinds, TypecheckedHsExpr, - TypecheckedDictBinds, TcMonoBinds, - TypecheckedMonoBinds, - zonkTopBinds ) +import RnHsSyn ( RenamedHsModule ) +import TcHsSyn ( TcMonoBinds, TypecheckedMonoBinds, + TypecheckedForeignDecl, TypecheckedRuleDecl, + zonkTopBinds, zonkForeignExports, zonkRules + ) import TcMonad import Inst ( Inst, emptyLIE, plusLIE ) import TcBinds ( tcTopBindsAndThen ) import TcClassDcl ( tcClassDecls2 ) import TcDefaults ( tcDefaults ) -import TcEnv ( TcIdOcc(..), tcExtendGlobalValEnv, tcExtendTyConEnv, getEnv_LocalIds, - getEnv_TyCons, getEnv_Classes, tcLookupLocalValue, - tcLookupLocalValueByKey, tcLookupTyCon, - tcLookupGlobalValueByKeyMaybe ) +import TcEnv ( tcExtendGlobalValEnv, tcExtendTypeEnv, + getEnvTyCons, getEnvClasses, tcLookupValueMaybe, + explicitLookupValueByKey, tcSetValueEnv, + tcLookupTyCon, initEnv, + ValueEnv, TcTyThing(..) + ) import TcExpr ( tcId ) +import TcRules ( tcRules ) +import TcForeign ( tcForeignImports, tcForeignExports ) import TcIfaceSig ( tcInterfaceSigs ) import TcInstDcls ( tcInstDecls1, tcInstDecls2 ) import TcInstUtil ( buildInstanceEnvs, classDataCon, InstInfo ) import TcSimplify ( tcSimplifyTop ) -import TcTyClsDecls ( tcTyAndClassDecls1 ) +import TcTyClsDecls ( tcTyAndClassDecls ) import TcTyDecls ( mkDataBinds ) -import TcType ( TcType, tcInstType ) -import TcKind ( TcKind, kindToTcKind ) +import TcType ( TcType, typeToTcType, + TcKind, kindToTcKind, + newTyVarTy + ) -import RnMonad ( RnNameSupply(..) ) +import RnMonad ( RnNameSupply, getIfaceFixities, Fixities, InterfaceDetails ) import Bag ( isEmptyBag ) -import ErrUtils ( WarnMsg, ErrMsg, - pprBagOfErrors, dumpIfSet, ghcExit - ) -import Id ( idType, GenId, IdEnv, nullIdEnv ) -import Maybes ( catMaybes, MaybeErr(..) ) -import Name ( Name, isLocallyDefined, pprModule, NamedThing(..) ) -import TyCon ( TyCon, isSynTyCon, tyConKind ) +import ErrUtils ( Message, printErrorsAndWarnings, dumpIfSet ) +import Id ( Id, idType ) +import Module ( pprModuleName ) +import Name ( Name, nameUnique, isLocallyDefined, NamedThing(..) ) +import TyCon ( TyCon, tyConKind ) +import DataCon ( dataConId ) import Class ( Class, classSelIds, classTyCon ) -import Type ( mkTyConApp, mkSynTy, Type ) -import TyVar ( emptyTyVarEnv ) +import Type ( mkTyConApp, mkForAllTy, + boxedTypeKind, getTyVar, Type ) import TysWiredIn ( unitTy ) -import PrelMods ( gHC_MAIN, mAIN ) -import PrelInfo ( main_NAME, ioTyCon_NAME ) -import Unify ( unifyTauTy ) -import UniqFM ( lookupUFM_Directly, lookupWithDefaultUFM_Directly, - filterUFM, eltsUFM ) +import PrelMods ( mAIN_Name ) +import PrelInfo ( main_NAME, thinAirIdNames, setThinAirIds ) +import TcUnify ( unifyTauTy ) import Unique ( Unique ) import UniqSupply ( UniqSupply ) +import Maybes ( maybeToBool ) import Util import Bag ( Bag, isEmptyBag ) -import FiniteMap ( emptyFM, FiniteMap ) import Outputable + +import IOExts \end{code} Outside-world interface: \begin{code} -- Convenient type synonyms first: -type TcResults - = (TypecheckedMonoBinds, - [TyCon], [Class], - Bag InstInfo, -- Instance declaration information - TcDDumpDeriv) - -type TcDDumpDeriv = SDoc +data TcResults + = TcResults { + tc_binds :: TypecheckedMonoBinds, + tc_tycons :: [TyCon], + tc_classes :: [Class], + tc_insts :: Bag InstInfo, -- Instance declaration information + tc_fords :: [TypecheckedForeignDecl], -- Foreign import & exports. + tc_rules :: [TypecheckedRuleDecl], -- Transformation rules + tc_env :: ValueEnv, + tc_thinair :: [Id] -- The thin-air Ids + } --------------- typecheckModule :: UniqSupply -> RnNameSupply + -> InterfaceDetails -> RenamedHsModule -> IO (Maybe TcResults) -typecheckModule us rn_name_supply mod - = let - (maybe_result, warns, errs) = initTc us (tcModule rn_name_supply mod) - in - print_errs warns >> - print_errs errs >> +typecheckModule us rn_name_supply iface_det mod + = initTc us initEnv (tcModule rn_name_supply (getIfaceFixities iface_det) mod) + >>= \ (maybe_result, warns, errs) -> + + printErrorsAndWarnings errs warns >> - dumpIfSet opt_D_dump_tc "Typechecked" - (case maybe_result of - Just (binds, _, _, _, _) -> ppr binds - Nothing -> text "Typecheck failed") >> + -- write the thin-air Id map + (case maybe_result of + Just results -> setThinAirIds (tc_thinair results) + Nothing -> return () + ) >> - dumpIfSet opt_D_dump_deriv "Derived instances" + dumpIfSet opt_D_dump_tc "Typechecked" (case maybe_result of - Just (_, _, _, _, dump_deriv) -> dump_deriv - Nothing -> empty) >> + Just results -> ppr (tc_binds results) + $$ + pp_rules (tc_rules results) + Nothing -> text "Typecheck failed") >> return (if isEmptyBag errs then maybe_result else Nothing) -print_errs errs - | isEmptyBag errs = return () - | otherwise = printErrs (pprBagOfErrors errs) +pp_rules [] = empty +pp_rules rs = vcat [ptext SLIT("{-# RULES"), + nest 4 (vcat (map ppr rs)), + ptext SLIT("#-}")] \end{code} The internal monster: \begin{code} tcModule :: RnNameSupply -- for renaming derivings + -> Fixities -- needed for Show/Read derivings. -> RenamedHsModule -- input -> TcM s TcResults -- output -tcModule rn_name_supply - (HsModule mod_name verion exports imports fixities decls src_loc) +tcModule rn_name_supply fixities + (HsModule mod_name verion exports imports decls _ src_loc) = tcAddSrcLoc src_loc $ -- record where we're starting fixTc (\ ~(unf_env ,_) -> @@ -126,33 +139,29 @@ tcModule rn_name_supply -- which is done lazily [ie failure just drops the pragma -- without having any global-failure effect]. -- - -- unf_env is also used to get the pragam info for dfuns. + -- unf_env is also used to get the pragam info + -- for imported dfuns and default methods -- The knot for instance information. This isn't used at all -- till we type-check value declarations - fixTc ( \ ~(rec_inst_mapper, _, _, _, _) -> + fixTc ( \ ~(rec_inst_mapper, _, _, _) -> -- Type-check the type and class decls - -- trace "tcTyAndClassDecls:" $ - tcTyAndClassDecls1 unf_env rec_inst_mapper decls `thenTc` \ env -> + tcTyAndClassDecls unf_env rec_inst_mapper decls `thenTc` \ env -> - -- trace "tc3" $ -- Typecheck the instance decls, includes deriving tcSetEnv env ( - -- trace "tcInstDecls:" $ - tcInstDecls1 unf_env decls mod_name rn_name_supply - ) `thenTc` \ (inst_info, deriv_binds, ddump_deriv) -> + tcInstDecls1 unf_env decls mod_name fixities rn_name_supply + ) `thenTc` \ (inst_info, deriv_binds) -> - -- trace "tc4" $ buildInstanceEnvs inst_info `thenNF_Tc` \ inst_mapper -> - returnTc (inst_mapper, env, inst_info, deriv_binds, ddump_deriv) + returnTc (inst_mapper, env, inst_info, deriv_binds) -- End of inner fix loop - ) `thenTc` \ (_, env, inst_info, deriv_binds, ddump_deriv) -> + ) `thenTc` \ (_, env, inst_info, deriv_binds) -> - -- trace "tc5" $ - tcSetEnv env $ + tcSetEnv env ( -- Default declarations tcDefaults decls `thenTc` \ defaulting_tys -> @@ -160,9 +169,12 @@ tcModule rn_name_supply -- 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 let - tycons = getEnv_TyCons env - classes = getEnv_Classes env + tycons = getEnvTyCons env + classes = getEnvClasses env local_tycons = filter isLocallyDefined tycons local_classes = filter isLocallyDefined classes in @@ -172,7 +184,9 @@ tcModule rn_name_supply -- (a) constructors -- (b) record selectors -- (c) class op selectors - -- (d) default-method ids + -- (d) default-method ids... where? I can't see where these are + -- put into the envt, and I'm worried that the zonking phase + -- will find they aren't there and complain. tcExtendGlobalValEnv data_ids $ tcExtendGlobalValEnv (concat (map classSelIds classes)) $ @@ -180,11 +194,11 @@ tcModule rn_name_supply -- the classes, and the global value environment with the -- corresponding data cons. -- They are mentioned in types in interface files. - tcExtendGlobalValEnv (map classDataCon classes) $ - tcExtendTyConEnv [ (getName tycon, (kindToTcKind (tyConKind tycon), Nothing, tycon)) - | clas <- classes, - let tycon = classTyCon clas - ] $ + tcExtendGlobalValEnv (map (dataConId . classDataCon) classes) $ + tcExtendTypeEnv [ (getName tycon, (kindToTcKind (tyConKind tycon), Nothing, ATyCon tycon)) + | clas <- classes, + let tycon = classTyCon clas + ] $ -- Interface type signatures -- We tie a knot so that the Ids read out of interfaces are in scope @@ -195,56 +209,86 @@ tcModule rn_name_supply tcInterfaceSigs unf_env decls `thenTc` \ sig_ids -> tcExtendGlobalValEnv sig_ids $ + -- foreign import declarations next. + 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 - -- trace "tcBinds:" $ tcTopBindsAndThen (\ is_rec binds1 (binds2, thing) -> (binds1 `AndMonoBinds` binds2, thing)) (get_val_decls decls `ThenBinds` deriv_binds) - ( tcGetEnv `thenNF_Tc` \ env -> + ( tcGetEnv `thenNF_Tc` \ env -> + tcGetUnique `thenNF_Tc` \ uniq -> returnTc ((EmptyMonoBinds, env), emptyLIE) ) `thenTc` \ ((val_binds, final_env), lie_valdecls) -> tcSetEnv final_env $ + -- foreign export declarations next. + tcForeignExports decls `thenTc` \ (lie_fodecls, foe_binds, foe_decls) -> -- Second pass over class and instance declarations, -- to compile the bindings themselves. - -- trace "tc8" $ tcInstDecls2 inst_info `thenNF_Tc` \ (lie_instdecls, inst_binds) -> tcClassDecls2 decls `thenNF_Tc` \ (lie_clasdecls, cls_binds) -> + tcRules decls `thenNF_Tc` \ (lie_rules, rules) -> - - -- Check that "main" has the right signature - tcCheckMainSig mod_name `thenTc_` - -- Deal with constant or ambiguous InstIds. How could -- there be ambiguous ones? They can only arise if a -- top-level decl falls under the monomorphism -- restriction, and no subsequent decl instantiates its -- type. (Usually, ambiguous type variables are resolved -- during the generalisation step.) - -- trace "tc9" $ let - lie_alldecls = lie_valdecls `plusLIE` lie_instdecls `plusLIE` lie_clasdecls + lie_alldecls = lie_valdecls `plusLIE` + lie_instdecls `plusLIE` + lie_clasdecls `plusLIE` + lie_fodecls `plusLIE` + lie_rules in tcSimplifyTop lie_alldecls `thenTc` \ const_inst_binds -> + -- Check that Main defines main + (if mod_name == mAIN_Name then + tcLookupValueMaybe main_NAME `thenNF_Tc` \ maybe_main -> + checkTc (maybeToBool maybe_main) noMainErr + else + returnTc () + ) `thenTc_` -- Backsubstitution. This must be done last. - -- Even tcCheckMainSig and tcSimplifyTop may do some unification. + -- Even tcSimplifyTop may do some unification. let all_binds = data_binds `AndMonoBinds` val_binds `AndMonoBinds` inst_binds `AndMonoBinds` cls_binds `AndMonoBinds` - const_inst_binds + const_inst_binds `AndMonoBinds` + foe_binds in - zonkTopBinds all_binds `thenNF_Tc` \ (all_binds', really_final_env) -> + zonkTopBinds all_binds `thenNF_Tc` \ (all_binds', really_final_env) -> + tcSetValueEnv really_final_env $ + zonkForeignExports foe_decls `thenNF_Tc` \ foe_decls' -> + zonkRules rules `thenNF_Tc` \ rules' -> + let + thin_air_ids = map (explicitLookupValueByKey really_final_env . nameUnique) thinAirIdNames + -- When looking up the thin-air names we must use + -- a global env that includes the zonked locally-defined Ids too + -- Hence using really_final_env + in returnTc (really_final_env, - (all_binds', local_tycons, local_classes, inst_info, ddump_deriv)) + (TcResults { tc_binds = all_binds', + tc_tycons = local_tycons, + tc_classes = local_classes, + tc_insts = inst_info, + tc_fords = foi_decls ++ foe_decls', + tc_rules = rules', + tc_env = really_final_env, + tc_thinair = thin_air_ids + })) + ) -- End of outer fix loop ) `thenTc` \ (final_env, stuff) -> @@ -255,43 +299,8 @@ get_val_decls decls = foldr ThenBinds EmptyBinds [binds | ValD binds <- decls] \begin{code} -tcCheckMainSig mod_name - | mod_name /= mAIN - = returnTc () -- A non-main module - - | otherwise - = -- Check that main is defined - tcLookupTyCon ioTyCon_NAME `thenTc` \ (_,_,ioTyCon) -> - tcLookupLocalValue main_NAME `thenNF_Tc` \ maybe_main_id -> - case maybe_main_id of { - Nothing -> failWithTc noMainErr ; - Just main_id -> - - -- Check that it has the right type (or a more general one) - let - expected_ty = mkTyConApp ioTyCon [unitTy] - in - tcInstType emptyTyVarEnv expected_ty `thenNF_Tc` \ expected_tau -> - tcId main_NAME `thenNF_Tc` \ (_, lie, main_tau) -> - tcSetErrCtxt mainTyCheckCtxt $ - unifyTauTy expected_tau - main_tau `thenTc_` - checkTc (isEmptyBag lie) (mainTyMisMatch expected_ty (idType main_id)) - } - - -mainTyCheckCtxt - = hsep [ptext SLIT("When checking that"), ppr main_NAME, ptext SLIT("has the required type")] - noMainErr - = hsep [ptext SLIT("Module"), quotes (pprModule mAIN), + = hsep [ptext SLIT("Module"), quotes (pprModuleName mAIN_Name), ptext SLIT("must include a definition for"), quotes (ppr main_NAME)] - -mainTyMisMatch :: Type -> TcType s -> ErrMsg -mainTyMisMatch expected actual - = hang (hsep [ppr main_NAME, ptext SLIT("has the wrong type")]) - 4 (vcat [ - hsep [ptext SLIT("Expected:"), ppr expected], - hsep [ptext SLIT("Inferred:"), ppr actual] - ]) \end{code} +