diff --git a/ghc/compiler/absCSyn/Costs.lhs b/ghc/compiler/absCSyn/Costs.lhs
index a0a6110fd0ab3d60899e1b21c8749852bca0839c..00e790465f7fd85890655f56a78d2e04d3d081ee 100644
--- a/ghc/compiler/absCSyn/Costs.lhs
+++ b/ghc/compiler/absCSyn/Costs.lhs
@@ -1,7 +1,7 @@
 %
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
-% $Id: Costs.lhs,v 1.24 2000/07/06 14:08:31 simonmar Exp $
+% $Id: Costs.lhs,v 1.25 2000/07/14 08:15:28 simonpj Exp $
 %
 % Only needed in a GranSim setup -- HWL
 % ---------------------------------------------------------------------------
@@ -315,10 +315,6 @@ exprMacroCosts side macro mode_list =
 stmtMacroCosts :: CStmtMacro -> [CAddrMode] -> CostRes
 
 stmtMacroCosts macro modes =
-  let
-    arg_costs =	  foldl (+) nullCosts
-			[addrModeCosts mode Rhs | mode <- modes]
-  in
   case macro of
     ARGS_CHK_LOAD_NODE  ->  Cost (2, 1, 0, 0, 0)	 {- StgMacros.lh  -}
 		-- p=probability of PAP (instead of AP): + p*(3,1,0,0,0)
diff --git a/ghc/compiler/absCSyn/PprAbsC.lhs b/ghc/compiler/absCSyn/PprAbsC.lhs
index ed066f120115d32297b0a4f0a378925902b05542..d4379e8a763f6e69c7f577e4cabdecd6c6d0d97f 100644
--- a/ghc/compiler/absCSyn/PprAbsC.lhs
+++ b/ghc/compiler/absCSyn/PprAbsC.lhs
@@ -812,14 +812,6 @@ pprCCall call@(CCall op_str is_asm may_gc cconv) args results vol_regs
     (local_arg_decls, pp_non_void_args)
       = unzip [ ppr_casm_arg a i | (a,i) <- non_void_args `zip` [1..] ]
 
-    ccall_arg_tys = map (text.showPrimRep.getAmodeRep) non_void_args
-
-    ccall_res_ty = 
-       case non_void_results of
-          []       -> ptext SLIT("void")
-	  [amode]  -> text (showPrimRep (getAmodeRep amode))
-	  _	   -> panic "pprCCall: ccall_res_ty"
-
     (declare_local_vars, local_vars, assign_results)
       = ppr_casm_results non_void_results
 
diff --git a/ghc/compiler/codeGen/CgCase.lhs b/ghc/compiler/codeGen/CgCase.lhs
index de7a898468c7816acc5ee4d4bd063aab69a9eeb8..339569b4df3602665ce3f51d85c61b1eada92cb5 100644
--- a/ghc/compiler/codeGen/CgCase.lhs
+++ b/ghc/compiler/codeGen/CgCase.lhs
@@ -1,7 +1,7 @@
 %
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
-% $Id: CgCase.lhs,v 1.43 2000/07/11 16:03:37 simonmar Exp $
+% $Id: CgCase.lhs,v 1.44 2000/07/14 08:14:53 simonpj Exp $
 %
 %********************************************************
 %*							*
@@ -899,8 +899,6 @@ mkReturnVector :: Unique
 mkReturnVector uniq tagged_alt_absCs deflt_absC srt liveness ret_conv
   = getSRTLabel `thenFC` \srt_label ->
     let
