Skip to content
Snippets Groups Projects
Commit 798374a5 authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

[project @ 2000-07-18 14:50:32 by simonpj]

Arrange that type signatures that have no "parent" signatures
work right.  For example

	   module A
	      f :: Int -> Int

The panic in RnEnv.lookupBndrRn becomes an error message.  Also
RnBinds.rnTopMonoBinds and rnMonoBinds were wrongly ignoring all
signatures altogether if there were no bindings!
parent 794f1a1d
No related branches found
No related tags found
No related merge requests found
......@@ -165,9 +165,6 @@ rnTopBinds (MonoBind bind sigs _) = rnTopMonoBinds bind sigs
-- The parser doesn't produce other forms
rnTopMonoBinds EmptyMonoBinds sigs
= returnRn (EmptyBinds, emptyFVs)
rnTopMonoBinds mbinds sigs
= mapRn lookupBndrRn binder_rdr_names `thenRn` \ binder_names ->
let
......@@ -218,8 +215,6 @@ rnMonoBinds :: RdrNameMonoBinds
-> (RenamedHsBinds -> RnMS (result, FreeVars))
-> RnMS (result, FreeVars)
rnMonoBinds EmptyMonoBinds sigs thing_inside = thing_inside EmptyBinds
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
......@@ -284,7 +279,7 @@ rn_mono_binds siglist mbinds
let
edges = mkEdges (mbinds_info `zip` [(0::Int)..])
scc_result = stronglyConnComp edges
final_binds = foldr1 ThenBinds (map reconstructCycle scc_result)
final_binds = foldr (ThenBinds . reconstructCycle) EmptyBinds scc_result
-- Deal with bound and free-var calculation
rhs_fvs = plusFVs [fvs | (_,fvs,_,_) <- mbinds_info]
......
......@@ -452,7 +452,14 @@ lookupBndrRn rdr_name
case lookupRdrEnv global_env (qualifyRdrName mod rdr_name) of
Just (name:rest) -> ASSERT( null rest )
returnRn name
Nothing -> pprPanic "lookupBndrRn" (ppr mod <+> ppr rdr_name)
Nothing -> -- Almost always this case is a compiler bug.
-- But consider a type signature that doesn't have
-- a corresponding binder:
-- module M where { f :: Int->Int }
-- We use lookupSigOccRn, which uses lookupBndrRn (for good reasons)
-- and we don't want to panic. So we report an out-of-scope error
failWithRn (mkUnboundName rdr_name)
(unknownNameErr rdr_name)
}
-- lookupOccRn looks up an occurrence of a RdrName
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment