X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Frename%2FRnHsSyn.lhs;h=c26edbe33d8f9471940ddd880f73e17e698b20b7;hb=71284101f862a5fd9d9fea85497e3eb8cd7d9720;hp=7ef1cc3e39775059712d4509f434fc23a6d6a0e3;hpb=4a91d102be99778efcab80211ca5de3f2cf6619a;p=ghc-hetmet.git diff --git a/ghc/compiler/rename/RnHsSyn.lhs b/ghc/compiler/rename/RnHsSyn.lhs index 7ef1cc3..c26edbe 100644 --- a/ghc/compiler/rename/RnHsSyn.lhs +++ b/ghc/compiler/rename/RnHsSyn.lhs @@ -9,7 +9,8 @@ module RnHsSyn where #include "HsVersions.h" import HsSyn -import TysWiredIn ( tupleTyCon, listTyCon, charTyCon ) +import Class ( FunDep ) +import TysWiredIn ( tupleTyCon, listTyCon, parrTyCon, charTyCon ) import Name ( Name, getName, isTyVarName ) import NameSet import BasicTypes ( Boxity ) @@ -18,33 +19,33 @@ import Outputable \begin{code} -type RenamedArithSeqInfo = ArithSeqInfo Name RenamedPat +type RenamedHsDecl = HsDecl Name +type RenamedArithSeqInfo = ArithSeqInfo Name type RenamedClassOpSig = Sig Name type RenamedConDecl = ConDecl Name type RenamedContext = HsContext Name -type RenamedHsDecl = HsDecl Name RenamedPat -type RenamedRuleDecl = RuleDecl Name RenamedPat -type RenamedTyClDecl = TyClDecl Name RenamedPat +type RenamedRuleDecl = RuleDecl Name +type RenamedTyClDecl = TyClDecl Name type RenamedDefaultDecl = DefaultDecl Name type RenamedForeignDecl = ForeignDecl Name -type RenamedGRHS = GRHS Name RenamedPat -type RenamedGRHSs = GRHSs Name RenamedPat -type RenamedHsBinds = HsBinds Name RenamedPat -type RenamedHsExpr = HsExpr Name RenamedPat -type RenamedHsModule = HsModule Name RenamedPat -type RenamedInstDecl = InstDecl Name RenamedPat -type RenamedMatch = Match Name RenamedPat -type RenamedMonoBinds = MonoBinds Name RenamedPat +type RenamedGRHS = GRHS Name +type RenamedGRHSs = GRHSs Name +type RenamedHsBinds = HsBinds Name +type RenamedHsExpr = HsExpr Name +type RenamedInstDecl = InstDecl Name +type RenamedMatchContext = HsMatchContext Name +type RenamedMatch = Match Name +type RenamedMonoBinds = MonoBinds Name type RenamedPat = InPat Name type RenamedHsType = HsType Name type RenamedHsPred = HsPred Name -type RenamedRecordBinds = HsRecordBinds Name RenamedPat +type RenamedRecordBinds = HsRecordBinds Name type RenamedSig = Sig Name -type RenamedStmt = Stmt Name RenamedPat +type RenamedStmt = Stmt Name type RenamedFixitySig = FixitySig Name type RenamedDeprecation = DeprecDecl Name -type RenamedHsOverLit = HsOverLit Name -type RenamedIfaceSig = IfaceSig Name +type RenamedHsCmd = HsCmd Name +type RenamedHsCmdTop = HsCmdTop Name \end{code} %************************************************************************ @@ -56,9 +57,10 @@ type RenamedIfaceSig = IfaceSig Name These free-variable finders returns tycons and classes too. \begin{code} -charTyCon_name, listTyCon_name :: Name +charTyCon_name, listTyCon_name, parrTyCon_name :: Name charTyCon_name = getName charTyCon listTyCon_name = getName listTyCon +parrTyCon_name = getName parrTyCon tupleTyCon_name :: Boxity -> Int -> Name tupleTyCon_name boxity n = getName (tupleTyCon boxity n) @@ -66,27 +68,28 @@ tupleTyCon_name boxity n = getName (tupleTyCon boxity n) extractHsTyVars :: RenamedHsType -> NameSet extractHsTyVars x = filterNameSet isTyVarName (extractHsTyNames x) +extractFunDepNames :: FunDep Name -> NameSet +extractFunDepNames (ns1, ns2) = mkNameSet ns1 `unionNameSets` mkNameSet ns2 + extractHsTyNames :: RenamedHsType -> NameSet extractHsTyNames ty = get ty where get (HsAppTy ty1 ty2) = get ty1 `unionNameSets` get ty2 get (HsListTy ty) = unitNameSet listTyCon_name `unionNameSets` get ty - get (HsTupleTy (HsTupCon n _) tys) = unitNameSet n - `unionNameSets` extractHsTyNames_s tys + get (HsPArrTy ty) = unitNameSet parrTyCon_name `unionNameSets` get ty + get (HsTupleTy con tys) = extractHsTyNames_s tys get (HsFunTy ty1 ty2) = get ty1 `unionNameSets` get ty2 get (HsPredTy p) = extractHsPredTyNames p - get (HsUsgForAllTy uv ty) = get ty - get (HsUsgTy u ty) = get ty - get (HsOpTy ty1 tycon ty2) = get ty1 `unionNameSets` get ty2 `unionNameSets` - unitNameSet tycon + get (HsOpTy ty1 op ty2) = get ty1 `unionNameSets` get ty2 `unionNameSets` unitNameSet op + get (HsParTy ty) = get ty get (HsNumTy n) = emptyNameSet get (HsTyVar tv) = unitNameSet tv - get (HsForAllTy (Just tvs) + get (HsKindSig ty k) = get ty + get (HsForAllTy _ tvs ctxt ty) = (extractHsCtxtTyNames ctxt `unionNameSets` get ty) `minusNameSet` mkNameSet (hsTyVarNames tvs) - get ty@(HsForAllTy Nothing _ _) = pprPanic "extractHsTyNames" (ppr ty) extractHsTyNames_s :: [RenamedHsType] -> NameSet extractHsTyNames_s tys = foldr (unionNameSets . extractHsTyNames) emptyNameSet tys @@ -96,15 +99,53 @@ extractHsCtxtTyNames ctxt = foldr (unionNameSets . extractHsPredTyNames) emptyNa -- You don't import or export implicit parameters, -- so don't mention the IP names -extractHsPredTyNames (HsPClass cls tys) +extractHsPredTyNames (HsClassP cls tys) = unitNameSet cls `unionNameSets` extractHsTyNames_s tys -extractHsPredTyNames (HsPIParam n ty) +extractHsPredTyNames (HsIParam n ty) = extractHsTyNames ty \end{code} %************************************************************************ %* * +\subsection{Free variables of declarations} +%* * +%************************************************************************ + +Return the Names that must be in scope if we are to use this declaration. +In all cases this is set up for interface-file declarations: + - for class decls we ignore the bindings + - for instance decls likewise, plus the pragmas + - for rule decls, we ignore HsRules + - for data decls, we ignore derivings + + *** See "THE NAMING STORY" in HsDecls **** + +\begin{code} +---------------- +hsSigsFVs sigs = plusFVs (map hsSigFVs sigs) + +hsSigFVs (Sig v ty _) = extractHsTyNames ty +hsSigFVs (SpecInstSig ty _) = extractHsTyNames ty +hsSigFVs (SpecSig v ty _) = extractHsTyNames ty +hsSigFVs other = emptyFVs + +---------------- +conDeclFVs (ConDecl _ tyvars context details _) + = delFVs (map hsTyVarName tyvars) $ + extractHsCtxtTyNames context `plusFV` + conDetailsFVs details + +conDetailsFVs (PrefixCon btys) = plusFVs (map bangTyFVs btys) +conDetailsFVs (InfixCon bty1 bty2) = bangTyFVs bty1 `plusFV` bangTyFVs bty2 +conDetailsFVs (RecCon flds) = plusFVs [bangTyFVs bty | (_, bty) <- flds] + +bangTyFVs bty = extractHsTyNames (getBangType bty) +\end{code} + + +%************************************************************************ +%* * \subsection{A few functions on generic defintions %* * %************************************************************************ @@ -117,8 +158,8 @@ maybeGenericMatch :: RenamedMatch -> Maybe (RenamedHsType, RenamedMatch) -- Tells whether a Match is for a generic definition -- and extract the type from a generic match and put it at the front -maybeGenericMatch (Match tvs (TypePatIn ty : pats) sig_ty grhss) - = Just (ty, Match tvs pats sig_ty grhss) +maybeGenericMatch (Match (TypePat ty : pats) sig_ty grhss) + = Just (ty, Match pats sig_ty grhss) maybeGenericMatch other_match = Nothing \end{code}