-     srt_info = (srt_label, srt)
-
      (return_vec_amode, vtbl_body) = case ret_conv of {
 
 	-- might be a polymorphic case...
diff --git a/ghc/compiler/codeGen/CgClosure.lhs b/ghc/compiler/codeGen/CgClosure.lhs
index ae028d2a45ba6aea9b7fb01491bdf2d285b13387..34a84cc93c62cc72b9a53e228fa0b137a42901d8 100644
--- a/ghc/compiler/codeGen/CgClosure.lhs
+++ b/ghc/compiler/codeGen/CgClosure.lhs
@@ -1,7 +1,7 @@
 %
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
-% $Id: CgClosure.lhs,v 1.40 2000/07/06 14:08:31 simonmar Exp $
+% $Id: CgClosure.lhs,v 1.41 2000/07/14 08:14:53 simonpj Exp $
 %
 \section[CgClosure]{Code generation for closures}
 
@@ -158,9 +158,6 @@ cgStdRhsClosure binder cc binder_info fvs args body lf_info payload
 
 	-- RETURN
     returnFC (binder, heapIdInfo binder heap_offset lf_info)
-
-  where
-    is_std_thunk	   = isStandardFormThunk lf_info
 \end{code}
 
 Here's the general case.
@@ -311,7 +308,7 @@ closureCodeBody binder_info closure_info cc all_args body
 
 	-- Arg mapping for standard (slow) entry point; all args on stack,
 	-- with tagging.
-    	(sp_all_args, arg_offsets, arg_tags)
+    	(sp_all_args, arg_offsets, _)
 	   = mkTaggedVirtStkOffsets vSp idPrimRep all_args
 
 	-- Arg mapping for the fast entry point; as many args as poss in
diff --git a/ghc/compiler/codeGen/CgCon.lhs b/ghc/compiler/codeGen/CgCon.lhs
index 8aeda98f90e0d1fa11822fdbba498f9773daedaf..e04da6b9c3374600aaa6ebdf724d69ed61e45f77 100644
--- a/ghc/compiler/codeGen/CgCon.lhs
+++ b/ghc/compiler/codeGen/CgCon.lhs
@@ -91,7 +91,6 @@ cgTopRhsCon id con args
 	-- RETURN
     returnFC (id, stableAmodeIdInfo id (CLbl closure_label PtrRep) lf_info)
   where
-    con_tycon	    = dataConTyCon   con
     lf_info	    = mkConLFInfo    con
     closure_label   = mkClosureLabel name
     name            = idName id
@@ -173,8 +172,6 @@ buildDynCon binder cc con [arg_amode]
 
     in_range_int_lit (CLit (MachInt val)) = val <= mAX_INTLIKE && val >= mIN_INTLIKE
     in_range_int_lit other_amode	  = False
-
-    tycon = dataConTyCon con
 \end{code}
 
 Now the general case.
@@ -364,8 +361,6 @@ cgReturnDataCon con amodes
 		build_it_then (mkStaticAlgReturnCode con)
 
   where
-    con_name = dataConName con
-
     move_to_reg :: CAddrMode -> MagicId -> AbstractC
     move_to_reg src_amode dest_reg = CAssign (CReg dest_reg) src_amode
 
diff --git a/ghc/compiler/codeGen/CgConTbls.lhs b/ghc/compiler/codeGen/CgConTbls.lhs
index fcee09f5b4c945fa6fda5e76495095afb27e1625..e3197fadc419d8ccacd23c7d3a9a062f376e9061 100644
--- a/ghc/compiler/codeGen/CgConTbls.lhs
+++ b/ghc/compiler/codeGen/CgConTbls.lhs
@@ -124,7 +124,6 @@ genConInfo comp_info tycon data_con
 	    	      profCtrC SLIT("TICK_ENT_CON") [CReg node] `thenC`
 		      body_code))
 
-    entry_addr = CLbl entry_label CodePtrRep
     con_descr  = occNameUserString (getOccName data_con)
 
     -- Don't need any dynamic closure code for zero-arity constructors
@@ -135,10 +134,6 @@ genConInfo comp_info tycon data_con
 
     static_code  = CClosureInfoAndCode static_ci body Nothing con_descr
 
-    cost_centre  = mkCCostCentreStack dontCareCCS -- not worried about static data costs
-
-    zero_size arg_ty = getPrimRepSize (typePrimRep arg_ty) == 0
-
     zero_arity_con   = isNullaryDataCon data_con
 	-- We used to check that all the arg-sizes were zero, but we don't
 	-- really have any constructors with only zero-size args, and it's
diff --git a/ghc/compiler/codeGen/CgHeapery.lhs b/ghc/compiler/codeGen/CgHeapery.lhs
index 23928f69b716504920ab70a325d93e9a1f16318b..31cb2378911cb7d81304a76fb2eabc81f3cfa7b0 100644
--- a/ghc/compiler/codeGen/CgHeapery.lhs
+++ b/ghc/compiler/codeGen/CgHeapery.lhs
@@ -1,7 +1,7 @@
 %
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
-% $Id: CgHeapery.lhs,v 1.21 2000/07/11 16:03:37 simonmar Exp $
+% $Id: CgHeapery.lhs,v 1.22 2000/07/14 08:14:53 simonpj Exp $
 %
 \section[CgHeapery]{Heap management functions}
 
@@ -397,7 +397,6 @@ fetchAndReschedule regs node_reqd  =
 	then fetch_code `thenC` reschedule_code
 	else absC AbsCNop
       where
