diff --git a/Distribution/PackageDescription.hs b/Distribution/PackageDescription.hs
index 62eb04bcebbf9634e48e431926d14a3c7dd21006..e9c6bcdb59ab528330acc1c9f758ff102ca3fff9 100644
--- a/Distribution/PackageDescription.hs
+++ b/Distribution/PackageDescription.hs
@@ -129,7 +129,8 @@ data PackageDescription
         buildDepends   :: [Dependency],
         -- components
         library        :: Maybe Library,
-        executables    :: [Executable]
+        executables    :: [Executable],
+        otherFiles     :: [FilePath]
     }
     deriving (Show, Read, Eq)
 
@@ -159,7 +160,8 @@ emptyPackageDescription
                       description  = "",
                       category     = "",
                       library      = Nothing,
-                      executables  = []
+                      executables  = [],
+                      otherFiles   = []
                      }
 
 -- |Get all the module names from the libraries in this package
@@ -184,7 +186,7 @@ data BuildInfo = BuildInfo {
         ldOptions         :: [String],  -- ^ options for linker
         frameworks        :: [String], -- ^support frameworks for Mac OS X
         cSources          :: [FilePath],
-        hsSourceDir       :: FilePath, -- ^ where to look for the haskell module hierarchy
+        hsSourceDirs      :: [FilePath], -- ^ where to look for the haskell module hierarchy
         otherModules      :: [String], -- ^ non-exposed or non-main modules
         extensions        :: [Extension],
         extraLibs         :: [String], -- ^ what libraries to link with when compiling a program that uses your package
@@ -202,7 +204,7 @@ emptyBuildInfo = BuildInfo {
                       ldOptions         = [],
                       frameworks        = [],
                       cSources          = [],
-                      hsSourceDir       = currentDir,
+                      hsSourceDirs      = [currentDir],
                       otherModules      = [],
                       extensions        = [],
                       extraLibs         = [],
@@ -286,7 +288,7 @@ unionBuildInfo b1 b2
          ldOptions         = combine ldOptions,
          frameworks        = combine frameworks,
          cSources          = combine cSources,
-         hsSourceDir       = override hsSourceDir "hs-source-dir",
+         hsSourceDirs      = combine hsSourceDirs,
          otherModules      = combine otherModules,
          extensions        = combine extensions,
          extraLibs         = combine extraLibs,
@@ -298,14 +300,6 @@ unionBuildInfo b1 b2
       where 
       combine :: (Eq a) => (BuildInfo -> [a]) -> [a]
       combine f = f b1 ++ f b2
-      override :: (Eq a) => (BuildInfo -> a) -> String -> a
-      override f s
-        | v1 == def = v2
-        | v2 == def = v1
-        | otherwise = error $ "union: Two non-empty fields found in union attempt: " ++ s
-        where v1 = f b1
-              v2 = f b2
-              def = f emptyBuildInfo
 
 -- |Select options for a particular Haskell compiler.
 hcOptions :: CompilerFlavor -> [(CompilerFlavor, [String])] -> [String]
@@ -371,6 +365,8 @@ basicStanzaFields =
  , listField "tested-with"
                            showTestedWith         parseTestedWithQ
                            testedWith             (\val pkg -> pkg{testedWith=val})
+ , listField "other-files" showFilePath           parseFilePathQ
+                           otherFiles             (\val pkg -> pkg{otherFiles=val})
  ]
 
 executableStanzaFields :: [StanzaField Executable]
@@ -415,9 +411,9 @@ binfoFields =
  , listField   "include-dirs"
                            showFilePath       parseFilePathQ
                            includeDirs        (\paths binfo -> binfo{includeDirs=paths})
- , simpleField "hs-source-dir"
+ , listField   "hs-source-dirs"
                            showFilePath       parseFilePathQ
-                           hsSourceDir        (\path  binfo -> binfo{hsSourceDir=path})
+                           hsSourceDirs       (\paths binfo -> binfo{hsSourceDirs=paths})
  , listField   "other-modules"         
                            text               parseModuleNameQ
                            otherModules       (\val binfo -> binfo{otherModules=val})
diff --git a/Distribution/ParseUtils.hs b/Distribution/ParseUtils.hs
index 5b5fa773e4cb5ce25caa1bcd3c0d46551fe28308..31092305b5730b291b4f473c6671f28cd8b0cc4f 100644
--- a/Distribution/ParseUtils.hs
+++ b/Distribution/ParseUtils.hs
@@ -63,7 +63,7 @@ import Distribution.Extension
 import Distribution.Package	( parsePackageName )
 import Distribution.Compat.ReadP as ReadP hiding (get)
 import Distribution.Setup(CompilerFlavor(..))
-
+import Debug.Trace
 import Data.Char
 
 -- -----------------------------------------------------------------------------
@@ -186,7 +186,10 @@ mkStanza []          = return []
 mkStanza ((n,xs):ys) =
   case break (==':') xs of
     (fld', ':':val) -> do
-       let fld = map toLower fld'
+       let fld'' = map toLower fld'
+           fld | fld'' == "hs-source-dir"
+                           = trace "The field \"hs-source-dir\" is deprecated, please use hs-source-dirs." "hs-source-dirs"
+               | otherwise = fld''
        ss <- mkStanza ys
        checkDuplField fld ss
        return ((n, fld, dropWhile isSpace val):ss)
diff --git a/Distribution/PreProcess.hs b/Distribution/PreProcess.hs
index d4140690c3a74f208bcee1dc406c8ddf746363d0..b42642b7a73262e4a17b9dbc98918342f95c6ac5 100644
--- a/Distribution/PreProcess.hs
+++ b/Distribution/PreProcess.hs
@@ -88,7 +88,7 @@ type PreProcessor = FilePath  -- Location of the source file in need of preproce
 type PPSuffixHandler
     = (String, BuildInfo -> LocalBuildInfo -> PreProcessor)
 
--- |Apply preprocessors to the sources from 'hsSourceDir', to obtain
+-- |Apply preprocessors to the sources from 'hsSourceDirs', to obtain
 -- a Haskell source file for each module.
 preprocessSources :: PackageDescription 
 		  -> LocalBuildInfo 
@@ -101,7 +101,7 @@ preprocessSources pkg_descr lbi verbose handlers = do
         setupMessage "Preprocessing library" pkg_descr
         let bi = libBuildInfo lib
 	let biHandlers = localHandlers bi
-	sequence_ [do retVal <- preprocessModule [hsSourceDir bi] modu
+	sequence_ [do retVal <- preprocessModule (hsSourceDirs bi) modu
                                                  verbose builtinSuffixes biHandlers
                       unless (retVal == ExitSuccess)
                              (error $ "got error code while preprocessing: " ++ modu)
@@ -111,9 +111,8 @@ preprocessSources pkg_descr lbi verbose handlers = do
     withExe pkg_descr $ \ theExe -> do
         let bi = buildInfo theExe
 	let biHandlers = localHandlers bi
-	sequence_ [do retVal <- preprocessModule ((hsSourceDir bi)
-                                     :(maybeToList (library pkg_descr
-                                                     >>= Just . hsSourceDir . libBuildInfo)))
+	sequence_ [do retVal <- preprocessModule ((hsSourceDirs bi)
+                                     ++(maybe [] (hsSourceDirs . libBuildInfo) (library pkg_descr)))
                                      modu verbose builtinSuffixes biHandlers
                       unless (retVal == ExitSuccess)
                              (error $ "got error code while preprocessing: " ++ modu)
@@ -161,23 +160,23 @@ removePreprocessedPackage :: PackageDescription
 removePreprocessedPackage  pkg_descr r suff
     = do withLib pkg_descr () (\lib -> do
                      let bi = libBuildInfo lib
-                     removePreprocessed (r `joinFileName` hsSourceDir bi) (libModules pkg_descr) suff)
+                     removePreprocessed (map (joinFileName r) (hsSourceDirs bi)) (libModules pkg_descr) suff)
          withExe pkg_descr (\theExe -> do
                      let bi = buildInfo theExe
-                     removePreprocessed (r `joinFileName` hsSourceDir bi) (otherModules bi) suff)
+                     removePreprocessed (map (joinFileName r) (hsSourceDirs bi)) (otherModules bi) suff)
 
 -- |Remove the preprocessed .hs files. (do we need to get some .lhs files too?)
-removePreprocessed :: FilePath -- ^search Location
+removePreprocessed :: [FilePath] -- ^search Location
                    -> [String] -- ^Modules
                    -> [String] -- ^suffixes
                    -> IO ()
-removePreprocessed searchLoc mods suffixesIn
+removePreprocessed searchLocs mods suffixesIn
     = mapM_ removePreprocessedModule mods
   where removePreprocessedModule m = do
 	    -- collect related files
-	    fs <- moduleToFilePath [searchLoc] m otherSuffixes
+	    fs <- moduleToFilePath searchLocs m otherSuffixes
 	    -- does M.hs also exist?
-	    hs <- moduleToFilePath [searchLoc] m ["hs"]
+	    hs <- moduleToFilePath searchLocs m ["hs"]
 	    unless (null fs) (mapM_ removeFile hs)
 	otherSuffixes = filter (/= "hs") suffixesIn
 
diff --git a/Distribution/Simple.hs b/Distribution/Simple.hs
index d69372cd64a6bc0be1b07810dcd8d7ddd780a35c..8ce4161986e53d9b9d904fa73539231203e85836 100644
--- a/Distribution/Simple.hs
+++ b/Distribution/Simple.hs
@@ -253,7 +253,7 @@ defaultMainWorker pkg_descr_in action args hooks
                       createDirectoryIfMissing True tmpDir
                       createDirectoryIfMissing True targetDir
                       preprocessSources pkg_descr lbi verbose pps
-                      inFiles <- sequence [moduleToFilePath [hsSourceDir bi] m ["hs", "lhs"]
+                      inFiles <- sequence [moduleToFilePath (hsSourceDirs bi) m ["hs", "lhs"]
                                              | m <- exposedModules lib] >>= return . concat
                       mapM_ (mockPP ["-D__HADDOCK__"] pkg_descr bi lbi tmpDir verbose) inFiles
                       let showPkg = showPackageId (package pkg_descr)
@@ -286,7 +286,7 @@ defaultMainWorker pkg_descr_in action args hooks
                        let bi = libBuildInfo lib
                        let mods = exposedModules lib ++ otherModules (libBuildInfo lib)
                        preprocessSources pkg_descr lbi verbose pps
-                       inFiles <- sequence [moduleToFilePath [hsSourceDir bi] m ["hs", "lhs"]
+                       inFiles <- sequence [moduleToFilePath (hsSourceDirs bi) m ["hs", "lhs"]
                                               | m <- mods] >>= return . concat
                        code <- rawSystemVerbose verbose (fromJust mPfe)
                                 ("noplogic":"cpp": (if verbose > 4 then ["-v"] else [])
@@ -308,15 +308,15 @@ defaultMainWorker pkg_descr_in action args hooks
                 removePreprocessedPackage pkg_descr currentDir (ppSuffixes pps)
 
                 -- remove source stubs for library
-                withLib pkg_descr () (\Library{libBuildInfo=BuildInfo{hsSourceDir=dir}} -> do
-                                      s <- sequence [moduleToFilePath [dir] (x ++"_stub") ["h", "c"]
+                withLib pkg_descr () (\Library{libBuildInfo=BuildInfo{hsSourceDirs=dirs}} -> do
+                                      s <- sequence [moduleToFilePath dirs (x ++"_stub") ["h", "c"]
                                                  | x <- libModules pkg_descr ]
                                       mapM_ removeFile (concat s)
                                      )
                 -- remove source stubs for executables
                 withExe pkg_descr (\Executable{modulePath=exeSrcName
-                                              ,buildInfo=BuildInfo{hsSourceDir=dir}} -> do
-                                   s <- sequence [moduleToFilePath [dir] (x ++"_stub") ["h", "c"]
+                                              ,buildInfo=BuildInfo{hsSourceDirs=dirs}} -> do
+                                   s <- sequence [moduleToFilePath dirs (x ++"_stub") ["h", "c"]
                                               | x <- exeModules pkg_descr ]
                                    mapM_ removeFile (concat s)
                                    let (startN, _) = splitFileExt exeSrcName
diff --git a/Distribution/Simple/Build.hs b/Distribution/Simple/Build.hs
index 254cc6d57eccaa87f70e1ba24e8f968a7abdff84..2ab0e8061ff3fb62a07698bc4ddf01e810824a30 100644
--- a/Distribution/Simple/Build.hs
+++ b/Distribution/Simple/Build.hs
@@ -63,7 +63,8 @@ import Distribution.Simple.Utils (rawSystemExit, die, rawSystemPathExit,
                                   mkLibName, dotToSep,
 				  moduleToFilePath, currentDir,
 				  getOptionsFromSource, stripComments,
-                                  smartCopySources
+                                  smartCopySources,
+                                  findFile
                                  )
 
 import Data.Maybe(maybeToList)
@@ -76,7 +77,8 @@ import IO (try)
 import Data.List(nub, sort, isSuffixOf)
 import System.Directory (removeFile)
 import Distribution.Compat.Directory (copyFile,createDirectoryIfMissing)
-import Distribution.Compat.FilePath (splitFilePath, joinFileName, joinFileExt,
+import Distribution.Compat.FilePath (splitFilePath, joinFileName,
+                                splitFileExt, joinFileExt,
 				searchPathSeparator, objExtension, joinPaths, splitFileName)
 import qualified Distribution.Simple.GHCPackageConfig
     as GHC (localPackageConfig, canReadLocalPackageConfig)
@@ -125,10 +127,10 @@ buildGHC pkg_descr lbi verbose = do
   -- Build lib
   withLib pkg_descr () $ \lib -> do
       let libBi = libBuildInfo lib
-          libTargetDir = pref `joinFileName` (hsSourceDir libBi)
+          libTargetDir = pref
       createDirectoryIfMissing True libTargetDir
       -- put hi-boot files into place for mutually recurive modules
-      smartCopySources verbose (hsSourceDir libBi)
+      smartCopySources verbose (hsSourceDirs libBi)
                        libTargetDir (libModules pkg_descr) ["hi-boot"] False
       let ghcArgs = ["-I" ++ dir | dir <- includeDirs libBi]
               ++ ["-optc" ++ opt | opt <- ccOptions libBi]
@@ -137,7 +139,7 @@ buildGHC pkg_descr lbi verbose = do
                   "-odir",  libTargetDir,
                   "-hidir", libTargetDir
                  ]
-              ++ constructGHCCmdLine (compiler lbi) Nothing libBi (packageDeps lbi)
+              ++ constructGHCCmdLine (compiler lbi) [] libBi (packageDeps lbi)
               ++ (libModules pkg_descr)
               ++ (if verbose > 4 then ["-v"] else [])
       unless (null (libModules pkg_descr)) $
@@ -155,7 +157,7 @@ buildGHC pkg_descr lbi verbose = do
                                    | c <- cSources libBi]
 
       -- link:
-      let hObjs = [ (hsSourceDir libBi) `joinFileName` (dotToSep x) `joinFileExt` objExtension
+      let hObjs = [ (dotToSep x) `joinFileExt` objExtension
                   | x <- libModules pkg_descr ]
           cObjs = [ path `joinFileName` file `joinFileExt` objExtension
                   | (path, file, _) <- (map splitFilePath (cSources libBi)) ]
@@ -174,13 +176,13 @@ buildGHC pkg_descr lbi verbose = do
 
   -- build any executables
   withExe pkg_descr $ \ (Executable exeName' modPath exeBi) -> do
-                 createDirectoryIfMissing True (pref `joinFileName` (hsSourceDir exeBi))
-		 let targetDir = pref `joinFileName` hsSourceDir exeBi
+		 let targetDir = pref `joinFileName` exeName'
                  let exeDir = joinPaths targetDir (exeName' ++ "-tmp")
+                 createDirectoryIfMissing True targetDir
                  createDirectoryIfMissing True exeDir
-                 -- put hi-boot files into place for mutually recurive modules
+                 -- put hi-boot files into place for mutually recursive modules
                  -- FIX: what about exeName.hi-boot?
-                 smartCopySources verbose (hsSourceDir exeBi)
+                 smartCopySources verbose (hsSourceDirs exeBi)
                                   exeDir (otherModules exeBi) ["hi-boot"] False
 
                  -- build executables
@@ -194,6 +196,8 @@ buildGHC pkg_descr lbi verbose = do
                                 rawSystemExit verbose ghcPath (cArgs ++ [c])
                                     | c <- cSources exeBi]
 
+                 srcMainFile <- findFile (hsSourceDirs exeBi) modPath
+
                  let cObjs = [ path `joinFileName` file `joinFileExt` objExtension
                                    | (path, file, _) <- (map splitFilePath (cSources exeBi)) ]
                  let binArgs = ["-I" ++ dir | dir <- includeDirs exeBi]
@@ -203,10 +207,10 @@ buildGHC pkg_descr lbi verbose = do
                              "-hidir", exeDir,
                              "-o",     targetDir `joinFileName` exeName'
                             ]
-                         ++ constructGHCCmdLine (compiler lbi) (library pkg_descr >>= Just . hsSourceDir . libBuildInfo)
+                         ++ constructGHCCmdLine (compiler lbi) (maybe [] (hsSourceDirs . libBuildInfo) (library pkg_descr))
                                                 exeBi (packageDeps lbi)
                          ++ [exeDir `joinFileName` x | x <- cObjs]
-                         ++ [hsSourceDir exeBi `joinFileName` modPath]
+                         ++ [srcMainFile]
 			 ++ ldOptions exeBi
 			 ++ ["-l"++lib | lib <- extraLibs exeBi]
 			 ++ ["-L"++libDir | libDir <- extraLibDirs exeBi]
@@ -217,18 +221,18 @@ dirOf :: FilePath -> FilePath
 dirOf f = (\ (x, _, _) -> x) $ (splitFilePath f)
 
 constructGHCCmdLine :: Compiler
-                    -> Maybe FilePath  -- If we're building an executable, we need the library's filepath
+                    -> [FilePath]  -- If we're building an executable, we need the library's filepath
                     -> BuildInfo
                     -> [PackageIdentifier]
                     -> [String]
-constructGHCCmdLine comp mSrcLoc bi deps = 
+constructGHCCmdLine comp srcLocs bi deps = 
     -- Unsupported extensions have already been checked by configure
     let flags = snd $ extensionsToGHCFlag (extensions bi)
      in (if compilerVersion comp > Version [6,4] []
             then ["-fhide-all-packages"]
             else [])
-     ++ ["--make", "-i" ++ hsSourceDir bi ]
-     ++ maybe []  (\l -> ["-i" ++ l]) mSrcLoc
+     ++ ["--make"]
+     ++ ["-i" ++ l | l <- hsSourceDirs bi ++ srcLocs]
      ++ [ "-#include \"" ++ inc ++ "\"" | inc <- includes bi ]
      ++ nub (flags ++ hcOptions GHC (options bi))
      ++ (concat [ ["-package", showPackageId pkg] | pkg <- deps ])
@@ -237,37 +241,37 @@ constructGHCCmdLine comp mSrcLoc bi deps =
 buildHugs :: PackageDescription -> LocalBuildInfo -> Int -> IO ()
 buildHugs pkg_descr lbi verbose = do
     let pref = buildDir lbi
-    withLib pkg_descr () $ (\l -> compileBuildInfo pref Nothing (libModules pkg_descr) (libBuildInfo l))
+    withLib pkg_descr () $ (\l -> compileBuildInfo pref [] (libModules pkg_descr) (libBuildInfo l))
     withExe pkg_descr $ compileExecutable (pref `joinFileName` "programs")
   where
 	compileExecutable :: FilePath -> Executable -> IO ()
 	compileExecutable destDir (exe@Executable {modulePath=mainPath, buildInfo=bi}) = do
             let exeMods = otherModules bi
-	    let srcMainFile = hsSourceDir bi `joinFileName` mainPath
+	    srcMainFile <- findFile (hsSourceDirs bi) mainPath
 	    let exeDir = destDir `joinFileName` exeName exe
 	    let destMainFile = exeDir `joinFileName` hugsMainFilename exe
 	    copyModule (CPP `elem` extensions bi) bi srcMainFile destMainFile
-	    compileBuildInfo exeDir (library pkg_descr >>= Just . hsSourceDir . libBuildInfo) exeMods bi
+	    compileBuildInfo exeDir (maybe [] (hsSourceDirs . libBuildInfo) (library pkg_descr)) exeMods bi
 	    compileFFI bi destMainFile
 	
 	compileBuildInfo :: FilePath
-                         -> Maybe FilePath -- ^The library source dir, if building exes
+                         -> [FilePath] -- ^library source dirs, if building exes
                          -> [String] -- ^Modules
                          -> BuildInfo -> IO ()
-	compileBuildInfo destDir mLibSrcDir mods bi = do
+	compileBuildInfo destDir mLibSrcDirs mods bi = do
 	    -- Pass 1: copy or cpp files from src directory to build directory
 	    let useCpp = CPP `elem` extensions bi
-            let srcDir = hsSourceDir bi
-	    let srcDirs = srcDir:(maybeToList mLibSrcDir)
+	    let srcDirs = hsSourceDirs bi ++ mLibSrcDirs
             when (verbose > 3) (putStrLn $ "Source directories: " ++ show srcDirs)
-	    fileLists <- sequence [moduleToFilePath srcDirs modu suffixes |
-			modu <- mods]
-	    let trimSrcDir
-		  | null srcDir || srcDir == currentDir = id
-		  | otherwise = drop (length srcDir + 1)
-	    let copy_or_cpp f =
-		    copyModule useCpp bi f (destDir `joinFileName` trimSrcDir f)
-	    mapM_ copy_or_cpp (concat fileLists)
+            flip mapM_ mods $ \ m -> do
+                fs <- moduleToFilePath srcDirs m suffixes
+                if null fs then
+                    die ("can't find source for module " ++ m)
+                  else do
+                    let srcFile = head fs
+                    let (_, ext) = splitFileExt srcFile
+                    copyModule useCpp bi srcFile
+                        (destDir `joinFileName` dotToSep m `joinFileExt` ext)
 	    -- Pass 2: compile foreign stubs in build directory
 	    stubsFileLists <- sequence [moduleToFilePath [destDir] modu suffixes |
 			modu <- mods]
@@ -295,7 +299,6 @@ buildHugs pkg_descr lbi verbose = do
                 when (verbose > 2) (putStrLn "Compiling FFI stubs")
 		(_, opts, file_incs) <- getOptionsFromSource file
 		let ghcOpts = hcOptions GHC opts
-		let srcDir = hsSourceDir bi
 		let pkg_incs = ["\"" ++ inc ++ "\"" | inc <- includes bi]
 		let incs = uniq (sort (file_incs ++ includeOpts ghcOpts ++ pkg_incs))
 		let pathFlag = "-P" ++ buildDir lbi ++ [searchPathSeparator]
@@ -304,7 +307,7 @@ buildHugs pkg_descr lbi verbose = do
 		let cArgs =
 			["-I" ++ dir | dir <- includeDirs bi] ++
 			ccOptions bi ++
-			map (joinFileName srcDir) cfiles ++
+			cfiles ++
 			["-L" ++ dir | dir <- extraLibDirs bi] ++
 			ldOptions bi ++
 			["-l" ++ lib | lib <- extraLibs bi] ++
diff --git a/Distribution/Simple/Install.hs b/Distribution/Simple/Install.hs
index 08fc7ee0170ddd09dd7b4013ec422dc44d2d3460..6013dcaa281067e2cbb6f03ead902895e0841c2a 100644
--- a/Distribution/Simple/Install.hs
+++ b/Distribution/Simple/Install.hs
@@ -110,7 +110,7 @@ installExeGhc :: Int      -- ^verbose
 installExeGhc verbose pref buildPref pkg_descr
     = do createDirectoryIfMissing True pref
          withExe pkg_descr $ \ (Executable e _ b) ->
-             copyFileVerbose verbose (buildPref `joinFileName` (hsSourceDir b) `joinFileName` e) (pref `joinFileName` e)
+             copyFileVerbose verbose (buildPref `joinFileName` e) (pref `joinFileName` e)
 
 -- |Install for ghc, .hi and .a
 installLibGHC :: Int      -- ^verbose
@@ -119,7 +119,7 @@ installLibGHC :: Int      -- ^verbose
               -> PackageDescription -> IO ()
 installLibGHC verbose pref buildPref pd@PackageDescription{library=Just l,
                                                    package=p}
-    = do smartCopySources verbose (buildPref `joinFileName` (hsSourceDir $ libBuildInfo l)) pref (libModules pd) ["hi"] True
+    = do smartCopySources verbose [buildPref] pref (libModules pd) ["hi"] True
          let libTargetLoc = mkLibName pref (showPackageId p)
          copyFileVerbose verbose (mkLibName buildPref (showPackageId p)) libTargetLoc
 
@@ -160,7 +160,7 @@ installHugs verbose libPref binPref targetLibPref buildPref pkg_descr = do
         let pkgDir = libPref `joinFileName` "packages"
                     `joinFileName` pkg_name
         try $ removeDirectoryRecursive pkgDir
-        smartCopySources verbose buildPref pkgDir (libModules pkg_descr) hugsInstallSuffixes True
+        smartCopySources verbose [buildPref] pkgDir (libModules pkg_descr) hugsInstallSuffixes True
     let progBuildDir = buildPref `joinFileName` "programs"
     let progInstallDir = libPref `joinFileName` "programs"
     let progTargetDir = targetLibPref `joinFileName` "programs"
@@ -171,7 +171,7 @@ installHugs verbose libPref binPref targetLibPref buildPref pkg_descr = do
         let installDir = progInstallDir `joinFileName` exeName exe
         let targetDir = progTargetDir `joinFileName` exeName exe
         try $ removeDirectoryRecursive installDir
-        smartCopySources verbose buildDir installDir
+        smartCopySources verbose [buildDir] installDir
             ("Main" : otherModules (buildInfo exe)) hugsInstallSuffixes True
 #ifndef mingw32_TARGET_OS
         -- FIX (HUGS): works for Unix only
diff --git a/Distribution/Simple/SrcDist.hs b/Distribution/Simple/SrcDist.hs
index 295cc8f52068810d0d80d5043e8e0da17872b3dc..000399eea2866a7d661f0a40b902d0ab4a893f07 100644
--- a/Distribution/Simple/SrcDist.hs
+++ b/Distribution/Simple/SrcDist.hs
@@ -54,7 +54,7 @@ import Distribution.PackageDescription
          setupMessage, libModules)
 import Distribution.Package (showPackageId)
 import Distribution.Simple.Utils
-        (smartCopySources, die, findPackageDesc, copyFileVerbose)
+        (smartCopySources, die, findPackageDesc, findFile, copyFileVerbose)
 import Distribution.PreProcess (PPSuffixHandler, ppSuffixes, removePreprocessed)
 
 import Control.Monad(when)
@@ -86,9 +86,12 @@ sdist tmpDir targetPref verbose pps pkg_descr = do
   -- move the executables into place
   flip mapM_ (executables pkg_descr) $ \ (Executable _ mainPath exeBi) -> do
     prepareDir verbose targetDir pps [] exeBi
-    copyFileTo verbose targetDir (hsSourceDir exeBi `joinFileName` mainPath)
+    srcMainFile <- findFile (hsSourceDirs exeBi) mainPath
+    copyFileTo verbose targetDir srcMainFile
   when (not (null (licenseFile pkg_descr))) $
     copyFileTo verbose targetDir (licenseFile pkg_descr)
+  flip mapM_ (otherFiles pkg_descr) $ \ fpath -> do
+    copyFileTo verbose targetDir fpath
   -- setup isn't listed in the description file.
   hsExists <- doesFileExist "Setup.hs"
   lhsExists <- doesFileExist "Setup.lhs"
@@ -114,11 +117,10 @@ prepareDir :: Int       -- ^verbose
            -> [String]  -- ^Exposed modules
            -> BuildInfo
            -> IO ()
-prepareDir verbose inPref pps mods BuildInfo{hsSourceDir=srcDir, otherModules=mods', cSources=cfiles}
-    = do let pref = inPref `joinFileName` srcDir
-         let suff = ppSuffixes pps  ++ ["hs", "lhs"]
-         smartCopySources verbose srcDir pref (mods++mods') suff True
-         removePreprocessed pref mods suff
+prepareDir verbose inPref pps mods BuildInfo{hsSourceDirs=srcDirs, otherModules=mods', cSources=cfiles}
+    = do let suff = ppSuffixes pps  ++ ["hs", "lhs"]
+         smartCopySources verbose srcDirs inPref (mods++mods') suff True
+         removePreprocessed (map (joinFileName inPref) srcDirs) mods suff
          mapM_ (copyFileTo verbose inPref) cfiles
 
 copyFileTo :: Int -> FilePath -> FilePath -> IO ()
diff --git a/Distribution/Simple/Utils.hs b/Distribution/Simple/Utils.hs
index 74f840422d658a1dc263db2ad3c3c0f7cdd50ec5..535e6faf43900812c4395d84625be90a59a7110f 100644
--- a/Distribution/Simple/Utils.hs
+++ b/Distribution/Simple/Utils.hs
@@ -58,6 +58,7 @@ module Distribution.Simple.Utils (
 	withTempFile,
 	getOptionsFromSource,
 	stripComments,
+	findFile,
         defaultPackageDesc,
         findPackageDesc,
 	defaultHookedPackageDesc,
@@ -174,6 +175,20 @@ moduleToFilePath pref s possibleSuffixes
           searchModuleToPossiblePaths s' suffs searchP
               = moduleToPossiblePaths searchP s' suffs
 
+-- |Like 'moduleToFilePath', but return the location and the rest of
+-- the path as separate results.
+moduleToFilePath2
+    :: [FilePath] -- ^search locations
+    -> String   -- ^Module Name
+    -> [String] -- ^possible suffixes
+    -> IO [(FilePath, FilePath)] -- ^locations and relative names
+moduleToFilePath2 locs mname possibleSuffixes
+    = filterM exists $
+        [(loc, fname `joinFileExt` ext) | loc <- locs, ext <- possibleSuffixes]
+  where
+    fname = dotToSep mname
+    exists (loc, relname) = doesFileExist (loc `joinFileName` relname)
+
 -- |Get the possible file paths based on this module name.
 moduleToPossiblePaths :: FilePath -- ^search prefix
                       -> String -- ^module name
@@ -183,6 +198,16 @@ moduleToPossiblePaths searchPref s possibleSuffixes =
   let fname = searchPref `joinFileName` (dotToSep s)
   in [fname `joinFileExt` ext | ext <- possibleSuffixes]
 
+findFile :: [FilePath]    -- ^search locations
+         -> FilePath      -- ^File Name
+         -> IO FilePath
+findFile prefPaths locPath = do
+  paths <- filterM doesFileExist [prefPath `joinFileName` locPath | prefPath <- prefPaths]
+  case paths of
+    [path] -> return path
+    []     -> die (locPath ++ " doesn't exists")
+    paths  -> die (locPath ++ "is found in multiple places:" ++ unlines (map ((++) "    ") paths))
+
 dotToSep :: String -> String
 dotToSep = map dts
   where
@@ -195,29 +220,26 @@ dotToSep = map dts
 -- directory.
 
 smartCopySources :: Int      -- ^verbose
-            -> FilePath -- ^build prefix (location of objects)
+            -> [FilePath] -- ^build prefix (location of objects)
             -> FilePath -- ^Target directory
             -> [String] -- ^Modules
             -> [String] -- ^search suffixes
             -> Bool     -- ^Exit if no such modules
             -> IO ()
-smartCopySources verbose pref targetDir sources searchSuffixes exitIfNone
+smartCopySources verbose srcDirs targetDir sources searchSuffixes exitIfNone
     = do createDirectoryIfMissing True targetDir
+         allLocations <- mapM moduleToFPErr sources
+         let copies = [(srcDir `joinFileName` name,
+                        targetDir `joinFileName` name) |
+                       (srcDir, name) <- concat allLocations]
 	 -- Create parent directories for everything:
-         sourceLocs' <- mapM moduleToFPErr sources
-         let sourceLocs = concat $ filter (not . null) sourceLocs'
-         let sourceLocsNoPref -- get rid of the prefix, for target location.
-                 = if null pref || pref == currentDir then sourceLocs
-                   else map (dropPrefix pref) sourceLocs
-	 mapM (createDirectoryIfMissing True)
-		  $ nub [fst (splitFileName (targetDir `joinFileName` x))
-		   | x <- sourceLocsNoPref, fst (splitFileName x) /= "."]
+	 mapM_ (createDirectoryIfMissing True) $ nub $
+             [fst (splitFileName targetFile) | (_, targetFile) <- copies]
 	 -- Put sources into place:
-	 sequence_ [copyFileVerbose verbose x (targetDir `joinFileName` y)
-                      | (x,y) <- (zip sourceLocs sourceLocsNoPref)]
-	 return ()
+	 sequence_ [copyFileVerbose verbose srcFile destFile |
+                    (srcFile, destFile) <- copies]
     where moduleToFPErr m
-              = do p <- moduleToFilePath [pref] m searchSuffixes
+              = do p <- moduleToFilePath2 srcDirs m searchSuffixes
                    when (null p && exitIfNone)
                             (putStrLn ("Error: Could not find module: " ++ m
                                        ++ " with any suffix: " ++ (show searchSuffixes))
@@ -427,8 +449,8 @@ hunitTests
     = let suffixes = ["hs", "lhs"]
           in [TestCase $
 #ifdef mingw32_TARGET_OS
-       do mp1 <- moduleToFilePath "" "Distribution.Simple.Build" suffixes --exists
-          mp2 <- moduleToFilePath "" "Foo.Bar" suffixes    -- doesn't exist
+       do mp1 <- moduleToFilePath [""] "Distribution.Simple.Build" suffixes --exists
+          mp2 <- moduleToFilePath [""] "Foo.Bar" suffixes    -- doesn't exist
           assertEqual "existing not found failed"
                    (Just "Distribution\\Simple\\Build.hs") mp1
           assertEqual "not existing not nothing failed" Nothing mp2,
diff --git a/doc/Cabal.xml b/doc/Cabal.xml
index eb286fb5ed7a2596715c4ead7998325e950832c1..ed77f9b2a70efa1627c1ab307e631127f9e6f3d3 100644
--- a/doc/Cabal.xml
+++ b/doc/Cabal.xml
@@ -455,6 +455,18 @@ Other-Modules:   A, C, Utils</programlisting>
           </listitem>
         </varlistentry>
 
+        <varlistentry>
+          <term>
+            <literal>other-files:</literal>
+            <replaceable>filename list</replaceable>
+          </term>
+          <listitem>
+            <para>A list of additional files to be included in source
+              distributions built with <command>setup sdist</command>
+              (see <xref linkend="setup-sdist"/>).</para>
+          </listitem>
+        </varlistentry>
+
         <varlistentry>
           <term>
             <literal>exposed-modules:</literal>
@@ -514,8 +526,8 @@ Other-Modules:   A, C, Utils</programlisting>
             </term>
             <listitem>
               <para>The name of the source file containing the
-                <literal>Main</literal> module, relative to the
-                <literal>hs-source-dir</literal> directory.</para>
+                <literal>Main</literal> module, relative to one of the
+                directories listed in <literal>hs-source-dirs</literal>.</para>
             </listitem>
           </varlistentry>
         </variablelist>
@@ -561,13 +573,15 @@ Other-Modules:   A, C, Utils</programlisting>
 
           <varlistentry>
             <term>
-              <literal>hs-source-dir:</literal>
-              <replaceable>directory</replaceable>
+              <literal>hs-source-dirs:</literal>
+              <replaceable>directory list</replaceable>
               (default: <quote><literal>.</literal></quote>)
             </term>
             <listitem>
-              <para>The name of root directory of the module
-                hierarchy.</para>
+              <para>Root directories for the module hierarchy.</para>
+
+              <para>For backwards compatibility, the old variant
+                <literal>hs-source-dir</literal> is also recognized.</para>
             </listitem>
           </varlistentry>
           <varlistentry>
@@ -747,10 +761,11 @@ Other-Modules:   A, C, Utils</programlisting>
     <sect2 id="system-dependent">
       <title>System-dependent parameters</title>
 
-      <para>For some packages, implementation details and the build
-        procedure depend on the build environment.  The simple build
-        infrastructure can handle many such situations using a slightly
-        longer <filename>Setup.hs</filename>:</para>
+      <para>For some packages, especially those interfacing with C
+        libraries, implementation details and the build procedure depend
+        on the build environment.  The simple build infrastructure
+        can handle many such situations using a slightly longer
+        <filename>Setup.hs</filename>:</para>
       <programlisting>
 import Distribution.Simple
 main = defaultMainWithHooks defaultUserHooks</programlisting>
@@ -861,6 +876,15 @@ ld-options:  -L/usr/X11R6/lib</programlisting>
           various tests.  This file may be included by C source files
           and preprocessed Haskell source files in the package.</para>
       </example>
+
+      <note>
+        <para>Packages using these features will also need to list
+          additional files such as <filename>configure</filename>,
+          templates for <literal>.buildinfo</literal> files, files named
+          only in <literal>.buildinfo</literal> files, header files and
+          so on in the <literal>other-files</literal> field, to ensure
+          that they are included in source distributions.</para>
+      </note>
     </sect2>
 
     <sect2 id="complex-packages">
@@ -1026,7 +1050,7 @@ runhaskell Setup.hs unregister --gen-script</screen>
       other options will be reported as errors, except in the case of
       the <literal>configure</literal> command.</para>
 
-    <sect2>
+    <sect2 id="setup-configure">
       <title>setup configure</title>
       <para>Prepare to build the package.
         Typically, this step checks that the target platform is capable
@@ -1156,19 +1180,19 @@ runhaskell Setup.hs unregister --gen-script</screen>
 
     </sect2>
 
-    <sect2>
+    <sect2 id="setup-build">
       <title>setup build</title>
       <para>Perform any preprocessing or compilation needed to make this
         package ready for installation.</para>
     </sect2>
 
-    <sect2>
+    <sect2 id="setup-haddock">
       <title>setup haddock</title>
       <para>Build the interface documentation for a library using
         &Haddock;.</para>
     </sect2>
 
-    <sect2>
+    <sect2 id="setup-install">
       <title>setup install</title>
       <para>Copy the files into the install locations and (for library
         packages) register the package with the compiler, i.e. make the
@@ -1195,7 +1219,7 @@ runhaskell Setup.hs unregister --gen-script</screen>
       </variablelist>
     </sect2>
 
-    <sect2>
+    <sect2 id="setup-copy">
       <title>setup copy</title>
       <para>Copy the files without registering them.  This command
         is mainly of use to those creating binary packages.</para>
@@ -1215,7 +1239,7 @@ runhaskell Setup.hs unregister --gen-script</screen>
       </variablelist>
     </sect2>
 
-    <sect2>
+    <sect2 id="setup-register">
       <title>setup register</title>
       <para>Register this package with the compiler, i.e. make the
         modules it contains available to programs.  This only makes sense
@@ -1257,7 +1281,7 @@ runhaskell Setup.hs unregister --gen-script</screen>
       </variablelist>
     </sect2>
 
-    <sect2>
+    <sect2 id="setup-unregister">
       <title>setup unregister</title>
       <para>Deregister this package with the compiler.</para>
 
@@ -1300,16 +1324,21 @@ runhaskell Setup.hs unregister --gen-script</screen>
         steps.</para>
     </sect2>
 
-    <sect2>
+    <sect2 id="setup-sdist">
       <title>setup sdist</title>
       <para>Create a system- and compiler-independent source distribution
         in a file
         <filename><replaceable>package</replaceable>-<replaceable>version</replaceable>.tgz</filename>
-        that can be distributed to package builders.  When unpacked,
-        the commands listed in this section will be available.</para>
-
-      <para>However this command is not yet working in the simple build
-        infrastructure.</para>
+        in the <filename>dist</filename> subdirectory, for distribution
+        to package builders.  When unpacked, the commands listed in this
+        section will be available.</para>
+
+      <para>The files placed in this distribution are the package
+        description file, the setup script, the sources of the modules
+        named in the package description file, and files named in the
+        <literal>license-file</literal>, <literal>main-is</literal>,
+        <literal>c-sources</literal> and <literal>other-files</literal>
+        fields.</para>
     </sect2>
   </sect1>
 
@@ -1319,11 +1348,6 @@ runhaskell Setup.hs unregister --gen-script</screen>
     <para>All these should be fixed in future versions:</para>
 
     <itemizedlist>
-      <listitem>
-        <para>In the simple build infrastructure, the
-          <literal>sdist</literal> command does not work.</para>
-      </listitem>
-
       <listitem>
         <para>The scheme described in <xref linkend="system-dependent"/>
           will not work on Windows without MSYS or Cygwin.</para>
@@ -1334,18 +1358,13 @@ runhaskell Setup.hs unregister --gen-script</screen>
           and building packages for it:</para>
         <itemizedlist>
           <listitem>
-            <para>Cabal does not work with the current stable release
-              (Nov 2003), just the development version.</para>
+            <para>Cabal requires the latest release (Mar 2005).</para>
           </listitem>
 
           <listitem>
             <para>It doesn't work with Windows.</para>
           </listitem>
 
-          <listitem>
-            <para>The <option>--user</option> option is unavailable.</para>
-          </listitem>
-
           <listitem>
             <para>There is no <literal>hugs-pkg</literal> tool.</para>
           </listitem>