X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Frename%2FRnBinds.lhs;h=aefb9ec051c451187747dfc3eacb462b169e0ad9;hb=111cee3f1ad93816cb828e38b38521d85c3bcebb;hp=b6f6d2cc2f2918a50655249e119438838780a190;hpb=0d8269cc016f7063365a9d335c6108703d3d1286;p=ghc-hetmet.git diff --git a/ghc/compiler/rename/RnBinds.lhs b/ghc/compiler/rename/RnBinds.lhs index b6f6d2c..aefb9ec 100644 --- a/ghc/compiler/rename/RnBinds.lhs +++ b/ghc/compiler/rename/RnBinds.lhs @@ -153,7 +153,7 @@ it expects the global environment to contain bindings for the binders %************************************************************************ %* * -%* Top-level bindings +\subsubsection{ Top-level bindings} %* * %************************************************************************ @@ -178,8 +178,8 @@ rnTopMonoBinds mbinds sigs binder_occ_fm = listToFM [(nameOccName x,x) | x <- binder_names] in renameSigs opt_WarnMissingSigs binder_set - (lookupSigOccRn binder_occ_fm) sigs `thenRn` \ (siglist, sig_fvs) -> - rn_mono_binds siglist mbinds `thenRn` \ (final_binds, bind_fvs) -> + (lookupSigOccRn binder_occ_fm) sigs `thenRn` \ (siglist, sig_fvs) -> + rn_mono_binds siglist mbinds `thenRn` \ (final_binds, bind_fvs) -> returnRn (final_binds, bind_fvs `plusFV` sig_fvs) where binder_rdr_names = map fst (bagToList (collectMonoBinders mbinds)) @@ -199,12 +199,16 @@ lookupSigOccRn binder_occ_fm rdr_name %* * %************************************************************************ -@rnMonoBinds@ - - collects up the binders for this declaration group, - - checks that they form a set - - extends the environment to bind them to new local names - - calls @rnMonoBinds@ to do the real work +\subsubsection{Nested binds} +@rnMonoBinds@ +\begin{itemize} +\item collects up the binders for this declaration group, +\item checks that they form a set +\item extends the environment to bind them to new local names +\item calls @rnMonoBinds@ to do the real work +\end{itemize} +% \begin{code} rnBinds :: RdrNameHsBinds -> (RenamedHsBinds -> RnMS (result, FreeVars)) @@ -226,9 +230,11 @@ rnMonoBinds mbinds sigs thing_inside -- Non-empty monobinds = -- Extract all the binders in this group, -- and extend current scope, inventing new names for the new binders -- This also checks that the names form a set - bindLocatedLocalsRn (text "a binding group") mbinders_w_srclocs $ \ new_mbinders -> + bindLocatedLocalsRn (text "a binding group") mbinders_w_srclocs + $ \ new_mbinders -> let - binder_set = mkNameSet new_mbinders + binder_set = mkNameSet new_mbinders + binder_occ_fm = listToFM [(nameOccName x,x) | x <- new_mbinders] -- Weed out the fixity declarations that do not -- apply to any of the binders in this group. @@ -237,26 +243,25 @@ rnMonoBinds mbinds sigs thing_inside -- Non-empty monobinds forLocalBind (FixSig sig@(FixitySig name _ _ )) = isJust (lookupFM binder_occ_fm (rdrNameOcc name)) forLocalBind _ = True - - binder_occ_fm = listToFM [(nameOccName x,x) | x <- new_mbinders] - in - -- Report the fixity declarations in this group that - -- don't refer to any of the group's binders. - -- - mapRn_ (unknownSigErr) fixes_not_for_me `thenRn_` + -- Rename the signatures renameSigs False binder_set (lookupSigOccRn binder_occ_fm) sigs_for_me `thenRn` \ (siglist, sig_fvs) -> + + -- Report the fixity declarations in this group that + -- don't refer to any of the group's binders. + -- Then install the fixity declarations that do apply here + -- Notice that they scope over thing_inside too + mapRn_ (unknownSigErr) fixes_not_for_me `thenRn_` let fixity_sigs = [(name,sig) | FixSig sig@(FixitySig name _ _) <- siglist ] in - -- Install the fixity declarations that do apply here and go. - extendFixityEnv fixity_sigs ( - rn_mono_binds siglist mbinds - ) `thenRn` \ (binds, bind_fvs) -> + extendFixityEnv fixity_sigs $ - -- Now do the "thing inside", and deal with the free-variable calculations - thing_inside binds `thenRn` \ (result,result_fvs) -> + rn_mono_binds siglist mbinds `thenRn` \ (binds, bind_fvs) -> + + -- Now do the "thing inside", and deal with the free-variable calculations + thing_inside binds `thenRn` \ (result,result_fvs) -> let all_fvs = result_fvs `plusFV` bind_fvs `plusFV` sig_fvs unused_binders = nameSetToList (binder_set `minusNameSet` all_fvs) @@ -270,14 +275,14 @@ rnMonoBinds mbinds sigs thing_inside -- Non-empty monobinds %************************************************************************ %* * -%* MonoBinds -- the main work is done here +\subsubsection{ MonoBinds -- the main work is done here} %* * %************************************************************************ -@rn_mono_binds@ is used by *both* top-level and nested bindings. It -assumes that all variables bound in this group are already in scope. -This is done *either* by pass 3 (for the top-level bindings), *or* by -@rnMonoBinds@ (for the nested ones). +@rn_mono_binds@ is used by {\em both} top-level and nested bindings. +It assumes that all variables bound in this group are already in scope. +This is done {\em either} by pass 3 (for the top-level bindings), +{\em or} by @rnMonoBinds@ (for the nested ones). \begin{code} rn_mono_binds :: [RenamedSig] -- Signatures attached to this group @@ -307,8 +312,8 @@ rn_mono_binds siglist mbinds @flattenMonoBinds@ is ever-so-slightly magical in that it sticks unique ``vertex tags'' on its output; minor plumbing required. -Sigh - need to pass along the signatures for the group of bindings, -in case any of them +Sigh --- need to pass along the signatures for the group of bindings, +in case any of them \fbox{\ ???\ } \begin{code} flattenMonoBinds :: [RenamedSig] -- Signatures @@ -357,7 +362,19 @@ flattenMonoBinds sigs (FunMonoBind name inf matches locn) @rnMethodBinds@ is used for the method bindings of a class and an instance -declaration. like @rnMonoBinds@ but without dependency analysis. +declaration. Like @rnMonoBinds@ but without dependency analysis. + +NOTA BENE: we record each {\em binder} of a method-bind group as a free variable. +That's crucial when dealing with an instance decl: +\begin{verbatim} + instance Foo (T a) where + op x = ... +\end{verbatim} +This might be the {\em sole} occurrence of @op@ for an imported class @Foo@, +and unless @op@ occurs we won't treat the type signature of @op@ in the class +decl for @Foo@ as a source of instance-decl gates. But we should! Indeed, +in many ways the @op@ in an instance decl is just like an occurrence, not +a binder. \begin{code} rnMethodBinds :: RdrNameMonoBinds -> RnMS (RenamedMonoBinds, FreeVars) @@ -377,13 +394,13 @@ rnMethodBinds (FunMonoBind name inf matches locn) mapFvRn rnMatch matches `thenRn` \ (new_matches, fvs) -> mapRn_ (checkPrecMatch inf sel_name) new_matches `thenRn_` - returnRn (FunMonoBind sel_name inf new_matches locn, fvs) + returnRn (FunMonoBind sel_name inf new_matches locn, fvs `addOneFV` sel_name) rnMethodBinds (PatMonoBind (VarPatIn name) grhss locn) = pushSrcLocRn locn $ lookupGlobalOccRn name `thenRn` \ sel_name -> rnGRHSs grhss `thenRn` \ (grhss', fvs) -> - returnRn (PatMonoBind (VarPatIn sel_name) grhss' locn, fvs) + returnRn (PatMonoBind (VarPatIn sel_name) grhss' locn, fvs `addOneFV` sel_name) -- Can't handle method pattern-bindings which bind multiple methods. rnMethodBinds mbind@(PatMonoBind other_pat _ locn) @@ -417,7 +434,7 @@ reconstructCycle (CyclicSCC cycle) %************************************************************************ %* * -%* Manipulating FlatMonoBindInfo * +\subsubsection{ Manipulating FlatMonoBindInfo} %* * %************************************************************************ @@ -455,19 +472,22 @@ mkEdges flat_info %* * %************************************************************************ -@renameSigs@ checks for: (a)~more than one sig for one thing; -(b)~signatures given for things not bound here; (c)~with suitably -flaggery, that all top-level things have type signatures. - +@renameSigs@ checks for: +\begin{enumerate} +\item more than one sig for one thing; +\item signatures given for things not bound here; +\item with suitably flaggery, that all top-level things have type signatures. +\end{enumerate} +% At the moment we don't gather free-var info from the types in signatures. We'd only need this if we wanted to report unused tyvars. \begin{code} -renameSigs :: Bool -- True => warn if (required) type signatures are missing. - -> NameSet -- Set of names bound in this group +renameSigs :: Bool -- True => warn if (required) type signatures are missing. + -> NameSet -- Set of names bound in this group -> (RdrName -> RnMS Name) -> [RdrNameSig] - -> RnMS ([RenamedSig], FreeVars) -- List of Sig constructors + -> RnMS ([RenamedSig], FreeVars) -- List of Sig constructors renameSigs sigs_required binders lookup_occ_nm sigs = -- Rename the signatures @@ -499,6 +519,8 @@ renameSigs sigs_required binders lookup_occ_nm sigs -- is in scope. (I'm assuming that Baz.op isn't in scope unqualified.) -- Doesn't seem worth much trouble to sort this. +renameSig :: (RdrName -> RnMS Name) -> Sig RdrName -> RnMS (Sig Name, FreeVars) + renameSig lookup_occ_nm (Sig v ty src_loc) = pushSrcLocRn src_loc $ lookup_occ_nm v `thenRn` \ new_v -> @@ -507,7 +529,7 @@ renameSig lookup_occ_nm (Sig v ty src_loc) renameSig _ (SpecInstSig ty src_loc) = pushSrcLocRn src_loc $ - rnHsSigType (text "A SPECIALISE instance pragma") ty `thenRn` \ (new_ty, fvs) -> + rnHsSigType (text "A SPECIALISE instance pragma") ty `thenRn` \ (new_ty, fvs) -> returnRn (SpecInstSig new_ty src_loc, fvs) renameSig lookup_occ_nm (SpecSig v ty src_loc) @@ -516,29 +538,60 @@ renameSig lookup_occ_nm (SpecSig v ty src_loc) rnHsSigType (quotes (ppr v)) ty `thenRn` \ (new_ty,fvs) -> returnRn (SpecSig new_v new_ty src_loc, fvs `addOneFV` new_v) -renameSig lookup_occ_nm (InlineSig v src_loc) +renameSig lookup_occ_nm (FixSig (FixitySig v fix src_loc)) = pushSrcLocRn src_loc $ lookup_occ_nm v `thenRn` \ new_v -> - returnRn (InlineSig new_v src_loc, unitFV new_v) + returnRn (FixSig (FixitySig new_v fix src_loc), unitFV new_v) -renameSig lookup_occ_nm (FixSig (FixitySig v fix src_loc)) +renameSig lookup_occ_nm (DeprecSig (Deprecation ie txt) src_loc) + = pushSrcLocRn src_loc $ + renameIE lookup_occ_nm ie `thenRn` \ (new_ie, fvs) -> + returnRn (DeprecSig (Deprecation new_ie txt) src_loc, fvs) + +renameSig lookup_occ_nm (InlineSig v p src_loc) = pushSrcLocRn src_loc $ lookup_occ_nm v `thenRn` \ new_v -> - returnRn (FixSig (FixitySig new_v fix src_loc), unitFV new_v) + returnRn (InlineSig new_v p src_loc, unitFV new_v) -renameSig lookup_occ_nm (NoInlineSig v src_loc) +renameSig lookup_occ_nm (NoInlineSig v p src_loc) = pushSrcLocRn src_loc $ lookup_occ_nm v `thenRn` \ new_v -> - returnRn (NoInlineSig new_v src_loc, unitFV new_v) + returnRn (NoInlineSig new_v p src_loc, unitFV new_v) +\end{code} + +\begin{code} +renameIE :: (RdrName -> RnMS Name) -> IE RdrName -> RnMS (IE Name, FreeVars) +renameIE lookup_occ_nm (IEVar v) + = lookup_occ_nm v `thenRn` \ new_v -> + returnRn (IEVar new_v, unitFV new_v) + +renameIE lookup_occ_nm (IEThingAbs v) + = lookup_occ_nm v `thenRn` \ new_v -> + returnRn (IEThingAbs new_v, unitFV new_v) + +renameIE lookup_occ_nm (IEThingAll v) + = lookup_occ_nm v `thenRn` \ new_v -> + returnRn (IEThingAll new_v, unitFV new_v) + +renameIE lookup_occ_nm (IEThingWith v vs) + = lookup_occ_nm v `thenRn` \ new_v -> + mapRn lookup_occ_nm vs `thenRn` \ new_vs -> + returnRn (IEThingWith new_v new_vs, plusFVs [ unitFV x | x <- new_v:new_vs ]) + +renameIE lookup_occ_nm (IEModuleContents m) + = returnRn (IEModuleContents m, emptyFVs) \end{code} Checking for distinct signatures; oh, so boring + \begin{code} cmp_sig :: RenamedSig -> RenamedSig -> Ordering -cmp_sig (Sig n1 _ _) (Sig n2 _ _) = n1 `compare` n2 -cmp_sig (InlineSig n1 _) (InlineSig n2 _) = n1 `compare` n2 -cmp_sig (NoInlineSig n1 _) (NoInlineSig n2 _) = n1 `compare` n2 +cmp_sig (Sig n1 _ _) (Sig n2 _ _) = n1 `compare` n2 +cmp_sig (DeprecSig (Deprecation ie1 _) _) + (DeprecSig (Deprecation ie2 _) _) = cmp_ie ie1 ie2 +cmp_sig (InlineSig n1 _ _) (InlineSig n2 _ _) = n1 `compare` n2 +cmp_sig (NoInlineSig n1 _ _) (NoInlineSig n2 _ _) = n1 `compare` n2 cmp_sig (SpecInstSig ty1 _) (SpecInstSig ty2 _) = cmpHsType compare ty1 ty2 cmp_sig (SpecSig n1 ty1 _) (SpecSig n2 ty2 _) = -- may have many specialisations for one value; @@ -549,12 +602,21 @@ cmp_sig other_1 other_2 -- Tags *must* be different | (sig_tag other_1) _LT_ (sig_tag other_2) = LT | otherwise = GT +cmp_ie :: IE Name -> IE Name -> Ordering +cmp_ie (IEVar n1 ) (IEVar n2 ) = n1 `compare` n2 +cmp_ie (IEThingAbs n1 ) (IEThingAbs n2 ) = n1 `compare` n2 +cmp_ie (IEThingAll n1 ) (IEThingAll n2 ) = n1 `compare` n2 +-- Hmmm... +cmp_ie (IEThingWith n1 _) (IEThingWith n2 _) = n1 `compare` n2 +cmp_ie (IEModuleContents _ ) (IEModuleContents _ ) = EQ + sig_tag (Sig n1 _ _) = (ILIT(1) :: FAST_INT) sig_tag (SpecSig n1 _ _) = ILIT(2) -sig_tag (InlineSig n1 _) = ILIT(3) -sig_tag (NoInlineSig n1 _) = ILIT(4) +sig_tag (InlineSig n1 _ _) = ILIT(3) +sig_tag (NoInlineSig n1 _ _) = ILIT(4) sig_tag (SpecInstSig _ _) = ILIT(5) sig_tag (FixSig _) = ILIT(6) +sig_tag (DeprecSig _ _) = ILIT(7) sig_tag _ = panic# "tag(RnBinds)" \end{code} @@ -581,12 +643,13 @@ unknownSigErr sig (what_it_is, loc) = sig_doc sig sig_doc (Sig _ _ loc) = (SLIT("type signature"),loc) -sig_doc (ClassOpSig _ _ _ loc) = (SLIT("class-method type signature"), loc) +sig_doc (ClassOpSig _ _ _ _ loc) = (SLIT("class-method type signature"), loc) sig_doc (SpecSig _ _ loc) = (SLIT("SPECIALISE pragma"),loc) -sig_doc (InlineSig _ loc) = (SLIT("INLINE pragma"),loc) -sig_doc (NoInlineSig _ loc) = (SLIT("NOINLINE pragma"),loc) +sig_doc (InlineSig _ _ loc) = (SLIT("INLINE pragma"),loc) +sig_doc (NoInlineSig _ _ loc) = (SLIT("NOINLINE pragma"),loc) sig_doc (SpecInstSig _ loc) = (SLIT("SPECIALISE instance pragma"),loc) sig_doc (FixSig (FixitySig _ _ loc)) = (SLIT("fixity declaration"), loc) +sig_doc (DeprecSig _ loc) = (SLIT("DEPRECATED pragma"), loc) missingSigWarn var = sep [ptext SLIT("definition but no type signature for"), quotes (ppr var)]