-	all_regs = if node_reqd then node:regs else regs
         liveness_mask = mkRegLiveness regs
 	reschedule_code = absC  (CMacroStmt GRAN_RESCHEDULE [
                                  mkIntCLit (IBOX(word2Int# liveness_mask)), 
@@ -431,7 +430,6 @@ yield regs node_reqd =
      then yield_code
      else absC AbsCNop
    where
-     -- all_regs = if node_reqd then node:regs else regs
      liveness_mask = mkRegLiveness regs
      yield_code = 
        absC (CMacroStmt GRAN_YIELD 
diff --git a/ghc/compiler/codeGen/CgTailCall.lhs b/ghc/compiler/codeGen/CgTailCall.lhs
index c1a6ec31d7a1bc865401908f02a4fc6ae7288dfa..7428e5eb62ab845410d5905918c4473799bc7aad 100644
--- a/ghc/compiler/codeGen/CgTailCall.lhs
+++ b/ghc/compiler/codeGen/CgTailCall.lhs
@@ -1,7 +1,7 @@
 %
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
-% $Id: CgTailCall.lhs,v 1.25 2000/07/11 16:03:37 simonmar Exp $
+% $Id: CgTailCall.lhs,v 1.26 2000/07/14 08:14:53 simonpj Exp $
 %
 %********************************************************
 %*							*
@@ -403,8 +403,6 @@ doTailCall arg_amodes arg_regs finish_code arity pending_assts
   = getEndOfBlockInfo	`thenFC` \ eob@(EndOfBlockInfo args_sp sequel) ->
 
     let
-	no_of_args = length arg_amodes
-
 	(reg_arg_amodes, stk_arg_amodes) = splitAt (length arg_regs) arg_amodes
 	    -- We get some stk_arg_amodes if (a) no regs, or 
 	    --				     (b) args beyond arity
@@ -428,7 +426,6 @@ doTailCall arg_amodes arg_regs finish_code arity pending_assts
 		splitAt arity stk_arg_amodes
 
 	-- eager blackholing, at the end of the basic block.
-	node_save = CTemp (mkPseudoUnique1 2) DataPtrRep
 	(r1_tmp_asst, bh_asst)
 	 = case sequel of
 #if 0
@@ -441,6 +438,8 @@ doTailCall arg_amodes arg_regs finish_code arity pending_assts
 		    CAssign (CVal (CIndex node_save (mkIntCLit 0) PtrRep) 
 				  PtrRep)
 			    (CLbl mkBlackHoleInfoTableLabel DataPtrRep))
+		   where
+		     node_save = CTemp (mkPseudoUnique1 2) DataPtrRep
 #endif
 		_ -> (AbsCNop, AbsCNop)
     in
diff --git a/ghc/compiler/codeGen/ClosureInfo.lhs b/ghc/compiler/codeGen/ClosureInfo.lhs
index 302dbc44380a3b292b93f8dad47f2297cfe8a565..6ccd79e184f38468a6314357c887ee14bfcbcdcb 100644
--- a/ghc/compiler/codeGen/ClosureInfo.lhs
+++ b/ghc/compiler/codeGen/ClosureInfo.lhs
@@ -1,7 +1,7 @@
 %
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
-% $Id: ClosureInfo.lhs,v 1.42 2000/05/25 12:41:15 simonpj Exp $
+% $Id: ClosureInfo.lhs,v 1.43 2000/07/14 08:14:53 simonpj Exp $
 %
 \section[ClosureInfo]{Data structures which describe closures}
 
@@ -421,8 +421,6 @@ layOutStaticClosure name kind_fn things lf_info
     closure_type = getClosureType is_static tot_wds ptr_wds lf_info
     is_static    = True
 
-    bot = panic "layoutStaticClosure"
-
 layOutStaticNoFVClosure :: Name -> LambdaFormInfo -> ClosureInfo
 layOutStaticNoFVClosure name lf_info
   = MkClosureInfo name lf_info (GenericRep is_static 0 0 (getClosureType is_static 0 0 lf_info))
@@ -973,8 +971,6 @@ mkConEntryPtr :: DataCon -> SMRep -> CLabel
 mkConEntryPtr con rep
   | isStaticRep rep = mkStaticConEntryLabel (dataConName con)
   | otherwise       = mkConEntryLabel       (dataConName con)
-  where
-    name = dataConName con
 
 closureLabelFromCI (MkClosureInfo id _ other_rep)   = mkClosureLabel id
 
diff --git a/ghc/compiler/coreSyn/CoreUnfold.lhs b/ghc/compiler/coreSyn/CoreUnfold.lhs
index 463326eab05d43fb785dd4ef7b6066b4ca2986a1..239cd1d5df72e91d5d3a40afe97c99402d14eb21 100644
--- a/ghc/compiler/coreSyn/CoreUnfold.lhs
+++ b/ghc/compiler/coreSyn/CoreUnfold.lhs
@@ -236,7 +236,6 @@ sizeExpr (I# bOMB_OUT_SIZE) top_args expr
 	= alts_size (foldr addSize sizeOne alt_sizes)	-- The 1 is for the scrutinee
 		    (foldr1 maxSize alt_sizes)
 	where
-	  v_in_args = v `elem` top_args
 	  alt_sizes = map size_up_alt alts
 
 	  alts_size (SizeIs tot tot_disc tot_scrut)		-- Size of all alternatives