diff --git a/ghc/compiler/reader/RdrHsSyn.lhs b/ghc/compiler/reader/RdrHsSyn.lhs
index 3beba6cbeb70564c1a8a128e8d1d97aacd300386..f7f9eed0104c9bae87bdd71c37ca73ce6051d2af 100644
--- a/ghc/compiler/reader/RdrHsSyn.lhs
+++ b/ghc/compiler/reader/RdrHsSyn.lhs
@@ -63,6 +63,8 @@ import Util		( thenCmp )
 import HsPragmas	( GenPragmas, ClassPragmas, DataPragmas, ClassOpPragmas, InstancePragmas )
 import List		( nub )
 import Outputable
+
+import Char		( isUpper )
 \end{code}
 
 \begin{code}
diff --git a/ghc/compiler/rename/RnBinds.lhs b/ghc/compiler/rename/RnBinds.lhs
index 8780058bc478e1b80f6f56db65f474c3044eac18..cd048443e8c129ea1157c97d7ce49d683255f6f2 100644
--- a/ghc/compiler/rename/RnBinds.lhs
+++ b/ghc/compiler/rename/RnBinds.lhs
@@ -266,12 +266,12 @@ rn_mono_binds top_lev binders mbinds sigs
     flattenMonoBinds siglist mbinds	`thenRn` \ mbinds_info ->
 
 	 -- Do the SCC analysis
-    let edges	    = mkEdges (mbinds_info `zip` [0..])
+    let edges	    = mkEdges (mbinds_info `zip` [(0::Int)..])
 	scc_result  = stronglyConnComp edges
 	final_binds = foldr1 ThenBinds (map reconstructCycle scc_result)
 
 	 -- Deal with bound and free-var calculation
-	rhs_fvs = unionManyNameSets [fvs | (_,_,fvs,_,_) <- mbinds_info]
+	rhs_fvs = unionManyNameSets [fvs | (_,fvs,_,_) <- mbinds_info]
     in
     returnRn (final_binds, rhs_fvs)
 \end{code}
@@ -282,7 +282,7 @@ unique ``vertex tags'' on its output; minor plumbing required.
 \begin{code}
 flattenMonoBinds :: [RenamedSig]		-- Signatures
 		 -> RdrNameMonoBinds
-		 -> RnMS s (Int, [FlatMonoBindsInfo])
+		 -> RnMS s [FlatMonoBindsInfo]
 
 flattenMonoBinds sigs EmptyMonoBinds = returnRn []
 
@@ -387,14 +387,14 @@ as the two cases are similar.
 reconstructCycle :: SCC FlatMonoBindsInfo
 		 -> RenamedHsBinds
 
-reconstructCycle (AcyclicSCC (_, _, _, binds, sigs))
+reconstructCycle (AcyclicSCC (_, _, binds, sigs))
   = MonoBind binds sigs NonRecursive
 
 reconstructCycle (CyclicSCC cycle)
   = MonoBind this_gp_binds this_gp_sigs Recursive
   where
-    this_gp_binds      = foldr1 AndMonoBinds [binds | (_, _, _, binds, _) <- cycle]
-    this_gp_sigs       = foldr1 (++)	     [sigs  | (_, _, _, _, sigs) <- cycle]
+    this_gp_binds      = foldr1 AndMonoBinds [binds | (_, _, binds, _) <- cycle]
+    this_gp_sigs       = foldr1 (++)	     [sigs  | (_, _, _, sigs) <- cycle]
 \end{code}
 
 %************************************************************************
diff --git a/ghc/compiler/rename/RnEnv.lhs b/ghc/compiler/rename/RnEnv.lhs
index dff9abed0da1693f64f615127d5537f416dd62ee..2260f56f1fe006d061442cc970624954903fc740 100644
--- a/ghc/compiler/rename/RnEnv.lhs
+++ b/ghc/compiler/rename/RnEnv.lhs
@@ -473,7 +473,7 @@ addOneToGlobalNameEnv :: GlobalNameEnv -> RdrName -> (Name, HowInScope) -> RnM s
 addOneToGlobalNameEnv env rdr_name name
  = case lookupFM env rdr_name of
 	Just name2 | conflicting_name name name2
-		   -> addNameClashErrRn (rdr_name, (name, name2)))	`thenRn_`
+		   -> addNameClashErrRn (rdr_name, (name, name2)) `thenRn_`
 		      returnRn env
 
 	other      -> returnRn (addToFM env rdr_name name)
@@ -713,7 +713,7 @@ addNameClashErrRn (rdr_name, ((_,how_in_scope1), (_, how_in_scope2)))
   | otherwise
   = addErrRn (hang (hsep [ptext SLIT("Conflicting definitions for"), quotes (ppr rdr_name)])
 	      4 (vcat [ppr how_in_scope1,
-		       ppr how_in_scope2])
+		       ppr how_in_scope2]))
 
 fixityClashErr (rdr_name, ((_,how_in_scope1), (_, how_in_scope2)))
   = hang (hsep [ptext SLIT("Conflicting fixities for"), quotes (ppr rdr_name)])