diff --git a/ghc/driver/Main.hs b/ghc/driver/Main.hs
index d3f5cd7d3bbacfac0fa174d126af512c41778473..03fececccee8cb69b313737b0b63ee864322c302 100644
--- a/ghc/driver/Main.hs
+++ b/ghc/driver/Main.hs
@@ -645,14 +645,14 @@ getPackageIncludePath   :: IO [String]
 getPackageIncludePath = do
   ps <- readIORef packages
   ps' <- getPackageDetails ps
-  return (nub (filter (not.null) (map include_dir ps')))
+  return (nub (filter (not.null) (concatMap include_dirs ps')))
 
 	-- includes are in reverse dependency order (i.e. rts first)
 getPackageCIncludes   :: IO [String]
 getPackageCIncludes = do
   ps <- readIORef packages
   ps' <- getPackageDetails ps
-  return (reverse (nub (filter (not.null) (map c_include ps'))))
+  return (reverse (nub (filter (not.null) (concatMap c_includes ps'))))
 
 getPackageLibraryPath  :: IO [String]
 getPackageLibraryPath = do
@@ -672,26 +672,24 @@ getPackageExtraGhcOpts :: IO [String]
 getPackageExtraGhcOpts = do
   ps <- readIORef packages
   ps' <- getPackageDetails ps
-  return (map extra_ghc_opts ps')
+  return (concatMap extra_ghc_opts ps')
 
 getPackageExtraCcOpts  :: IO [String]
 getPackageExtraCcOpts = do
   ps <- readIORef packages
   ps' <- getPackageDetails ps
-  return (map extra_cc_opts ps')
+  return (concatMap extra_cc_opts ps')
 
 getPackageExtraLdOpts  :: IO [String]
 getPackageExtraLdOpts = do
   ps <- readIORef packages
   ps' <- getPackageDetails ps
-  return (map extra_ld_opts ps')
+  return (concatMap extra_ld_opts ps')
 
+getPackageDetails :: [String] -> IO [Package]
 getPackageDetails ps = do
   pkg_details <- readIORef package_details
-  let getDetails p =  case lookup p pkg_details of
-			Just details -> return details
-			Nothing -> error "getPackageDetails"
-  mapM getDetails ps
+  return [ pkg | p <- ps, Just pkg <- [ lookup p pkg_details ] ]
 
 GLOBAL_VAR(package_details, (error "package_details"), [(String,Package)])
 
diff --git a/ghc/driver/Package.hs b/ghc/driver/Package.hs
index 92525f63b07c80e6c93615ab1618711cdbfc8fd3..778d7be13c60fad7edf95f256dc464865505d40f 100644
--- a/ghc/driver/Package.hs
+++ b/ghc/driver/Package.hs
@@ -6,12 +6,12 @@ data Package = Package {
 		import_dirs    :: [String],
       		library_dirs   :: [String],
       		libraries      :: [String],
-      		include_dir    :: String,
-		c_include      :: String,
+      		include_dirs   :: [String],
+		c_includes     :: [String],
       		package_deps   :: [String],
-      		extra_ghc_opts :: String,
-      		extra_cc_opts  :: String,
-      		extra_ld_opts  :: String
+      		extra_ghc_opts :: [String],
+      		extra_cc_opts  :: [String],
+      		extra_ld_opts  :: [String]
      		}
   deriving (Read, Show)
 
@@ -22,30 +22,26 @@ dumpPackages :: [(String,Package)] -> String
 dumpPackages pkgs = 
    render (brackets (vcat (punctuate comma (map dumpPkg pkgs))))
 
-dumpPkg (name, pkg) = parens (hang (text (show name) <> comma) 
-				2 (dumpPkgGuts pkg))
+dumpPkg :: (String,Package) -> Doc
+dumpPkg (name, pkg) =
+   parens (hang (text (show name) <> comma) 2 (dumpPkgGuts pkg))
 
-dumpPkgGuts (Package
-	{ import_dirs    = import_dirs    
-      	, library_dirs   = library_dirs   
-      	, libraries      = libraries      
-      	, include_dir    = include_dir    
-	, c_include      = c_include      
-      	, package_deps   = package_deps   
-      	, extra_ghc_opts = extra_ghc_opts 
-      	, extra_cc_opts  = extra_cc_opts  
-      	, extra_ld_opts  = extra_ld_opts   })
-   = text "Package" $$ nest 3 (braces (
-   	sep (punctuate comma [
-   	   hang (text "import_dirs ="     ) 2 (pprStrs import_dirs),
-   	   hang (text "library_dirs = "   ) 2 (pprStrs library_dirs),
-   	   hang (text "libraries = "      ) 2 (pprStrs libraries),
-   	   hang (text "include_dir = "    ) 2 (text (show include_dir)),
-   	   hang (text "c_include = "      ) 2 (text (show c_include)),
-   	   hang (text "package_deps = "   ) 2 (pprStrs package_deps),
-   	   hang (text "extra_ghc_opts = " ) 2 (text (show extra_ghc_opts)),
-   	   hang (text "extra_cc_opts = "  ) 2 (text (show extra_cc_opts)),
-   	   hang (text "extra_ld_opts = "  ) 2 (text (show extra_ld_opts))
-   	])))
+dumpPkgGuts :: Package -> Doc
+dumpPkgGuts pkg =
+   text "Package" $$ nest 3 (braces (
+      sep (punctuate comma [
+         dumpField "import_dirs"    (import_dirs    pkg),
+         dumpField "library_dirs"   (library_dirs   pkg),
+         dumpField "libraries"      (libraries      pkg),
+         dumpField "include_dirs"   (include_dirs   pkg),
+         dumpField "c_includes"     (c_includes     pkg),
+         dumpField "package_deps"   (package_deps   pkg),
+         dumpField "extra_ghc_opts" (extra_ghc_opts pkg),
+         dumpField "extra_cc_opts"  (extra_cc_opts  pkg),
+         dumpField "extra_ld_opts"  (extra_ld_opts  pkg)
+      ])))
 
-pprStrs strs = brackets (sep (punctuate comma (map (text . show) strs)))
+dumpField :: String -> [String] -> Doc
+dumpField name val =
+   hang (text name <+> equals) 2
+        (brackets (sep (punctuate comma (map (text . show) val))))
diff --git a/ghc/driver/PackageSrc.hs b/ghc/driver/PackageSrc.hs
index 845748c4df3ce2a091c2857d56f603f32212ef6f..2c8726e4446eaeb504db9cc827f54ef357c58f00 100644
--- a/ghc/driver/PackageSrc.hs
+++ b/ghc/driver/PackageSrc.hs
@@ -1,332 +1,333 @@
 module Main (main) where
 
-import IOExts
 import IO
 import System
 import Config
 import Package
 
+main :: IO ()
 main = do
   args <- getArgs
   case args of
-	[ "install"  ] -> do { putStr (dumpPackages (package_details True)) }
-	[ "in-place" ] -> do { putStr (dumpPackages (package_details False)) }
-	_ -> do hPutStr stderr "usage: pkgconf (install | in-place)\n"
-	        exitWith (ExitFailure 1)
+        [ "install"  ] -> do { putStr (dumpPackages (package_details True)) }
+        [ "in-place" ] -> do { putStr (dumpPackages (package_details False)) }
+        _ -> do hPutStr stderr "usage: pkgconf (install | in-place)\n"
+                exitWith (ExitFailure 1)
 
 package_details :: Bool -> [(String,Package)]
 package_details installing =
  [
-      ( "gmp",	-- GMP is at the bottom of the heap
-	Package {
-	import_dirs    = [],
-	library_dirs   = if cHaveLibGmp == "YES"
-			     then []
-			     else if installing 
-				   then [ clibdir ]
-				   else [ ghc_src_dir cGHC_RUNTIME_DIR ++ "/gmp" ],
-	libraries      = [ "gmp" ],
-	include_dir    = "",
-	c_include      = "",
-	package_deps   = [],
-	extra_ghc_opts = "",
-	extra_cc_opts  = "",
-	extra_ld_opts  = ""
-	}
+      ( "gmp",  -- GMP is at the bottom of the heap
+        Package {
+        import_dirs    = [],
+        library_dirs   = if cHaveLibGmp == "YES"
+                            then []
+                            else if installing
+                                    then [ clibdir ]
+                                    else [ ghc_src_dir cGHC_RUNTIME_DIR ++ "/gmp" ],
+        libraries      = [ "gmp" ],
+        include_dirs   = [],
+        c_includes     = [],
+        package_deps   = [],
+        extra_ghc_opts = [],
+        extra_cc_opts  = [],
+        extra_ld_opts  = []
+        }
        ),
 
-      ( "rts",	-- The RTS is just another package!
-	Package {
-	import_dirs    = [],
-	library_dirs   = [ if installing 
-	       		      then clibdir
-	       		      else ghc_src_dir cGHC_RUNTIME_DIR ],
-	libraries      = [ "HSrts" ],
-	include_dir    = if installing 
-			    then clibdir ++ "/includes"
-			    else ghc_src_dir cGHC_INCLUDE_DIR,
-	c_include      = "Stg.h",		-- ha!
-	package_deps   = [ "gmp" ],
-	extra_ghc_opts = "",
-	extra_cc_opts  = "",
-		-- the RTS forward-references to a bunch of stuff in the prelude,
-		-- so we force it to be included with special options to ld.
-	extra_ld_opts  = unwords [
-         "-u PrelMain_mainIO_closure",
-         "-u PrelBase_Izh_static_info",
-         "-u PrelBase_Czh_static_info",
-         "-u PrelFloat_Fzh_static_info",
-         "-u PrelFloat_Dzh_static_info",
-         "-u PrelAddr_Azh_static_info",
-         "-u PrelAddr_Wzh_static_info",
-         "-u PrelAddr_I64zh_static_info",
-         "-u PrelAddr_W64zh_static_info",
-         "-u PrelStable_StablePtr_static_info",
-	 "-u PrelBase_Izh_con_info",
-         "-u PrelBase_Czh_con_info",
-         "-u PrelFloat_Fzh_con_info",
-         "-u PrelFloat_Dzh_con_info",
-         "-u PrelAddr_Azh_con_info",
-         "-u PrelAddr_Wzh_con_info",
-         "-u PrelAddr_I64zh_con_info",
-         "-u PrelAddr_W64zh_con_info",
-         "-u PrelStable_StablePtr_con_info",
-         "-u PrelBase_False_closure",
-         "-u PrelBase_True_closure",
-         "-u PrelPack_unpackCString_closure",
-         "-u PrelIOBase_stackOverflow_closure",
-         "-u PrelIOBase_heapOverflow_closure",
-         "-u PrelIOBase_NonTermination_closure",
-         "-u PrelIOBase_PutFullMVar_closure",
-         "-u PrelIOBase_BlockedOnDeadMVar_closure",
-	 "-u PrelWeak_runFinalizzerBatch_closure",
-         "-u __init_Prelude",
-         "-u __init_PrelMain"
+      ( "rts",  -- The RTS is just another package!
+        Package {
+        import_dirs    = [],
+        library_dirs   = if installing
+                            then [ clibdir ]
+                            else [ ghc_src_dir cGHC_RUNTIME_DIR ],
+        libraries      = [ "HSrts" ],
+        include_dirs   = if installing
+                            then [ clibdir ++ "/includes" ]
+                            else [ ghc_src_dir cGHC_INCLUDE_DIR ],
+        c_includes     = [ "Stg.h" ],           -- ha!
+        package_deps   = [ "gmp" ],
+        extra_ghc_opts = [],
+        extra_cc_opts  = [],
+                -- the RTS forward-references to a bunch of stuff in the prelude,
+                -- so we force it to be included with special options to ld.
+        extra_ld_opts  = [
+           "-u PrelMain_mainIO_closure"
+         , "-u PrelBase_Izh_static_info"
+         , "-u PrelBase_Czh_static_info"
+         , "-u PrelFloat_Fzh_static_info"
+         , "-u PrelFloat_Dzh_static_info"
+         , "-u PrelAddr_Azh_static_info"
+         , "-u PrelAddr_Wzh_static_info"
+         , "-u PrelAddr_I64zh_static_info"
+         , "-u PrelAddr_W64zh_static_info"
+         , "-u PrelStable_StablePtr_static_info"
+         , "-u PrelBase_Izh_con_info"
+         , "-u PrelBase_Czh_con_info"
+         , "-u PrelFloat_Fzh_con_info"
+         , "-u PrelFloat_Dzh_con_info"
+         , "-u PrelAddr_Azh_con_info"
+         , "-u PrelAddr_Wzh_con_info"
+         , "-u PrelAddr_I64zh_con_info"
+         , "-u PrelAddr_W64zh_con_info"
+         , "-u PrelStable_StablePtr_con_info"
+         , "-u PrelBase_False_closure"
+         , "-u PrelBase_True_closure"
+         , "-u PrelPack_unpackCString_closure"
+         , "-u PrelIOBase_stackOverflow_closure"
+         , "-u PrelIOBase_heapOverflow_closure"
+         , "-u PrelIOBase_NonTermination_closure"
+         , "-u PrelIOBase_PutFullMVar_closure"
+         , "-u PrelIOBase_BlockedOnDeadMVar_closure"
+         , "-u PrelWeak_runFinalizzerBatch_closure"
+         , "-u __init_Prelude"
+         , "-u __init_PrelMain"
          ]
-	}
+        }
       ),
 
-      ( "std",	-- The Prelude & Standard Libraries
-	Package {
-	import_dirs    = [ if installing 
-	     	       	     then clibdir ++ "/imports/std"
-	     	       	     else ghc_src_dir cGHC_LIB_DIR ++ "/std" ],
-	library_dirs   = if installing 
-	       	       	   then [ clibdir ]
-	       	       	   else [ ghc_src_dir cGHC_LIB_DIR ++ "/std"
-				, ghc_src_dir cGHC_LIB_DIR ++ "/std/cbits" ],
-	libraries      = [ "HSstd", "HSstd_cbits" ],
-	include_dir    = if installing 
-		       	   then "" 
-		       	   else ghc_src_dir cGHC_LIB_DIR ++ "/std/cbits",
-	c_include      = "HsStd.h",
-	package_deps   = [ "rts" ],
-	extra_ghc_opts = "",
-	extra_cc_opts  = "",
-	extra_ld_opts  = "-lm"
-	}
+      ( "std",  -- The Prelude & Standard Libraries
+        Package {
+        import_dirs    = if installing
+                            then [ clibdir ++ "/imports/std" ]
+                            else [ ghc_src_dir cGHC_LIB_DIR ++ "/std" ],
+        library_dirs   = if installing
+                            then [ clibdir ]
+                            else [ ghc_src_dir cGHC_LIB_DIR ++ "/std"
+                                 , ghc_src_dir cGHC_LIB_DIR ++ "/std/cbits" ],
+        libraries      = [ "HSstd", "HSstd_cbits" ],
+        include_dirs   = if installing
+                            then []
+                            else [ ghc_src_dir cGHC_LIB_DIR ++ "/std/cbits" ],
+        c_includes     = [ "HsStd.h" ],
+        package_deps   = [ "rts" ],
+        extra_ghc_opts = [],
+        extra_cc_opts  = [],
+        extra_ld_opts  = [ "-lm" ]
+        }
        ),
 
        ( "lang",
-	 Package { 
-	 import_dirs    = if installing 
-	       		   then [ clibdir ++ "/imports/lang" ]
-	       		   else [ cFPTOOLS_TOP_ABS ++ "/hslibs/lang"
-		    	        , cFPTOOLS_TOP_ABS ++ "/hslibs/lang/monads"],
-	 library_dirs   = if installing 
-	       		     then [ clibdir ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/lang"
-				  , cFPTOOLS_TOP_ABS ++ "/hslibs/lang/cbits" ],
-	 libraries      = [ "HSlang", "HSlang_cbits" ],
-	 include_dir    = if installing 
-			     then "" 
-			     else cFPTOOLS_TOP_ABS ++ "/hslibs/lang/cbits",
-	 c_include      = "HsLang.h",
-	 package_deps   = [],
-	 extra_ghc_opts = "",
-	 extra_cc_opts  = "",
-	 extra_ld_opts  = ""
-	}
+         Package { 
+         import_dirs    = if installing
+                             then [ clibdir ++ "/imports/lang" ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/lang"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/lang/monads" ],
+         library_dirs   = if installing
+                             then [ clibdir ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/lang"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/lang/cbits" ],
+         libraries      = [ "HSlang", "HSlang_cbits" ],
+         include_dirs   = if installing
+                             then []
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/lang/cbits" ],
+         c_includes     = [ "HsLang.h" ],
+         package_deps   = [],
+         extra_ghc_opts = [],
+         extra_cc_opts  = [],
+         extra_ld_opts  = []
+        }
        ),
 
        ( "concurrent",
-	 Package {
-	 import_dirs    = [ if installing 
-	       		        then clibdir ++ "/imports/concurrent"
-	       		        else cFPTOOLS_TOP_ABS ++ "/hslibs/concurrent" ],
-	 library_dirs   = [ if installing 
-	       		        then clibdir
-	       		        else cFPTOOLS_TOP_ABS ++ "/hslibs/concurrent" ],
-	 libraries      = [ "HSconcurrent" ],
-	 include_dir    = if installing 
-			    then "" 
-			    else cFPTOOLS_TOP_ABS ++ "/hslibs/concurrent/cbits",
-	 c_include      = "HsConcurrent.h",
-	 package_deps   = [ "lang" ],
-	 extra_ghc_opts = "",
-	 extra_cc_opts  = "",
-	 extra_ld_opts  = ""
-	}
+         Package {
+         import_dirs    = if installing
+                             then [ clibdir ++ "/imports/concurrent" ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/concurrent" ],
+         library_dirs   = if installing
+                             then [ clibdir ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/concurrent" ],
+         libraries      = [ "HSconcurrent" ],
+         include_dirs   = if installing
+                             then []
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/concurrent/cbits" ],
+         c_includes     = [ "HsConcurrent.h" ],
+         package_deps   = [ "lang" ],
+         extra_ghc_opts = [],
+         extra_cc_opts  = [],
+         extra_ld_opts  = []
+        }
        ),
 
        ( "data",
-	 Package {
-	 import_dirs    = if installing 
-	       		     then [ clibdir ++ "/imports/data" ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/data"
-		    	          , cFPTOOLS_TOP_ABS ++ "/hslibs/data/edison"
-		    	          , cFPTOOLS_TOP_ABS ++ "/hslibs/data/edison/Assoc"
-		    	          , cFPTOOLS_TOP_ABS ++ "/hslibs/data/edison/Coll"
-		                  , cFPTOOLS_TOP_ABS ++ "/hslibs/data/edison/Seq" ],
-	 library_dirs   = if installing 
-	       		     then [clibdir ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/data" ],
-	 libraries      = [ "HSdata" ],
-	 include_dir    = if installing 
-			     then "" 
-			     else cFPTOOLS_TOP_ABS ++ "/hslibs/data/cbits",
-	 c_include      = "HsData.h",
-	 package_deps   = [ "lang" ],
-	 extra_ghc_opts = "",
-	 extra_cc_opts  = "",
-	 extra_ld_opts  = ""
-	}
+         Package {
+         import_dirs    = if installing
+                             then [ clibdir ++ "/imports/data" ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/data"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/data/edison"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/data/edison/Assoc"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/data/edison/Coll"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/data/edison/Seq" ],
+         library_dirs   = if installing
+                             then [clibdir ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/data" ],
+         libraries      = [ "HSdata" ],
+         include_dirs   = if installing
+                             then []
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/data/cbits" ],
+         c_includes     = [ "HsData.h" ],
+         package_deps   = [ "lang" ],
+         extra_ghc_opts = [],
+         extra_cc_opts  = [],
+         extra_ld_opts  = []
+        }
        ),
 
        ( "net",
-	 Package {
-	 import_dirs    = if installing 
-	       		     then [ clibdir ++ "/imports/net" ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/net" ],
-	 library_dirs   = if installing 
-	       		     then [ clibdir ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/net"
-				  , cFPTOOLS_TOP_ABS ++ "/hslibs/net/cbits" ],
-	 libraries      = [ "HSnet", "HSnet_cbits" ],
-	 include_dir    = if installing 
-			     then "" 
-			     else cFPTOOLS_TOP_ABS ++ "/hslibs/net/cbits",
-	 c_include      = "HsNet.h",
-	 package_deps   = [ "lang", "text" ],
-	 extra_ghc_opts = "",
-	 extra_cc_opts  = "",
-	 extra_ld_opts  = if postfixMatch "solaris2" cTARGETPLATFORM
-				then "-lnsl -lsocket"
-				else ""
-	}
+         Package {
+         import_dirs    = if installing
+                             then [ clibdir ++ "/imports/net" ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/net" ],
+         library_dirs   = if installing
+                             then [ clibdir ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/net"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/net/cbits" ],
+         libraries      = [ "HSnet", "HSnet_cbits" ],
+         include_dirs   = if installing
+                             then []
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/net/cbits" ],
+         c_includes     = [ "HsNet.h" ],
+         package_deps   = [ "lang", "text" ],
+         extra_ghc_opts = [],
+         extra_cc_opts  = [],
+         extra_ld_opts  = if postfixMatch "solaris2" cTARGETPLATFORM
+                             then [ "-lnsl",  "-lsocket" ]
+                             else []
+        }
        ),
 
        ( "posix",
-	 Package {
-	 import_dirs    = if installing 
-	       		     then [ clibdir ++ "/imports/posix" ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/posix" ],
-	 library_dirs   = if installing 
-	       		     then [ clibdir ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/posix"
-				  , cFPTOOLS_TOP_ABS ++ "/hslibs/posix/cbits" ],
-	 libraries      = [ "HSposix", "HSposix_cbits" ],
-	 include_dir    = if installing 
-			     then "" 
-			     else cFPTOOLS_TOP_ABS ++ "/hslibs/posix/cbits",
-	 c_include      = "HsPosix.h",
-	 package_deps   = [ "lang" ],
-	 extra_ghc_opts = "",
-	 extra_cc_opts  = "",
-	 extra_ld_opts  = ""
-	}
+         Package {
+         import_dirs    = if installing
+                             then [ clibdir ++ "/imports/posix" ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/posix" ],
+         library_dirs   = if installing
+                             then [ clibdir ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/posix"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/posix/cbits" ],
+         libraries      = [ "HSposix", "HSposix_cbits" ],
+         include_dirs   = if installing
+                             then []
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/posix/cbits" ],
+         c_includes     = [ "HsPosix.h" ],
+         package_deps   = [ "lang" ],
+         extra_ghc_opts = [],
+         extra_cc_opts  = [],
+         extra_ld_opts  = []
+        }
        ),
 
        ( "text",
-	 Package {
-	 import_dirs    = if installing 
-	       		     then [ clibdir ++ "/imports/text" ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/text" 
-			 	  , cFPTOOLS_TOP_ABS ++ "/hslibs/text/html" 
-			 	  , cFPTOOLS_TOP_ABS ++ "/hslibs/text/haxml/lib" 
-			 	  , cFPTOOLS_TOP_ABS ++ "/hslibs/text/parsec" ],
-	 library_dirs   = if installing 
-	       		     then [ clibdir ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/text"
-				  , cFPTOOLS_TOP_ABS ++ "/hslibs/text/cbits" ],
-	 libraries      = [ "HStext", "HStext_cbits" ],
-	 include_dir    = if installing 
-			     then "" 
-			     else cFPTOOLS_TOP_ABS ++ "/hslibs/text/cbits",
-	 c_include      = "HsText.h",
-	 package_deps   = [ "lang", "data" ],
-	 extra_ghc_opts = "",
-	 extra_cc_opts  = "",
-	 extra_ld_opts  = ""
-	}
+         Package {
+         import_dirs    = if installing
+                             then [ clibdir ++ "/imports/text" ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/text" 
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/text/html" 
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/text/haxml/lib" 
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/text/parsec" ],
+         library_dirs   = if installing
+                             then [ clibdir ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/text"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/text/cbits" ],
+         libraries      = [ "HStext", "HStext_cbits" ],
+         include_dirs   = if installing
+                             then []
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/text/cbits" ],
+         c_includes     = [ "HsText.h" ],
+         package_deps   = [ "lang", "data" ],
+         extra_ghc_opts = [],
+         extra_cc_opts  = [],
+         extra_ld_opts  = []
+        }
        ),
 
        ( "util",
-	 Package {
-	 import_dirs    = if installing 
-	       		     then [ clibdir ++ "/imports/util" ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/util"
-		    	          , cFPTOOLS_TOP_ABS ++ "/hslibs/util/check" ],
-	 library_dirs   = if installing 
-	       		     then [ clibdir ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/util"
-				  , cFPTOOLS_TOP_ABS ++ "/hslibs/util/cbits" ],
-	 libraries      = [ "HSutil", "HSutil_cbits" ],
-	 include_dir    = if installing 
-			     then "" 
-			     else cFPTOOLS_TOP_ABS ++ "/hslibs/util/cbits",
-	 c_include      = "HsUtil.h",
-	 package_deps   = ["lang", "concurrent", "posix"],
-	 extra_ghc_opts = "",
-	 extra_cc_opts  = "",
-	 extra_ld_opts  = ""
-	}
+         Package {
+         import_dirs    = if installing
+                             then [ clibdir ++ "/imports/util" ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/util"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/util/check" ],
+         library_dirs   = if installing
+                             then [ clibdir ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/util"
+                                  , cFPTOOLS_TOP_ABS ++ "/hslibs/util/cbits" ],
+         libraries      = [ "HSutil", "HSutil_cbits" ],
+         include_dirs   = if installing
+                             then []
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/util/cbits" ],
+         c_includes     = [ "HsUtil.h" ],
+         package_deps   = [ "lang", "concurrent", "posix" ],
+         extra_ghc_opts = [],
+         extra_cc_opts  = [],
+         extra_ld_opts  = []
+        }
        ),
 
-	-- no cbits at the moment, we'll need to add one if this library
-	-- ever calls out to any C libs.
+        -- no cbits at the moment, we'll need to add one if this library
+        -- ever calls out to any C libs.
        ( "hssource",
-	 Package {
-	 import_dirs    = if installing 
-	       		     then [ clibdir ++ "/imports/hssource" ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/hssource" ],
-	 library_dirs   = if installing 
-	       		     then [ clibdir ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/hssource" ],
-	 libraries      = [ "HShssource" ],
-	 include_dir    = "",
-	 c_include      = "",
-	 package_deps   = ["text"],
-	 extra_ghc_opts = "",
-	 extra_cc_opts  = "",
-	 extra_ld_opts  = ""
-	}
+         Package {
+         import_dirs    = if installing
+                             then [ clibdir ++ "/imports/hssource" ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/hssource" ],
+         library_dirs   = if installing
+                             then [ clibdir ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/hssource" ],
+         libraries      = [ "HShssource" ],
+         include_dirs   = [],
+         c_includes     = [],
+         package_deps   = [ "text" ],
+         extra_ghc_opts = [],
+         extra_cc_opts  = [],
+         extra_ld_opts  = []
+        }
        ),
 
        ( "win32",
-	 Package {
-	 import_dirs    = if installing 
-	       		     then [ clibdir ++ "/imports/win32" ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/win32/src" ],
-	 library_dirs   = if installing 
-	       		     then [ clibdir ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hslibs/win32/src" ],
-	 libraries      = [ "HSwin32" ],
-	 include_dir    = "",
-	 c_include      = "",		-- ???
-	 package_deps   = ["lang"],
-	 extra_ghc_opts = "",
-	 extra_cc_opts  = "",
-	 extra_ld_opts  = "-luser32 -lgdi32"
-	}
+         Package {
+         import_dirs    = if installing
+                             then [ clibdir ++ "/imports/win32" ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/win32/src" ],
+         library_dirs   = if installing
+                             then [ clibdir ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hslibs/win32/src" ],
+         libraries      = [ "HSwin32" ],
+         include_dirs   = [],
+         c_includes     = [],           -- ???
+         package_deps   = [ "lang" ],
+         extra_ghc_opts = [],
+         extra_cc_opts  = [],
+         extra_ld_opts  = [ "-luser32",  "-lgdi32" ]
+        }
        ),
 
        ( "com",
-	 Package {
-	 import_dirs    = if installing 
-	       		     then [ clibdir ++ "/imports/com" ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hdirect/lib" ],
-	 library_dirs   = if installing 
-	       		     then [ clibdir ]
-	       		     else [ cFPTOOLS_TOP_ABS ++ "/hdirect/lib" ],
-	 libraries      = [ "HScom" ],
-	 include_dir    = "",
-	 c_include      = "",		-- ???
-	 package_deps   = [ "lang" ],
-	 extra_ghc_opts = "",
-	 extra_cc_opts  = "",
-	 extra_ld_opts  = "-luser32 -lole32 -loleaut32 -ladvapi32"
-	}
+         Package {
+         import_dirs    = if installing
+                             then [ clibdir ++ "/imports/com" ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hdirect/lib" ],
+         library_dirs   = if installing
+                             then [ clibdir ]
+                             else [ cFPTOOLS_TOP_ABS ++ "/hdirect/lib" ],
+         libraries      = [ "HScom" ],
+         include_dirs   = [],
+         c_includes     = [],           -- ???
+         package_deps   = [ "lang" ],
+         extra_ghc_opts = [],
+         extra_cc_opts  = [],
+         extra_ld_opts  = [ "-luser32",  "-lole32",  "-loleaut32", "-ladvapi32" ]
+        }
        )
    ]
 
+ghc_src_dir :: String -> String
 ghc_src_dir path = cFPTOOLS_TOP_ABS ++ '/':cCURRENT_DIR ++ '/':path
 
 prefixMatch :: Eq a => [a] -> [a] -> Bool
-prefixMatch [] str = True
-prefixMatch pat [] = False
+prefixMatch [] _str = True
+prefixMatch _pat [] = False
 prefixMatch (p:ps) (s:ss) | p == s    = prefixMatch ps ss
-			  | otherwise = False
+                          | otherwise = False
 
 postfixMatch :: String -> String -> Bool
 postfixMatch pat str = prefixMatch (reverse pat) (reverse str)