diff --git a/ghc/compiler/main/CmdLineOpts.lhs b/ghc/compiler/main/CmdLineOpts.lhs
index 9bc8766e597f7c34a22911565e6e8ad131762a02..7b1a71d3336af0aa8d9ea45c6a279460f9e8671b 100644
--- a/ghc/compiler/main/CmdLineOpts.lhs
+++ b/ghc/compiler/main/CmdLineOpts.lhs
@@ -89,8 +89,8 @@ module CmdLineOpts (
 
 	opt_Verbose,
 	opt_WarnNameShadowing,
-	opt_WarnUnusedNames,
-	opt_WarnUnusedTopLevel,
+	opt_WarnUnusedMatches,
+	opt_WarnUnusedBinds,
 	opt_WarnUnusedImports,
 	opt_WarnIncompletePatterns,
 	opt_WarnOverlappingPatterns,
@@ -340,8 +340,8 @@ opt_WarnNameShadowing		= lookUp  SLIT("-fwarn-name-shadowing")
 opt_WarnIncompletePatterns	= lookUp  SLIT("-fwarn-incomplete-patterns")
 opt_WarnOverlappingPatterns	= lookUp  SLIT("-fwarn-overlapping-patterns")
 opt_WarnSimplePatterns	     	= lookUp  SLIT("-fwarn-simple-patterns")
-opt_WarnUnusedNames		= lookUp  SLIT("-fwarn-unused-names")
-opt_WarnUnusedTopLevel		= lookUp  SLIT("-fwarn-unused-toplevel")
+opt_WarnUnusedMatches		= lookUp  SLIT("-fwarn-unused-matches")
+opt_WarnUnusedBinds		= lookUp  SLIT("-fwarn-unused-binds")
 opt_WarnUnusedImports		= lookUp  SLIT("-fwarn-unused-imports")
 opt_WarnMissingMethods		= lookUp  SLIT("-fwarn-missing-methods")
 opt_WarnDuplicateExports	= lookUp  SLIT("-fwarn-duplicate-exports")
diff --git a/ghc/compiler/rename/Rename.lhs b/ghc/compiler/rename/Rename.lhs
index 614882a528802cb44935dfab137fcfb8e4f77a8b..0cb23f06dd4c70d7ff9e6d463b957db4b9714261 100644
--- a/ghc/compiler/rename/Rename.lhs
+++ b/ghc/compiler/rename/Rename.lhs
@@ -14,7 +14,7 @@ import RnHsSyn		( RenamedHsModule, RenamedHsDecl, extractHsTyNames )
 
 import CmdLineOpts	( opt_HiMap, opt_WarnNameShadowing, opt_D_show_rn_trace,
 			  opt_D_dump_rn, opt_D_show_rn_stats,
-			  opt_WarnUnusedNames
+			  opt_WarnUnusedBinds, opt_WarnUnusedImports
 		        )
 import RnMonad
 import RnNames		( getGlobalNames )
@@ -33,7 +33,7 @@ import Name		( Name, PrintUnqualified, Provenance, ExportFlag(..),
 			)
 import TysWiredIn	( unitTyCon, intTyCon, doubleTyCon )
 import TyCon		( TyCon )
-import PrelMods		( mAIN, gHC_MAIN )
+import PrelMods		( mAIN, pREL_MAIN )
 import PrelInfo		( ioTyCon_NAME )
 import ErrUtils		( pprBagOfErrors, pprBagOfWarnings,
 			  doIfSet, dumpIfSet, ghcExit
@@ -174,7 +174,7 @@ addImplicits mod_name
 
 	-- Add occurrences for IO or PrimIO
     implicit_main |  mod_name == mAIN
-		  || mod_name == gHC_MAIN = [ioTyCon_NAME]
+		  || mod_name == pREL_MAIN = [ioTyCon_NAME]
 		  |  otherwise 		  = []
 \end{code}
 
@@ -266,10 +266,6 @@ rn_data_decl mode (tycon_name,ty_decl) = rn_iface_decl mod_name mode (TyD ty_dec
 
 \begin{code}
 reportUnusedNames explicit_avail_names
-  | not opt_WarnUnusedNames
-  = returnRn ()
-
-  | otherwise
   = getSlurpedNames			`thenRn` \ slurped_names ->
     let
 	unused	      = explicit_avail_names `minusNameSet` slurped_names
@@ -277,19 +273,19 @@ reportUnusedNames explicit_avail_names
 	imports_by_module = equivClasses cmp imported_unused
 	name1 `cmp` name2 = nameModule name1 `compare` nameModule name2 
 
-	pp_imp = sep [text "For information: the following unqualified imports are unused:",
+	pp_imp = sep [text "Warning: the following unqualified imports are unused:",
 			  nest 4 (vcat (map pp_group imports_by_module))]
 	pp_group (n:ns) = sep [hcat [text "Module ", pprModule (nameModule n), char ':'],
 				   nest 4 (sep (map (pprOccName . nameOccName) (n:ns)))]
 
-	pp_local = sep [text "For information: the following local top-level definitions are unused:",
+	pp_local = sep [text "Warning: the following local top-level definitions are unused:",
 			    nest 4 (sep (map (pprOccName . nameOccName) local_unused))]
     in
-    (if null imported_unused 
+    (if not opt_WarnUnusedImports || null imported_unused
      then returnRn ()
      else addWarnRn pp_imp)	`thenRn_`
 
-    (if null local_unused
+    (if not opt_WarnUnusedBinds || null local_unused
      then returnRn ()
      else addWarnRn pp_local)
 
diff --git a/ghc/compiler/rename/RnBinds.lhs b/ghc/compiler/rename/RnBinds.lhs
index 046cd6876eb2fd105547dee869f36a1e5bb94ef2..4a7bd54ee35329111772e33ddfe6487b8306b57b 100644
--- a/ghc/compiler/rename/RnBinds.lhs
+++ b/ghc/compiler/rename/RnBinds.lhs
@@ -26,7 +26,7 @@ import RnHsSyn
 import RnMonad
 import RnExpr		( rnMatch, rnGRHSsAndBinds, rnPat, checkPrecMatch )
 import RnEnv		( bindLocatedLocalsRn, lookupBndrRn, lookupOccRn, 
-			  newLocalNames, isUnboundName, warnUnusedNames
+			  newLocalNames, isUnboundName, warnUnusedBinds
 			)
 import CmdLineOpts	( opt_SigsRequired )
 import Digraph		( stronglyConnComp, SCC(..) )
@@ -181,7 +181,7 @@ rnTopMonoBinds mbinds sigs
     let
 	unused_binders = binder_set `minusNameSet` (fv_set `unionNameSets` exported_binders)
     in
-    warnUnusedNames unused_binders	`thenRn_`
+    warnUnusedBinds unused_binders	`thenRn_`
     returnRn new_binds
   where
     binder_rdr_names = map fst (bagToList (collectMonoBinders mbinds))
@@ -233,7 +233,7 @@ rnMonoBinds mbinds sigs	thing_inside -- Non-empty monobinds
 	net_fvs        = all_fvs `minusNameSet` binder_set
 	unused_binders = binder_set `minusNameSet` all_fvs
     in
-    warnUnusedNames unused_binders	`thenRn_`
+    warnUnusedBinds unused_binders	`thenRn_`
     returnRn (result, net_fvs)
   where
     mbinders_w_srclocs = bagToList (collectMonoBinders mbinds)
diff --git a/ghc/compiler/rename/RnEnv.lhs b/ghc/compiler/rename/RnEnv.lhs
index 551c6c48f5a89c7854b33ac05a445c1959ec26e5..664fa700226327d2454f490fa43e4b700815f7d9 100644
--- a/ghc/compiler/rename/RnEnv.lhs
+++ b/ghc/compiler/rename/RnEnv.lhs
@@ -8,7 +8,8 @@ module RnEnv where		-- Export everything
 
 #include "HsVersions.h"
 
-import CmdLineOpts	( opt_WarnNameShadowing, opt_WarnUnusedNames )
+import CmdLineOpts	( opt_WarnNameShadowing, opt_WarnUnusedMatches,
+			  opt_WarnUnusedBinds, opt_WarnUnusedImports )
 import HsSyn
 import RdrHsSyn		( RdrName(..), RdrNameIE,
 			  rdrNameOcc, ieOcc, isQual, qual
@@ -644,11 +645,24 @@ conflictFM bad fm key elt
 
 
 \begin{code}
+warnUnusedBinds, warnUnusedMatches, warnUnusedImports :: NameSet -> RnM s d ()
+
+warnUnusedBinds names
+  | opt_WarnUnusedBinds = warnUnusedNames names
+  | otherwise           = returnRn ()
+
+warnUnusedMatches names
+  | opt_WarnUnusedMatches = warnUnusedNames names
+  | otherwise           = returnRn ()
+
+warnUnusedImports names
+  | opt_WarnUnusedImports = warnUnusedNames names
+  | otherwise           = returnRn ()
+
 warnUnusedNames :: NameSet -> RnM s d ()
 warnUnusedNames names 
-  | not opt_WarnUnusedNames = returnRn ()
-  | otherwise		    = mapRn warn (nameSetToList names)	`thenRn_`
-			      returnRn ()
+  = mapRn warn (nameSetToList names)	`thenRn_`
+    returnRn ()
   where
     warn name = pushSrcLocRn (getSrcLoc name) $
 		addWarnRn (unusedNameWarn name)
diff --git a/ghc/compiler/rename/RnExpr.lhs b/ghc/compiler/rename/RnExpr.lhs
index a4d82304cbcb5125bdf1d917d6d8200c3f133f9d..165555e1ad8f0c3427337d635807d7f604e98a4a 100644
--- a/ghc/compiler/rename/RnExpr.lhs
+++ b/ghc/compiler/rename/RnExpr.lhs
@@ -151,7 +151,8 @@ rnMatch match
 	unused_binders = binder_set `minusNameSet` fvs
 	net_fvs	       = fvs `minusNameSet` binder_set
     in
-    warnUnusedNames unused_binders	`thenRn_`
+    warnUnusedMatches unused_binders		`thenRn_`
+    
     returnRn (match', net_fvs)
  where
     get_binders (GRHSMatch _)	     = []
diff --git a/ghc/compiler/rename/RnIfaces.lhs b/ghc/compiler/rename/RnIfaces.lhs
index 9a3bbc2ea32d2218fd88a538cbacb767e6ffbbb8..f5e5e7783b3f9ad9c8553a3aa27b83308d37c3c1 100644
--- a/ghc/compiler/rename/RnIfaces.lhs
+++ b/ghc/compiler/rename/RnIfaces.lhs
@@ -55,7 +55,7 @@ import TyCon		( TyCon, tyConDataCons, isSynTyCon, getSynTyConDefn )
 import Type		( namesOfType )
 import TyVar		( GenTyVar )
 import SrcLoc		( mkSrcLoc, SrcLoc )
-import PrelMods		( gHC__ )
+import PrelMods		( pREL_GHC )
 import PrelInfo		( cCallishTyKeys )
 import Bag
 import Maybes		( MaybeErr(..), expectJust, maybeToBool )
@@ -509,7 +509,7 @@ getWiredInDecl name mode
 	mod        = nameModule main_name
 	doc_str    = sep [ptext SLIT("need home module for wired in thing"), ppr name]
     in
-    (if not main_is_tc || mod == gHC__ then
+    (if not main_is_tc || mod == pREL_GHC then
 	returnRn ()		
     else
 	loadInterface doc_str mod (ifaceFlavour main_name)	`thenRn_`
diff --git a/ghc/docs/users_guide/using.vsgml b/ghc/docs/users_guide/using.vsgml
index d2b35a11c829537903dc693a0ef68642759be29e..99e5a7dcdaa87960abcb8ce51ef2f902b8040f20 100644
--- a/ghc/docs/users_guide/using.vsgml
+++ b/ghc/docs/users_guide/using.vsgml
@@ -284,8 +284,8 @@ Synonym for @-Wnot@.
 <tag>@-W@:</tag>
 <nidx>-W option</nidx>
 
-Provides the standard warnings plus @-fwarn-incomplete-patterns@
-and @-fwarn-unused-names@.
+Provides the standard warnings plus @-fwarn-incomplete-patterns@,
+@-fwarn-unused-imports@ and @-fwarn-unused-binds@.
 
 <tag>@-Wall@:</tag>
 <nidx>-Wall option</nidx>
@@ -353,12 +353,31 @@ This option is on by default, and warns you whenever an instance
 declaration is missing one or more methods, and the corresponding
 class declaration has no default declaration for them.
 
-<tag>@-fwarn-unused-names@:</tag>
-<nidx>-fwarn-unused-names option</nidx>
-<nidx>unused names, warning</nidx>
-<nidx>names, unused</nidx>
+<tag>@-fwarn-unused-imports@:</tag>
+<nidx>-fwarn-unused-imports option</nidx>
+<nidx>unused imports, warning</nidx>
+<nidx>imports, unused</nidx>
 
-Have the renamer report which locally defined names are not used/exported.
+Report any objects that are explicitly imported but never used.
+
+<tag>@-fwarn-unused-binds@:</tag>
+<nidx>-fwarn-unused-binds option</nidx>
+<nidx>unused binds, warning</nidx>
+<nidx>binds, unused</nidx>
+
+Report any function definitions (and local bindings) which are unused.
+For top-level functions, the warning is only given if the binding is
+not exported.
+
+<tag>@-fwarn-unused-matches@:</tag>
+<nidx>-fwarn-unused-matches option</nidx>
+<nidx>unused matches, warning</nidx>
+<nidx>matches, unused</nidx>
+
+Report all unused variables which arise from pattern matches,
+including patterns consisting of a single variable.  For instance @f x
+y = []@ would report @x@ and @y@ as unused.  To eliminate the warning,
+all unused variables can be replaced with wildcards.
 
 <tag>@-fwarn-duplicate-exports@:</tag>
 <nidx>-fwarn-duplicate-exports option</nidx>
diff --git a/ghc/driver/ghc.lprl b/ghc/driver/ghc.lprl
index 166537f9c1543a5f2117cdcb90385ba8186113d2..92b6eeecd462b793387a9a98705f11502d46c094 100644
--- a/ghc/driver/ghc.lprl
+++ b/ghc/driver/ghc.lprl
@@ -138,7 +138,6 @@ $InstLibDirGhc     = "${libdir}";
 #
 $InstLibExecDirGhc = "${libexecdir}";
 $InstDataDirGhc    = "${datadir}";
-$InstSysLibDir     = ( $INSTALLING ) ? "${InstLibDirGhc}/hslibs" : "$TopPwd/hslibs";
 
 $Status  = 0; # just used for exit() status
 $Verbose = '';
@@ -282,8 +281,10 @@ these are turned off by -Wnot.
 		     '-fwarn-duplicate-exports');
 @MinusWOpts    	  = (@StandardWarnings, 
 		     '-fwarn-incomplete-patterns', 
-		     '-fwarn-unused-names');
+		     '-fwarn-unused-binds',
+		     '-fwarn-unused-imports');
 @MinusWallOpts 	  = (@MinusWOpts, 
+		     '-fwarn-unused-matches',
 		     '-fwarn-name-shadowing');
 \end{code}
 
@@ -370,13 +371,10 @@ require special handling.
 @Import_dir	= ('.'); #-i things
 @Include_dir	= ('.'); #-I things; other default(s) stuck on AFTER option processing
 
-# where to look for interface files (system hi's, i.e., prelude and hslibs)
+# where to look for interface files (system hi's, i.e., prelude and syslibs)
 @SysImport_dir	= ( $INSTALLING )
-		    ? ( "$InstLibDirGhc/imports" )
-		    : ( "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/required"
-		      , "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/ghc"
-		      , "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/glaExts"
-		      , "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/concurrent" );
+		    ? ( "$InstLibDirGhc/imports/std" )
+		    : ( "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/std" );
 
 # We need to look in ghc/ and glaExts/ when searching for implicitly needed .hi files, but 
 # we should really *not* look there for explicitly imported modules.
@@ -392,8 +390,8 @@ $Haskell1Version = 4; # i.e., Haskell 1.4
 		    ? $InstLibDirGhc
 		    : ( "$TopPwd/$CURRENT_DIR/$GHC_RUNTIME_DIR"
 		      , "$TopPwd/$CURRENT_DIR/$GHC_RUNTIME_DIR/gmp"
-		      , "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR"
-		      , "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/cbits"
+		      , "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/std"
+		      , "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/std/cbits"
 		      )
 		  );
 @SysLibrary = (); # will be built up as we go along
@@ -2431,17 +2429,18 @@ sub add_syslib {
     local($syslib) = @_;
     
     unshift(@SysImport_dir,
-	    ${INSTALLING} ? "$InstSysLibDir/$syslib/imports"
-		          : "$TopPwd/hslibs/$syslib/src");
+	    ${INSTALLING} ? "$InstLibDir/imports/$syslib"
+		          : "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/$syslib");
 
     push(@SysLibrary_dir,
-	 ${INSTALLING} ? ("$InstSysLibDir")
-                       : ("$TopPwd/hslibs/$syslib",
-			  "$TopPwd/hslibs/$syslib/cbits"));
+	 ${INSTALLING} ? ("$InstLibDir")
+                       : ("$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/$syslib",
+			  "$TopPwd/$CURRENT_DIR/$GHC_LIB_DIR/$syslib/cbits"));
 
     push(@SysLibrary, "-lHS$syslib");
     push(@SysLibrary, "-lHS${syslib}_cbits")
-          unless $syslib eq 'contrib'; #HACK! it has no cbits
+          unless $syslib eq 'contrib' || $syslib eq 'exts';
+	  #HACK! they have no cbits
 }
 \end{code}
 
@@ -2746,7 +2745,8 @@ arg: while($_ = $Args[0]) {
     #--------- ticky/concurrent/parallel -----------------------------------
     # we sort out the details a bit later on
 
-    /^-concurrent$/ && do { $CONCURing = 'c'; next arg; }; # concurrent Haskell
+    /^-concurrent$/ && do { $CONCURing = 'c'; &add_syslib('conc'); next arg; }; 
+			  # concurrent Haskell; implies -syslib conc
     /^-gransim$/    && do { $GRANing   = 'g'; next arg; }; # GranSim
     /^-ticky$/	    && do { $TICKYing  = 't'; next arg; }; # ticky-ticky
     /^-parallel$/   && do { $PARing    = 'p'; next arg; }; # parallel Haskell
@@ -2891,6 +2891,9 @@ arg: while($_ = $Args[0]) {
 			push(@HsP_flags, '-N');
 
 #			push(@HsC_flags, '-fshow-import-specs');
+		
+			# -fglasgow-exts implies -syslib exts
+			&add_syslib('exts');
 
 			next arg; };