From 9530f80db7f3204874aa05a299eb1e94c42a8e93 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Sun, 11 May 2008 15:56:40 +0000
Subject: [PATCH] Make the "dist" directory configurable

---
 Distribution/Simple.hs              |  91 +++++++++++++++--------
 Distribution/Simple/Build.hs        |  23 +++---
 Distribution/Simple/BuildPaths.hs   |  16 ++---
 Distribution/Simple/Configure.hs    |  42 +++++------
 Distribution/Simple/Haddock.hs      |  28 +++++---
 Distribution/Simple/Install.hs      |  12 ++--
 Distribution/Simple/Register.hs     |  54 +++++++-------
 Distribution/Simple/Setup.hs        | 108 ++++++++++++++++++++++++++--
 Distribution/Simple/SetupWrapper.hs |   7 +-
 Distribution/Simple/SrcDist.hs      |   8 ++-
 10 files changed, 264 insertions(+), 125 deletions(-)

diff --git a/Distribution/Simple.hs b/Distribution/Simple.hs
index 4f2cf35b7b..fb2e26657a 100644
--- a/Distribution/Simple.hs
+++ b/Distribution/Simple.hs
@@ -97,7 +97,7 @@ import Distribution.Simple.Configure(getPersistBuildConfig,
                                      configure, writePersistBuildConfig)
 
 import Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..) )
-import Distribution.Simple.BuildPaths ( distPref, srcPref)
+import Distribution.Simple.BuildPaths ( srcPref)
 import Distribution.Simple.Install (install)
 import Distribution.Simple.Haddock (haddock, hscolour)
 import Distribution.Simple.Utils
@@ -208,6 +208,7 @@ allSuffixHandlers hooks
 
 configureAction :: UserHooks -> ConfigFlags -> Args -> IO ()
 configureAction hooks flags args = do
+                let distPref = fromFlag $ configDistPref flags
                 pbi <- preConf hooks args flags
 
                 (mb_pd_file, pkg_descr0) <- confPkgDescr
@@ -223,7 +224,7 @@ configureAction hooks flags args = do
 
                 -- remember the .cabal filename if we know it
                 let localbuildinfo = localbuildinfo0{ pkgDescrFile = mb_pd_file }
-                writePersistBuildConfig localbuildinfo
+                writePersistBuildConfig distPref localbuildinfo
                 
 		let pkg_descr = localPkgDescr localbuildinfo
                 postConf hooks args flags pkg_descr localbuildinfo
@@ -243,7 +244,8 @@ configureAction hooks flags args = do
 
 buildAction :: UserHooks -> BuildFlags -> Args -> IO ()
 buildAction hooks flags args = do
-                lbi <- getBuildConfigIfUpToDate
+                let distPref = fromFlag $ buildDistPref flags
+                lbi <- getBuildConfigIfUpToDate distPref
                 let progs = foldr (uncurry userSpecifyArgs)
                                   (withPrograms lbi) (buildProgramArgs flags)
                 hookedAction preBuild buildHook postBuild
@@ -251,22 +253,32 @@ buildAction hooks flags args = do
                              hooks flags args
 
 makefileAction :: UserHooks -> MakefileFlags -> Args -> IO ()
-makefileAction = hookedAction preMakefile makefileHook postMakefile
-                              getBuildConfigIfUpToDate
+makefileAction hooks flags args
+    = do let distPref = fromFlag $ makefileDistPref flags
+         hookedAction preMakefile makefileHook postMakefile
+                      (getBuildConfigIfUpToDate distPref)
+                      hooks flags args
 
 hscolourAction :: UserHooks -> HscolourFlags -> Args -> IO ()
-hscolourAction = hookedAction preHscolour hscolourHook postHscolour
-                              getBuildConfigIfUpToDate
+hscolourAction hooks flags args
+    = do let distPref = fromFlag $ hscolourDistPref flags
+         hookedAction preHscolour hscolourHook postHscolour
+                      (getBuildConfigIfUpToDate distPref)
+                      hooks flags args
         
 haddockAction :: UserHooks -> HaddockFlags -> Args -> IO ()
-haddockAction = hookedAction preHaddock haddockHook postHaddock
-                             getBuildConfigIfUpToDate
+haddockAction hooks flags args
+    = do let distPref = fromFlag $ haddockDistPref flags
+         hookedAction preHaddock haddockHook postHaddock
+                      (getBuildConfigIfUpToDate distPref)
+                      hooks flags args
 
 cleanAction :: UserHooks -> CleanFlags -> Args -> IO ()
 cleanAction hooks flags args = do
+                let distPref = fromFlag $ cleanDistPref flags
                 pbi <- preClean hooks args flags
 
-                mlbi <- maybeGetPersistBuildConfig
+                mlbi <- maybeGetPersistBuildConfig distPref
                 pdfile <- defaultPackageDesc verbosity
                 ppd <- readPackageDescription verbosity pdfile
                 let pkg_descr0 = flattenPackageDescription ppd
@@ -277,18 +289,25 @@ cleanAction hooks flags args = do
   where verbosity = fromFlag (cleanVerbosity flags)
 
 copyAction :: UserHooks -> CopyFlags -> Args -> IO ()
-copyAction = hookedAction preCopy copyHook postCopy
-                          getBuildConfigIfUpToDate
+copyAction hooks flags args
+    = do let distPref = fromFlag $ copyDistPref flags
+         hookedAction preCopy copyHook postCopy
+                      (getBuildConfigIfUpToDate distPref)
+                      hooks flags args
 
 installAction :: UserHooks -> InstallFlags -> Args -> IO ()
-installAction = hookedAction preInst instHook postInst
-                             getBuildConfigIfUpToDate
+installAction hooks flags args
+    = do let distPref = fromFlag $ installDistPref flags
+         hookedAction preInst instHook postInst
+                      (getBuildConfigIfUpToDate distPref)
+                      hooks flags args
 
 sdistAction :: UserHooks -> SDistFlags -> Args -> IO ()
 sdistAction hooks flags args = do
+                let distPref = fromFlag $ sDistDistPref flags
                 pbi <- preSDist hooks args flags
 
-                mlbi <- maybeGetPersistBuildConfig
+                mlbi <- maybeGetPersistBuildConfig distPref
                 pdfile <- defaultPackageDesc verbosity
                 ppd <- readPackageDescription verbosity pdfile
                 let pkg_descr0 = flattenPackageDescription ppd
@@ -298,19 +317,26 @@ sdistAction hooks flags args = do
                 postSDist hooks args flags pkg_descr mlbi
   where verbosity = fromFlag (sDistVerbosity flags)
 
-testAction :: UserHooks -> () -> Args -> IO ()
-testAction hooks _flags args = do
-                localbuildinfo <- getBuildConfigIfUpToDate
+testAction :: UserHooks -> TestFlags -> Args -> IO ()
+testAction hooks flags args = do
+                let distPref = fromFlag $ testDistPref flags
+                localbuildinfo <- getBuildConfigIfUpToDate distPref
                 let pkg_descr = localPkgDescr localbuildinfo
                 runTests hooks args False pkg_descr localbuildinfo
 
 registerAction :: UserHooks -> RegisterFlags -> Args -> IO ()
-registerAction = hookedAction preReg regHook postReg
-                              getBuildConfigIfUpToDate
+registerAction hooks flags args
+    = do let distPref = fromFlag $ regDistPref flags
+         hookedAction preReg regHook postReg
+                      (getBuildConfigIfUpToDate distPref)
+                      hooks flags args
 
 unregisterAction :: UserHooks -> RegisterFlags -> Args -> IO ()
-unregisterAction = hookedAction preUnreg unregHook postUnreg
-                                getBuildConfigIfUpToDate
+unregisterAction hooks flags args
+    = do let distPref = fromFlag $ regDistPref flags
+         hookedAction preUnreg unregHook postUnreg
+                      (getBuildConfigIfUpToDate distPref)
+                      hooks flags args
 
 hookedAction :: (UserHooks -> Args -> flags -> IO HookedBuildInfo)
         -> (UserHooks -> PackageDescription -> LocalBuildInfo
@@ -330,12 +356,12 @@ hookedAction pre_hook cmd_hook post_hook get_build_config hooks flags args = do
    cmd_hook hooks pkg_descr localbuildinfo hooks flags
    post_hook hooks args flags pkg_descr localbuildinfo
 
-getBuildConfigIfUpToDate :: IO LocalBuildInfo
-getBuildConfigIfUpToDate = do
-   lbi <- getPersistBuildConfig
+getBuildConfigIfUpToDate :: FilePath -> IO LocalBuildInfo
+getBuildConfigIfUpToDate distPref = do
+   lbi <- getPersistBuildConfig distPref
    case pkgDescrFile lbi of
      Nothing -> return ()
-     Just pkg_descr_file -> checkPersistBuildConfig pkg_descr_file
+     Just pkg_descr_file -> checkPersistBuildConfig distPref pkg_descr_file
    return lbi
 
 -- --------------------------------------------------------------------------
@@ -343,10 +369,11 @@ getBuildConfigIfUpToDate = do
 
 clean :: PackageDescription -> CleanFlags -> IO ()
 clean pkg_descr flags = do
+    let distPref = fromFlag $ cleanDistPref flags
     notice verbosity "cleaning..."
 
     maybeConfig <- if fromFlag (cleanSaveConf flags)
-                     then maybeGetPersistBuildConfig
+                     then maybeGetPersistBuildConfig distPref
                      else return Nothing
 
     -- remove the whole dist/ directory rather than tracking exactly what files
@@ -362,7 +389,7 @@ clean pkg_descr flags = do
     mapM_ removeFileOrDirectory (extraTmpFiles pkg_descr)
 
     -- If the user wanted to save the config, write it back
-    maybe (return ()) writePersistBuildConfig maybeConfig
+    maybe (return ()) (writePersistBuildConfig distPref) maybeConfig
 
   where
         removeFileOrDirectory :: FilePath -> IO ()
@@ -387,7 +414,7 @@ simpleUserHooks =
        makefileHook = defaultMakefileHook,
        copyHook  = \desc lbi _ f -> install desc lbi f, -- has correct 'copy' behavior with params
        instHook  = defaultInstallHook,
-       sDistHook = \p l h f -> sdist p l f srcPref distPref (allSuffixHandlers h),
+       sDistHook = \p l h f -> sdist p l f srcPref (allSuffixHandlers h),
        cleanHook = \p _ _ f -> clean p f,
        hscolourHook = \p l h f -> hscolour p l (allSuffixHandlers h) f,
        haddockHook  = \p l h f -> haddock  p l (allSuffixHandlers h) f,
@@ -484,16 +511,18 @@ defaultInstallHook pkg_descr localbuildinfo _ flags = do
 defaultBuildHook :: PackageDescription -> LocalBuildInfo
 	-> UserHooks -> BuildFlags -> IO ()
 defaultBuildHook pkg_descr localbuildinfo hooks flags = do
+  let distPref = fromFlag $ buildDistPref flags
   build pkg_descr localbuildinfo flags (allSuffixHandlers hooks)
   when (hasLibs pkg_descr) $
-      writeInstalledConfig pkg_descr localbuildinfo False Nothing
+      writeInstalledConfig distPref pkg_descr localbuildinfo False Nothing
 
 defaultMakefileHook :: PackageDescription -> LocalBuildInfo
 	-> UserHooks -> MakefileFlags -> IO ()
 defaultMakefileHook pkg_descr localbuildinfo hooks flags = do
+  let distPref = fromFlag $ makefileDistPref flags
   makefile pkg_descr localbuildinfo flags (allSuffixHandlers hooks)
   when (hasLibs pkg_descr) $
-      writeInstalledConfig pkg_descr localbuildinfo False Nothing
+      writeInstalledConfig distPref pkg_descr localbuildinfo False Nothing
 
 defaultRegHook :: PackageDescription -> LocalBuildInfo
 	-> UserHooks -> RegisterFlags -> IO ()
diff --git a/Distribution/Simple/Build.hs b/Distribution/Simple/Build.hs
index 4b0583bd0a..d4a9c8bb57 100644
--- a/Distribution/Simple/Build.hs
+++ b/Distribution/Simple/Build.hs
@@ -91,8 +91,9 @@ build    :: PackageDescription  -- ^mostly information from the .cabal file
          -> [ PPSuffixHandler ] -- ^preprocessors to run before compiling
          -> IO ()
 build pkg_descr lbi flags suffixes = do
-  let verbosity = fromFlag (buildVerbosity flags)
-  initialBuildSteps pkg_descr lbi verbosity suffixes
+  let distPref  = fromFlag (buildDistPref flags)
+      verbosity = fromFlag (buildVerbosity flags)
+  initialBuildSteps distPref pkg_descr lbi verbosity suffixes
   setupMessage verbosity "Building" (packageId pkg_descr)
   case compilerFlavor (compiler lbi) of
     GHC  -> GHC.build  pkg_descr lbi verbosity
@@ -107,8 +108,9 @@ makefile :: PackageDescription  -- ^mostly information from the .cabal file
          -> [ PPSuffixHandler ] -- ^preprocessors to run before compiling
          -> IO ()
 makefile pkg_descr lbi flags suffixes = do
-  let verbosity = fromFlag (makefileVerbosity flags)
-  initialBuildSteps pkg_descr lbi verbosity suffixes
+  let distPref  = fromFlag (makefileDistPref flags)
+      verbosity = fromFlag (makefileVerbosity flags)
+  initialBuildSteps distPref pkg_descr lbi verbosity suffixes
   when (not (hasLibs pkg_descr)) $
       die ("Makefile is only supported for libraries, currently.")
   setupMessage verbosity "Generating Makefile" (packageId pkg_descr)
@@ -117,12 +119,13 @@ makefile pkg_descr lbi flags suffixes = do
     _    -> die ("Generating a Makefile is not supported for this compiler.")
 
 
-initialBuildSteps :: PackageDescription  -- ^mostly information from the .cabal file
+initialBuildSteps :: FilePath -- ^"dist" prefix
+                  -> PackageDescription  -- ^mostly information from the .cabal file
                   -> LocalBuildInfo -- ^Configuration information
                   -> Verbosity -- ^The verbosity to use
                   -> [ PPSuffixHandler ] -- ^preprocessors to run before compiling
                   -> IO ()
-initialBuildSteps pkg_descr lbi verbosity suffixes = do
+initialBuildSteps distPref pkg_descr lbi verbosity suffixes = do
   -- check that there's something to build
   let buildInfos =
           map libBuildInfo (maybeToList (library pkg_descr)) ++
@@ -135,7 +138,7 @@ initialBuildSteps pkg_descr lbi verbosity suffixes = do
 
   -- construct and write the Paths_<pkg>.hs file
   createDirectoryIfMissingVerbose verbosity True (autogenModulesDir lbi)
-  buildPathsModule pkg_descr lbi
+  buildPathsModule distPref pkg_descr lbi
 
   preprocessSources pkg_descr lbi False verbosity suffixes
 
@@ -147,8 +150,8 @@ initialBuildSteps pkg_descr lbi verbosity suffixes = do
 autogenModulesDir :: LocalBuildInfo -> String
 autogenModulesDir lbi = buildDir lbi </> "autogen"
 
-buildPathsModule :: PackageDescription -> LocalBuildInfo -> IO ()
-buildPathsModule pkg_descr lbi =
+buildPathsModule :: FilePath -> PackageDescription -> LocalBuildInfo -> IO ()
+buildPathsModule distPref pkg_descr lbi =
    let pragmas
 	| absolute || isHugs = ""
 	| otherwise =
@@ -215,7 +218,7 @@ buildPathsModule pkg_descr lbi =
 	  get_prefix_stuff++
 	  "\n"++
 	  filename_stuff
-   in do btime <- getModificationTime localBuildInfoFile
+   in do btime <- getModificationTime (localBuildInfoFile distPref)
    	 exists <- doesFileExist paths_filepath
    	 ptime <- if exists
    	            then getModificationTime paths_filepath
diff --git a/Distribution/Simple/BuildPaths.hs b/Distribution/Simple/BuildPaths.hs
index cd3feb2e01..7922eadbc3 100644
--- a/Distribution/Simple/BuildPaths.hs
+++ b/Distribution/Simple/BuildPaths.hs
@@ -42,7 +42,7 @@ THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
 OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}
 
 module Distribution.Simple.BuildPaths (
-    distPref, srcPref,
+    defaultDistPref, srcPref,
     hscolourPref, haddockPref,
     autogenModulesDir,
 
@@ -68,6 +68,7 @@ import Distribution.Compiler
          ( CompilerId(..) )
 import Distribution.PackageDescription (PackageDescription)
 import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(buildDir))
+import Distribution.Simple.Setup (defaultDistPref)
 import Distribution.Text
          ( display )
 import Distribution.System (OS(..), buildOS)
@@ -75,17 +76,14 @@ import Distribution.System (OS(..), buildOS)
 -- ---------------------------------------------------------------------------
 -- Build directories and files
 
-distPref :: FilePath
-distPref = "dist"
+srcPref :: FilePath -> FilePath
+srcPref distPref = distPref </> "src"
 
-srcPref :: FilePath
-srcPref = distPref </> "src"
-
-hscolourPref :: PackageDescription -> FilePath
+hscolourPref :: FilePath -> PackageDescription -> FilePath
 hscolourPref = haddockPref
 
-haddockPref :: PackageDescription -> FilePath
-haddockPref pkg_descr
+haddockPref :: FilePath -> PackageDescription -> FilePath
+haddockPref distPref pkg_descr
     = distPref </> "doc" </> "html" </> packageName pkg_descr
 
 -- |The directory in which we put auto-generated modules
diff --git a/Distribution/Simple/Configure.hs b/Distribution/Simple/Configure.hs
index 4ef1976a82..a281457348 100644
--- a/Distribution/Simple/Configure.hs
+++ b/Distribution/Simple/Configure.hs
@@ -91,8 +91,6 @@ import Distribution.Simple.InstallDirs
 import Distribution.Simple.LocalBuildInfo
     ( LocalBuildInfo(..), absoluteInstallDirs
     , prefixRelativeInstallDirs )
-import Distribution.Simple.BuildPaths
-    ( distPref )
 import Distribution.Simple.Utils
     ( die, warn, info, setupMessage, createDirectoryIfMissingVerbose
     , intercalate, comparing, cabalVersion, cabalBootstrapping )
@@ -182,30 +180,31 @@ tryGetConfigStateFile filename = do
              ++ ") which is probably the cause of the problem."
 
 -- internal function
-tryGetPersistBuildConfig :: IO (Either String LocalBuildInfo)
-tryGetPersistBuildConfig = tryGetConfigStateFile localBuildInfoFile
+tryGetPersistBuildConfig :: FilePath -> IO (Either String LocalBuildInfo)
+tryGetPersistBuildConfig distPref
+    = tryGetConfigStateFile (localBuildInfoFile distPref)
 
 -- |Read the 'localBuildInfoFile'.  Error if it doesn't exist.  Also
 -- fail if the file containing LocalBuildInfo is older than the .cabal
 -- file, indicating that a re-configure is required.
-getPersistBuildConfig :: IO LocalBuildInfo
-getPersistBuildConfig = do
-  lbi <- tryGetPersistBuildConfig
+getPersistBuildConfig :: FilePath -> IO LocalBuildInfo
+getPersistBuildConfig distPref = do
+  lbi <- tryGetPersistBuildConfig distPref
   either die return lbi
 
 -- |Try to read the 'localBuildInfoFile'.
-maybeGetPersistBuildConfig :: IO (Maybe LocalBuildInfo)
-maybeGetPersistBuildConfig = do
-  lbi <- tryGetPersistBuildConfig
+maybeGetPersistBuildConfig :: FilePath -> IO (Maybe LocalBuildInfo)
+maybeGetPersistBuildConfig distPref = do
+  lbi <- tryGetPersistBuildConfig distPref
   return $ either (const Nothing) Just lbi
 
 -- |After running configure, output the 'LocalBuildInfo' to the
 -- 'localBuildInfoFile'.
-writePersistBuildConfig :: LocalBuildInfo -> IO ()
-writePersistBuildConfig lbi = do
+writePersistBuildConfig :: FilePath -> LocalBuildInfo -> IO ()
+writePersistBuildConfig distPref lbi = do
   createDirectoryIfMissing False distPref
-  writeFile localBuildInfoFile $ showHeader pkgid
-                              ++ '\n' : show lbi
+  writeFile (localBuildInfoFile distPref)
+            (showHeader pkgid ++ '\n' : show lbi)
   where
     pkgid   = packageId (localPkgDescr lbi)
 
@@ -240,16 +239,16 @@ parseHeader header = case words header of
 
 -- |Check that localBuildInfoFile is up-to-date with respect to the
 -- .cabal file.
-checkPersistBuildConfig :: FilePath -> IO ()
-checkPersistBuildConfig pkg_descr_file = do
+checkPersistBuildConfig :: FilePath -> FilePath -> IO ()
+checkPersistBuildConfig distPref pkg_descr_file = do
   t0 <- getModificationTime pkg_descr_file
-  t1 <- getModificationTime localBuildInfoFile
+  t1 <- getModificationTime $ localBuildInfoFile distPref
   when (t0 > t1) $
     die (pkg_descr_file ++ " has been changed, please re-configure.")
 
 -- |@dist\/setup-config@
-localBuildInfoFile :: FilePath
-localBuildInfoFile = distPref </> "setup-config"
+localBuildInfoFile :: FilePath -> FilePath
+localBuildInfoFile distPref = distPref </> "setup-config"
 
 -- -----------------------------------------------------------------------------
 -- * Configuration
@@ -261,7 +260,8 @@ configure :: ( Either GenericPackageDescription PackageDescription
              , HookedBuildInfo) 
           -> ConfigFlags -> IO LocalBuildInfo
 configure (pkg_descr0, pbi) cfg
-  = do  let verbosity = fromFlag (configVerbosity cfg)
+  = do  let distPref = fromFlag (configDistPref cfg)
+            verbosity = fromFlag (configVerbosity cfg)
 
 	setupMessage verbosity "Configuring"
                      (packageId (either packageDescription id pkg_descr0))
@@ -369,7 +369,7 @@ configure (pkg_descr0, pbi) cfg
                          | (name, uses) <- inconsistencies
                          , (pkg, ver) <- uses ]
 
-	removeInstalledConfig
+	removeInstalledConfig distPref
 
 	-- installation directories
 	defaultDirs <- defaultInstallDirs flavor userInstall (hasLibs pkg_descr)
diff --git a/Distribution/Simple/Haddock.hs b/Distribution/Simple/Haddock.hs
index 40db0cf094..1bdad5d3a5 100644
--- a/Distribution/Simple/Haddock.hs
+++ b/Distribution/Simple/Haddock.hs
@@ -69,7 +69,7 @@ import Distribution.Simple.InstallDirs (InstallDirs(..), PathTemplate,
                                         substPathTemplate,
                                         initialPathTemplateEnv)
 import Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..) )
-import Distribution.Simple.BuildPaths ( distPref, haddockPref, haddockName,
+import Distribution.Simple.BuildPaths ( haddockPref, haddockName,
                                         hscolourPref, autogenModulesDir )
 import qualified Distribution.Simple.PackageIndex as PackageIndex
          ( lookupPackageId )
@@ -111,7 +111,8 @@ haddock pkg_descr _ _ haddockFlags
         ++ "--executables."
 
 haddock pkg_descr lbi suffixes flags = do
-    let doExes   = fromFlag (haddockExecutables flags)
+    let distPref = fromFlag (haddockDistPref flags)
+        doExes   = fromFlag (haddockExecutables flags)
         hsColour = fromFlag (haddockHscolour flags)
     when hsColour $ hscolour pkg_descr lbi suffixes defaultHscolourFlags {
       hscolourCSS         = haddockHscolourCss flags,
@@ -124,7 +125,8 @@ haddock pkg_descr lbi suffixes flags = do
 
     let tmpDir = buildDir lbi </> "tmp"
     createDirectoryIfMissingVerbose verbosity True tmpDir
-    createDirectoryIfMissingVerbose verbosity True $ haddockPref pkg_descr
+    createDirectoryIfMissingVerbose verbosity True $
+        haddockPref distPref pkg_descr
     preprocessSources pkg_descr lbi False verbosity suffixes
 
     setupMessage verbosity "Running Haddock for" (packageId pkg_descr)
@@ -182,7 +184,8 @@ haddock pkg_descr lbi suffixes flags = do
           then ("-B" ++ ghcLibDir) : map ("--optghc=" ++) (ghcSimpleOptions lbi bi preprocessDir)
           else []
 
-    when isVersion2 $ initialBuildSteps pkg_descr lbi verbosity suffixes
+    when isVersion2 $
+        initialBuildSteps distPref pkg_descr lbi verbosity suffixes
 
     withLib pkg_descr () $ \lib -> do
         let bi = libBuildInfo lib
@@ -202,7 +205,8 @@ haddock pkg_descr lbi suffixes flags = do
           let targets
                 | isVersion2 = modules
                 | otherwise  = replaceLitExts inFiles
-          let haddockFile = haddockPref pkg_descr </> haddockName pkg_descr
+          let haddockFile = haddockPref distPref pkg_descr
+                        </> haddockName pkg_descr
           -- FIX: replace w/ rawSystemProgramConf?
           let hideArgs | fromFlag (haddockInternal flags) = []
                        | otherwise                        = map ("--hide=" ++) (otherModules bi)
@@ -210,7 +214,7 @@ haddock pkg_descr lbi suffixes flags = do
                            | otherwise                        = []
           rawSystemProgram verbosity confHaddock
                   ([ outputFlag
-                   , "--odir=" ++ haddockPref pkg_descr
+                   , "--odir=" ++ haddockPref distPref pkg_descr
                    , "--title=" ++ showPkg ++ subtitle ++ titleComment
                    , "--dump-interface=" ++ haddockFile
                    , "--prologue=" ++ prologFileName ]
@@ -226,11 +230,11 @@ haddock pkg_descr lbi suffixes flags = do
                    ++ targets
                   )
           notice verbosity $ "Documentation created: "
-                          ++ (haddockPref pkg_descr </> "index.html")
+                          ++ (haddockPref distPref pkg_descr </> "index.html")
 
     withExe pkg_descr $ \exe -> when doExes $ do
         let bi = buildInfo exe
-            exeTargetDir = haddockPref pkg_descr </> exeName exe
+            exeTargetDir = haddockPref distPref pkg_descr </> exeName exe
         createDirectoryIfMissingVerbose verbosity True exeTargetDir
         inFiles' <- getModulePaths lbi bi (otherModules bi)
         srcMainPath <- findFile (hsSourceDirs bi) (modulePath exe)
@@ -350,10 +354,12 @@ ghcSimpleOptions lbi bi mockDir
 
 hscolour :: PackageDescription -> LocalBuildInfo -> [PPSuffixHandler] -> HscolourFlags -> IO ()
 hscolour pkg_descr lbi suffixes flags = do
+    let distPref = fromFlag $ hscolourDistPref flags
     (hscolourProg, _) <- requireProgram verbosity hscolourProgram
                          (orLaterVersion (Version [1,8] [])) (withPrograms lbi)
 
-    createDirectoryIfMissingVerbose verbosity True $ hscolourPref pkg_descr
+    createDirectoryIfMissingVerbose verbosity True $
+        hscolourPref distPref pkg_descr
     preprocessSources pkg_descr lbi False verbosity suffixes
 
     setupMessage verbosity "Running hscolour for" (packageId pkg_descr)
@@ -362,7 +368,7 @@ hscolour pkg_descr lbi suffixes flags = do
     withLib pkg_descr () $ \lib -> when (isJust $ library pkg_descr) $ do
         let bi = libBuildInfo lib
             modules = PD.exposedModules lib ++ otherModules bi
-	    outputDir = hscolourPref pkg_descr </> "src"
+	    outputDir = hscolourPref distPref pkg_descr </> "src"
 	createDirectoryIfMissingVerbose verbosity True outputDir
 	copyCSS hscolourProg outputDir
         inFiles <- getModulePaths lbi bi modules
@@ -374,7 +380,7 @@ hscolour pkg_descr lbi suffixes flags = do
     withExe pkg_descr $ \exe -> when doExes $ do
         let bi = buildInfo exe
             modules = "Main" : otherModules bi
-            outputDir = hscolourPref pkg_descr </> exeName exe </> "src"
+            outputDir = hscolourPref distPref pkg_descr </> exeName exe </> "src"
         createDirectoryIfMissingVerbose verbosity True outputDir
         copyCSS hscolourProg outputDir
         srcMainPath <- findFile (hsSourceDirs bi) (modulePath exe)
diff --git a/Distribution/Simple/Install.hs b/Distribution/Simple/Install.hs
index 7c128ee7c1..d45fcfb472 100644
--- a/Distribution/Simple/Install.hs
+++ b/Distribution/Simple/Install.hs
@@ -80,7 +80,8 @@ install :: PackageDescription -- ^information from the .cabal file
         -> CopyFlags -- ^flags sent to copy or install
         -> IO ()
 install pkg_descr lbi flags = do
-  let verbosity = fromFlag (copyVerbosity flags)
+  let distPref  = fromFlag (copyDistPref flags)
+      verbosity = fromFlag (copyVerbosity flags)
       copydest  = fromFlag (copyDest flags)
       InstallDirs {
          bindir     = binPref,
@@ -97,8 +98,8 @@ install pkg_descr lbi flags = do
       progPrefixPref = substPathTemplate pkg_descr lbi (progPrefix lbi)
       progSuffixPref = substPathTemplate pkg_descr lbi (progSuffix lbi)
   
-  docExists <- doesDirectoryExist $ haddockPref pkg_descr
-  info verbosity ("directory " ++ haddockPref pkg_descr ++
+  docExists <- doesDirectoryExist $ haddockPref distPref pkg_descr
+  info verbosity ("directory " ++ haddockPref distPref pkg_descr ++
                   " does exist: " ++ show docExists)
   flip mapM_ (dataFiles pkg_descr) $ \ file -> do
       let dir = takeDirectory file
@@ -106,7 +107,8 @@ install pkg_descr lbi flags = do
       copyFileVerbose verbosity file (dataPref </> file)
   when docExists $ do
       createDirectoryIfMissingVerbose verbosity True htmlPref
-      copyDirectoryRecursiveVerbose verbosity (haddockPref pkg_descr) htmlPref
+      copyDirectoryRecursiveVerbose verbosity
+          (haddockPref distPref pkg_descr) htmlPref
       -- setPermissionsRecursive [Read] htmlPref
       -- The haddock interface file actually already got installed
       -- in the recursive copy, but now we install it where we actually
@@ -114,7 +116,7 @@ install pkg_descr lbi flags = do
       -- copy in htmlPref first.
       createDirectoryIfMissingVerbose verbosity True interfacePref
       copyFileVerbose verbosity
-                      (haddockPref pkg_descr </> haddockName pkg_descr)
+                      (haddockPref distPref pkg_descr </> haddockName pkg_descr)
                       (interfacePref </> haddockName pkg_descr)
 
   let lfile = licenseFile pkg_descr
diff --git a/Distribution/Simple/Register.hs b/Distribution/Simple/Register.hs
index 990a44ffd0..2b230c88f8 100644
--- a/Distribution/Simple/Register.hs
+++ b/Distribution/Simple/Register.hs
@@ -52,7 +52,7 @@ module Distribution.Simple.Register (
 import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..),
                                            InstallDirs(..),
 					   absoluteInstallDirs)
-import Distribution.Simple.BuildPaths (distPref, haddockName)
+import Distribution.Simple.BuildPaths (haddockName)
 import Distribution.Simple.Compiler
          ( CompilerFlavor(..), compilerFlavor, PackageDB(..) )
 import Distribution.Simple.Program (ConfiguredProgram, programPath,
@@ -108,7 +108,8 @@ register pkg_descr lbi regFlags
     setupMessage (fromFlag $ regVerbosity regFlags) "No package to register" (packageId pkg_descr)
     return ()
   | otherwise = do
-    let isWindows = case buildOS of Windows -> True; _ -> False
+    let distPref = fromFlag $ regDistPref regFlags
+        isWindows = case buildOS of Windows -> True; _ -> False
         genScript = fromFlag (regGenScript regFlags)
         genPkgConf = isJust (fromFlag (regGenPkgConf regFlags))
         genPkgConfigDefault = display (packageId pkg_descr) <.> "conf"
@@ -132,12 +133,12 @@ register pkg_descr lbi regFlags
           SpecificPackageDB db -> return ["--package-conf=" ++ db]
 
 	let instConf | genPkgConf = genPkgConfigFile
-                     | inplace    = inplacePkgConfigFile
-		     | otherwise  = installedPkgConfigFile
+                     | inplace    = inplacePkgConfigFile distPref
+		     | otherwise  = installedPkgConfigFile distPref
 
         when (genPkgConf || not genScript) $ do
           info verbosity ("create " ++ instConf)
-          writeInstalledConfig pkg_descr lbi inplace (Just instConf)
+          writeInstalledConfig distPref pkg_descr lbi inplace (Just instConf)
 
         let register_flags   = let conf = if genScript && not isWindows
 		                             then ["-"]
@@ -150,7 +151,7 @@ register pkg_descr lbi regFlags
         case () of
           _ | genPkgConf -> return ()
             | genScript ->
-              do cfg <- showInstalledConfig pkg_descr lbi inplace
+              do cfg <- showInstalledConfig distPref pkg_descr lbi inplace
                  rawSystemPipe pkgTool regScriptLocation cfg allFlags
           _ -> rawSystemProgram verbosity pkgTool allFlags
 
@@ -158,7 +159,7 @@ register pkg_descr lbi regFlags
 	when inplace $ die "--inplace is not supported with Hugs"
         let installDirs = absoluteInstallDirs pkg_descr lbi NoCopyDest
 	createDirectoryIfMissingVerbose verbosity True (libdir installDirs)
-	copyFileVerbose verbosity installedPkgConfigFile
+	copyFileVerbose verbosity (installedPkgConfigFile distPref)
 	    (libdir installDirs </> "package.conf")
       JHC -> notice verbosity "registering for JHC (nothing to do)"
       NHC -> notice verbosity "registering nhc98 (nothing to do)"
@@ -169,26 +170,26 @@ register pkg_descr lbi regFlags
 
 -- |Register doesn't drop the register info file, it must be done in a
 -- separate step.
-writeInstalledConfig :: PackageDescription -> LocalBuildInfo -> Bool
-                     -> Maybe FilePath -> IO ()
-writeInstalledConfig pkg_descr lbi inplace instConfOverride = do
-  pkg_config <- showInstalledConfig pkg_descr lbi inplace
-  let instConfDefault | inplace   = inplacePkgConfigFile
-                      | otherwise = installedPkgConfigFile
+writeInstalledConfig :: FilePath -> PackageDescription -> LocalBuildInfo
+                     -> Bool -> Maybe FilePath -> IO ()
+writeInstalledConfig distPref pkg_descr lbi inplace instConfOverride = do
+  pkg_config <- showInstalledConfig distPref pkg_descr lbi inplace
+  let instConfDefault | inplace   = inplacePkgConfigFile distPref
+                      | otherwise = installedPkgConfigFile distPref
       instConf = fromMaybe instConfDefault instConfOverride
   writeFile instConf (pkg_config ++ "\n")
 
 -- |Create a string suitable for writing out to the package config file
-showInstalledConfig :: PackageDescription -> LocalBuildInfo -> Bool
+showInstalledConfig :: FilePath -> PackageDescription -> LocalBuildInfo -> Bool
   -> IO String
-showInstalledConfig pkg_descr lbi inplace
-    = do cfg <- mkInstalledPackageInfo pkg_descr lbi inplace
+showInstalledConfig distPref pkg_descr lbi inplace
+    = do cfg <- mkInstalledPackageInfo distPref pkg_descr lbi inplace
          return (showInstalledPackageInfo cfg)
 
-removeInstalledConfig :: IO ()
-removeInstalledConfig = do
-  try $ removeFile installedPkgConfigFile
-  try $ removeFile inplacePkgConfigFile
+removeInstalledConfig :: FilePath -> IO ()
+removeInstalledConfig distPref = do
+  try $ removeFile $ installedPkgConfigFile distPref
+  try $ removeFile $ inplacePkgConfigFile distPref
   return ()
 
 removeRegScripts :: IO ()
@@ -197,21 +198,22 @@ removeRegScripts = do
   try $ removeFile unregScriptLocation
   return ()
 
-installedPkgConfigFile :: FilePath
-installedPkgConfigFile = distPref </> "installed-pkg-config"
+installedPkgConfigFile :: FilePath -> FilePath
+installedPkgConfigFile distPref = distPref </> "installed-pkg-config"
 
-inplacePkgConfigFile :: FilePath
-inplacePkgConfigFile = distPref </> "inplace-pkg-config"
+inplacePkgConfigFile :: FilePath -> FilePath
+inplacePkgConfigFile distPref = distPref </> "inplace-pkg-config"
 
 -- -----------------------------------------------------------------------------
 -- Making the InstalledPackageInfo
 
 mkInstalledPackageInfo
-	:: PackageDescription
+	:: FilePath
+    -> PackageDescription
 	-> LocalBuildInfo
 	-> Bool
 	-> IO InstalledPackageInfo
-mkInstalledPackageInfo pkg_descr lbi inplace = do 
+mkInstalledPackageInfo distPref pkg_descr lbi inplace = do 
   pwd <- getCurrentDirectory
   let 
 	lib = fromJust (library pkg_descr) -- checked for Nothing earlier
diff --git a/Distribution/Simple/Setup.hs b/Distribution/Simple/Setup.hs
index 5fca8c848a..93606d7f4c 100644
--- a/Distribution/Simple/Setup.hs
+++ b/Distribution/Simple/Setup.hs
@@ -54,10 +54,12 @@ module Distribution.Simple.Setup (
   RegisterFlags(..), emptyRegisterFlags, defaultRegisterFlags, registerCommand,
                                                                unregisterCommand,
   SDistFlags(..),    emptySDistFlags,    defaultSDistFlags,    sdistCommand,
-                                                               testCommand,
+  TestFlags(..),     emptyTestFlags,     defaultTestFlags,     testCommand,
   CopyDest(..),
   configureArgs, configureOptions,
 
+  defaultDistPref,
+
   Flag(..),
   toFlag,
   fromFlag,
@@ -89,6 +91,10 @@ import Data.Char (isSpace)
 import Data.Monoid (Monoid(..))
 import Distribution.Verbosity
 
+-- XXX Not sure where this should live
+defaultDistPref :: FilePath
+defaultDistPref = "dist"
+
 -- ------------------------------------------------------------
 -- * Flag type
 -- ------------------------------------------------------------
@@ -246,6 +252,7 @@ data ConfigFlags = ConfigFlags {
     configExtraLibDirs  :: [FilePath],   -- ^ path to search for extra libraries
     configExtraIncludeDirs :: [FilePath],   -- ^ path to search for header files
 
+    configDistPref :: Flag FilePath, -- ^"dist" prefix
     configVerbosity :: Flag Verbosity, -- ^verbosity level
     configUserInstall :: Flag Bool,    -- ^The --user\/--global flag
     configPackageDB :: Flag PackageDB, -- ^Which package DB to use
@@ -269,6 +276,7 @@ defaultConfigFlags progConf = emptyConfigFlags {
     configOptimization = Flag NormalOptimisation,
     configProgPrefix   = Flag (toPathTemplate ""),
     configProgSuffix   = Flag (toPathTemplate ""),
+    configDistPref     = Flag defaultDistPref,
     configVerbosity    = Flag normal,
     configUserInstall  = Flag False,           --TODO: reverse this
     configGHCiLib      = Flag True,
@@ -294,6 +302,7 @@ configureCommand progConf = makeCommand name shortDesc longDesc defaultFlags opt
 configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
 configureOptions showOrParseArgs =
       [optionVerbosity configVerbosity (\v flags -> flags { configVerbosity = v })
+      ,optionDistPref configDistPref (\d flags -> flags { configDistPref = d })
 
       ,option [] ["compiler"] "compiler"
          configHcFlavor (\v flags -> flags { configHcFlavor = v })
@@ -510,6 +519,7 @@ instance Monoid ConfigFlags where
     configProgSuffix    = mempty,
     configInstallDirs   = mempty,
     configScratchDir    = mempty,
+    configDistPref      = mempty,
     configVerbosity     = mempty,
     configUserInstall   = mempty,
     configPackageDB     = mempty,
@@ -538,6 +548,7 @@ instance Monoid ConfigFlags where
     configProgSuffix    = combine configProgSuffix,
     configInstallDirs   = combine configInstallDirs,
     configScratchDir    = combine configScratchDir,
+    configDistPref      = combine configDistPref,
     configVerbosity     = combine configVerbosity,
     configUserInstall   = combine configUserInstall,
     configPackageDB     = combine configPackageDB,
@@ -558,6 +569,7 @@ instance Monoid ConfigFlags where
 -- | Flags to @copy@: (destdir, copy-prefix (backwards compat), verbosity)
 data CopyFlags = CopyFlags {
     copyDest      :: Flag CopyDest,
+    copyDistPref  :: Flag FilePath,
     copyVerbosity :: Flag Verbosity
   }
   deriving Show
@@ -565,6 +577,7 @@ data CopyFlags = CopyFlags {
 defaultCopyFlags :: CopyFlags
 defaultCopyFlags  = CopyFlags {
     copyDest      = Flag NoCopyDest,
+    copyDistPref  = Flag defaultDistPref,
     copyVerbosity = Flag normal
   }
 
@@ -578,6 +591,7 @@ copyCommand = makeCommand name shortDesc longDesc defaultCopyFlags options
        ++ "Without the --destdir flag, configure determines location.\n"
     options _  =
       [optionVerbosity copyVerbosity (\v flags -> flags { copyVerbosity = v })
+      ,optionDistPref copyDistPref (\d flags -> flags { copyDistPref = d })
 
       ,option "" ["destdir"]
          "directory to copy files to, prepended to installation directories"
@@ -599,10 +613,12 @@ emptyCopyFlags = mempty
 instance Monoid CopyFlags where
   mempty = CopyFlags {
     copyDest      = mempty,
+    copyDistPref  = mempty,
     copyVerbosity = mempty
   }
   mappend a b = CopyFlags {
     copyDest      = combine copyDest,
+    copyDistPref  = combine copyDistPref,
     copyVerbosity = combine copyVerbosity
   }
     where combine field = field a `mappend` field b
@@ -614,6 +630,7 @@ instance Monoid CopyFlags where
 -- | Flags to @install@: (package db, verbosity)
 data InstallFlags = InstallFlags {
     installPackageDB :: Flag PackageDB,
+    installDistPref  :: Flag FilePath,
     installVerbosity :: Flag Verbosity
   }
   deriving Show
@@ -621,6 +638,7 @@ data InstallFlags = InstallFlags {
 defaultInstallFlags :: InstallFlags
 defaultInstallFlags  = InstallFlags {
     installPackageDB = NoFlag,
+    installDistPref  = Flag defaultDistPref,
     installVerbosity = Flag normal
   }
 
@@ -635,6 +653,7 @@ installCommand = makeCommand name shortDesc longDesc defaultInstallFlags options
       ++ "specified in the configure step, use the copy command.\n"
     options _  =
       [optionVerbosity installVerbosity (\v flags -> flags { installVerbosity = v })
+      ,optionDistPref installDistPref (\d flags -> flags { installDistPref = d })
 
       ,option "" ["packageDB"] ""
          installPackageDB (\v flags -> flags { installPackageDB = v })
@@ -650,10 +669,12 @@ emptyInstallFlags = mempty
 instance Monoid InstallFlags where
   mempty = InstallFlags{
     installPackageDB = mempty,
+    installDistPref  = mempty,
     installVerbosity = mempty
   }
   mappend a b = InstallFlags{
     installPackageDB = combine installPackageDB,
+    installDistPref  = combine installDistPref,
     installVerbosity = combine installVerbosity
   }
     where combine field = field a `mappend` field b
@@ -665,6 +686,7 @@ instance Monoid InstallFlags where
 -- | Flags to @sdist@: (snapshot, verbosity)
 data SDistFlags = SDistFlags {
     sDistSnapshot  :: Flag Bool,
+    sDistDistPref  :: Flag FilePath,
     sDistVerbosity :: Flag Verbosity
   }
   deriving Show
@@ -672,6 +694,7 @@ data SDistFlags = SDistFlags {
 defaultSDistFlags :: SDistFlags
 defaultSDistFlags = SDistFlags {
     sDistSnapshot  = Flag False,
+    sDistDistPref  = Flag defaultDistPref,
     sDistVerbosity = Flag normal
   }
 
@@ -683,6 +706,7 @@ sdistCommand = makeCommand name shortDesc longDesc defaultSDistFlags options
     longDesc   = Nothing
     options _  =
       [optionVerbosity sDistVerbosity (\v flags -> flags { sDistVerbosity = v })
+      ,optionDistPref sDistDistPref (\d flags -> flags { sDistDistPref = d })
 
       ,option "" ["snapshot"]
          "Produce a snapshot source distribution"
@@ -696,10 +720,12 @@ emptySDistFlags = mempty
 instance Monoid SDistFlags where
   mempty = SDistFlags {
     sDistSnapshot  = mempty,
+    sDistDistPref  = mempty,
     sDistVerbosity = mempty
   }
   mappend a b = SDistFlags {
     sDistSnapshot  = combine sDistSnapshot,
+    sDistDistPref  = combine sDistDistPref,
     sDistVerbosity = combine sDistVerbosity
   }
     where combine field = field a `mappend` field b
@@ -715,6 +741,7 @@ data RegisterFlags = RegisterFlags {
     regGenScript   :: Flag Bool,
     regGenPkgConf  :: Flag (Maybe FilePath),
     regInPlace     :: Flag Bool,
+    regDistPref    :: Flag FilePath,
     regVerbosity   :: Flag Verbosity
   }
   deriving Show
@@ -725,6 +752,7 @@ defaultRegisterFlags = RegisterFlags {
     regGenScript   = Flag False,
     regGenPkgConf  = Flag Nothing,
     regInPlace     = Flag False,
+    regDistPref    = Flag defaultDistPref,
     regVerbosity   = Flag normal
   }
 
@@ -736,6 +764,7 @@ registerCommand = makeCommand name shortDesc longDesc defaultRegisterFlags optio
     longDesc   = Nothing
     options _  =
       [optionVerbosity regVerbosity (\v flags -> flags { regVerbosity = v })
+      ,optionDistPref regDistPref (\d flags -> flags { regDistPref = d })
 
       ,option "" ["packageDB"] ""
          regPackageDB (\v flags -> flags { regPackageDB = v })
@@ -768,6 +797,7 @@ unregisterCommand = makeCommand name shortDesc longDesc defaultRegisterFlags opt
     longDesc   = Nothing
     options _  =
       [optionVerbosity regVerbosity (\v flags -> flags { regVerbosity = v })
+      ,optionDistPref regDistPref (\d flags -> flags { regDistPref = d })
 
       ,option "" ["user"] ""
          regPackageDB (\v flags -> flags { regPackageDB = v })
@@ -791,6 +821,7 @@ instance Monoid RegisterFlags where
     regGenScript   = mempty,
     regGenPkgConf  = mempty,
     regInPlace     = mempty,
+    regDistPref    = mempty,
     regVerbosity   = mempty
   }
   mappend a b = RegisterFlags {
@@ -798,6 +829,7 @@ instance Monoid RegisterFlags where
     regGenScript   = combine regGenScript,
     regGenPkgConf  = combine regGenPkgConf,
     regInPlace     = combine regInPlace,
+    regDistPref    = combine regDistPref,
     regVerbosity   = combine regVerbosity
   }
     where combine field = field a `mappend` field b
@@ -809,6 +841,7 @@ instance Monoid RegisterFlags where
 data HscolourFlags = HscolourFlags {
     hscolourCSS         :: Flag FilePath,
     hscolourExecutables :: Flag Bool,
+    hscolourDistPref    :: Flag FilePath,
     hscolourVerbosity   :: Flag Verbosity
   }
   deriving Show
@@ -820,6 +853,7 @@ defaultHscolourFlags :: HscolourFlags
 defaultHscolourFlags = HscolourFlags {
     hscolourCSS         = NoFlag,
     hscolourExecutables = Flag False,
+    hscolourDistPref    = Flag defaultDistPref,
     hscolourVerbosity   = Flag normal
   }
 
@@ -827,11 +861,13 @@ instance Monoid HscolourFlags where
   mempty = HscolourFlags {
     hscolourCSS         = mempty,
     hscolourExecutables = mempty,
+    hscolourDistPref    = mempty,
     hscolourVerbosity   = mempty
   }
   mappend a b = HscolourFlags {
     hscolourCSS         = combine hscolourCSS,
     hscolourExecutables = combine hscolourExecutables,
+    hscolourDistPref    = combine hscolourDistPref,
     hscolourVerbosity   = combine hscolourVerbosity
   }
     where combine field = field a `mappend` field b
@@ -844,6 +880,7 @@ hscolourCommand = makeCommand name shortDesc longDesc defaultHscolourFlags optio
     longDesc   = Just (\_ -> "Requires hscolour.")
     options _  =
       [optionVerbosity hscolourVerbosity (\v flags -> flags { hscolourVerbosity = v })
+      ,optionDistPref hscolourDistPref (\d flags -> flags { hscolourDistPref = d })
 
       ,option "" ["executables"]
          "Run hscolour for Executables targets"
@@ -868,6 +905,7 @@ data HaddockFlags = HaddockFlags {
     haddockCss          :: Flag FilePath,
     haddockHscolour     :: Flag Bool,
     haddockHscolourCss  :: Flag FilePath,
+    haddockDistPref     :: Flag FilePath,
     haddockVerbosity    :: Flag Verbosity
   }
   deriving Show
@@ -881,6 +919,7 @@ defaultHaddockFlags  = HaddockFlags {
     haddockCss          = NoFlag,
     haddockHscolour     = Flag False,
     haddockHscolourCss  = NoFlag,
+    haddockDistPref     = Flag defaultDistPref,
     haddockVerbosity    = Flag normal
   }
 
@@ -892,6 +931,7 @@ haddockCommand = makeCommand name shortDesc longDesc defaultHaddockFlags options
     longDesc   = Just (\_ -> "Requires cpphs and haddock.\n")
     options _  =
       [optionVerbosity haddockVerbosity (\v flags -> flags { haddockVerbosity = v })
+      ,optionDistPref haddockDistPref (\d flags -> flags { haddockDistPref = d })
 
       ,option "" ["hoogle"]
          "Generate a hoogle database"
@@ -941,6 +981,7 @@ instance Monoid HaddockFlags where
     haddockCss          = mempty,
     haddockHscolour     = mempty,
     haddockHscolourCss  = mempty,
+    haddockDistPref     = mempty,
     haddockVerbosity    = mempty
   }
   mappend a b = HaddockFlags {
@@ -951,6 +992,7 @@ instance Monoid HaddockFlags where
     haddockCss          = combine haddockCss,
     haddockHscolour     = combine haddockHscolour,
     haddockHscolourCss  = combine haddockHscolourCss,
+    haddockDistPref     = combine haddockDistPref,
     haddockVerbosity    = combine haddockVerbosity
   }
     where combine field = field a `mappend` field b
@@ -961,6 +1003,7 @@ instance Monoid HaddockFlags where
 
 data CleanFlags = CleanFlags {
     cleanSaveConf  :: Flag Bool,
+    cleanDistPref  :: Flag FilePath,
     cleanVerbosity :: Flag Verbosity
   }
   deriving Show
@@ -968,6 +1011,7 @@ data CleanFlags = CleanFlags {
 defaultCleanFlags :: CleanFlags
 defaultCleanFlags  = CleanFlags {
     cleanSaveConf  = Flag False,
+    cleanDistPref  = Flag defaultDistPref,
     cleanVerbosity = Flag normal
   }
 
@@ -979,6 +1023,7 @@ cleanCommand = makeCommand name shortDesc longDesc defaultCleanFlags options
     longDesc   = Just (\_ -> "Removes .hi, .o, preprocessed sources, etc.\n")
     options _  =
       [optionVerbosity cleanVerbosity (\v flags -> flags { cleanVerbosity = v })
+      ,optionDistPref cleanDistPref (\d flags -> flags { cleanDistPref = d })
 
       ,option "s" ["save-configure"]
          "Do not remove the configuration file (dist/setup-config) during cleaning.  Saves need to reconfigure."
@@ -992,10 +1037,12 @@ emptyCleanFlags = mempty
 instance Monoid CleanFlags where
   mempty = CleanFlags {
     cleanSaveConf  = mempty,
+    cleanDistPref  = mempty,
     cleanVerbosity = mempty
   }
   mappend a b = CleanFlags {
     cleanSaveConf  = combine cleanSaveConf,
+    cleanDistPref  = combine cleanDistPref,
     cleanVerbosity = combine cleanVerbosity
   }
     where combine field = field a `mappend` field b
@@ -1006,6 +1053,7 @@ instance Monoid CleanFlags where
 
 data BuildFlags = BuildFlags {
     buildProgramArgs :: [(String, [String])],
+    buildDistPref    :: Flag FilePath,
     buildVerbosity   :: Flag Verbosity
   }
   deriving Show
@@ -1013,6 +1061,7 @@ data BuildFlags = BuildFlags {
 defaultBuildFlags :: BuildFlags
 defaultBuildFlags  = BuildFlags {
     buildProgramArgs = [],
+    buildDistPref    = Flag defaultDistPref,
     buildVerbosity   = Flag normal
   }
 
@@ -1024,6 +1073,7 @@ buildCommand progConf = makeCommand name shortDesc longDesc defaultBuildFlags op
     longDesc   = Nothing
     options showOrParseArgs =
       optionVerbosity buildVerbosity (\v flags -> flags { buildVerbosity = v })
+      : optionDistPref buildDistPref (\d flags -> flags { buildDistPref = d })
 
       : programConfigurationOptions progConf showOrParseArgs
           buildProgramArgs (\v flags -> flags { buildProgramArgs = v})
@@ -1034,11 +1084,13 @@ emptyBuildFlags = mempty
 instance Monoid BuildFlags where
   mempty = BuildFlags {
     buildProgramArgs = mempty,
-    buildVerbosity   = mempty
+    buildVerbosity   = mempty,
+    buildDistPref    = mempty
   }
   mappend a b = BuildFlags {
     buildProgramArgs = combine buildProgramArgs,
-    buildVerbosity   = combine buildVerbosity
+    buildVerbosity   = combine buildVerbosity,
+    buildDistPref    = combine buildDistPref
   }
     where combine field = field a `mappend` field b
 
@@ -1048,6 +1100,7 @@ instance Monoid BuildFlags where
 
 data MakefileFlags = MakefileFlags {
     makefileFile      :: Flag FilePath,
+    makefileDistPref  :: Flag FilePath,
     makefileVerbosity :: Flag Verbosity
   }
   deriving Show
@@ -1055,6 +1108,7 @@ data MakefileFlags = MakefileFlags {
 defaultMakefileFlags :: MakefileFlags
 defaultMakefileFlags  = MakefileFlags {
     makefileFile      = NoFlag,
+    makefileDistPref  = Flag defaultDistPref,
     makefileVerbosity = Flag normal
   }
 
@@ -1066,6 +1120,7 @@ makefileCommand = makeCommand name shortDesc longDesc defaultMakefileFlags optio
     longDesc   = Nothing
     options _  =
       [optionVerbosity makefileVerbosity (\v flags -> flags { makefileVerbosity = v })
+      ,optionDistPref makefileDistPref (\d flags -> flags { makefileDistPref = d })
 
       ,option "f" ["file"]
          "Filename to use (default: Makefile)."
@@ -1079,10 +1134,12 @@ emptyMakefileFlags  = mempty
 instance Monoid MakefileFlags where
   mempty = MakefileFlags {
     makefileFile      = mempty,
+    makefileDistPref  = mempty,
     makefileVerbosity = mempty
   }
   mappend a b = MakefileFlags {
     makefileFile      = combine makefileFile,
+    makefileDistPref  = combine makefileDistPref,
     makefileVerbosity = combine makefileVerbosity
   }
     where combine field = field a `mappend` field b
@@ -1091,13 +1148,42 @@ instance Monoid MakefileFlags where
 -- * Test flags
 -- ------------------------------------------------------------
 
-testCommand :: CommandUI ()
-testCommand = makeCommand name shortDesc longDesc () options
+data TestFlags = TestFlags {
+    testDistPref  :: Flag FilePath,
+    testVerbosity :: Flag Verbosity
+  }
+  deriving Show
+
+defaultTestFlags :: TestFlags
+defaultTestFlags  = TestFlags {
+    testDistPref  = Flag defaultDistPref,
+    testVerbosity = Flag normal
+  }
+
+testCommand :: CommandUI TestFlags
+testCommand = makeCommand name shortDesc longDesc defaultTestFlags options
   where
     name       = "test"
     shortDesc  = "Run the test suite, if any (configure with UserHooks)."
     longDesc   = Nothing
-    options _  = []
+    options _  =
+      [optionVerbosity testVerbosity (\v flags -> flags { testVerbosity = v })
+      ,optionDistPref testDistPref (\d flags -> flags { testDistPref = d })
+      ]
+
+emptyTestFlags :: TestFlags
+emptyTestFlags  = mempty
+
+instance Monoid TestFlags where
+  mempty = TestFlags {
+    testDistPref  = mempty,
+    testVerbosity = mempty
+  }
+  mappend a b = TestFlags {
+    testDistPref  = combine testDistPref,
+    testVerbosity = combine testVerbosity
+  }
+    where combine field = field a `mappend` field b
 
 -- ------------------------------------------------------------
 -- * Shared options utils
@@ -1177,6 +1263,16 @@ reqArgFlag :: ArgPlaceHolder -> SFlags -> LFlags -> Description ->
               (b -> Flag String) -> (Flag String -> b -> b) -> OptDescr b
 reqArgFlag ad = reqArg ad (succeedReadE Flag) flagToList
 
+optionDistPref :: (flags -> Flag FilePath)
+               -> (Flag FilePath -> flags -> flags)
+               -> OptionField flags
+optionDistPref get set =
+  option "" ["distpref"]
+    (   "Control which directory Cabal puts its generated files in "
+     ++ "(default " ++ defaultDistPref ++ ")")
+    get set
+    (reqArgFlag "DIR")
+
 optionVerbosity :: (flags -> Flag Verbosity)
                 -> (Flag Verbosity -> flags -> flags)
                 -> OptionField flags
diff --git a/Distribution/Simple/SetupWrapper.hs b/Distribution/Simple/SetupWrapper.hs
index 190460edcb..33021fc2c5 100644
--- a/Distribution/Simple/SetupWrapper.hs
+++ b/Distribution/Simple/SetupWrapper.hs
@@ -24,7 +24,7 @@ import Distribution.Simple.Configure
 import Distribution.PackageDescription
          ( PackageDescription(..), GenericPackageDescription(..), BuildType(..) )
 import Distribution.PackageDescription.Parse ( readPackageDescription )
-import Distribution.Simple.BuildPaths ( distPref, exeExtension )
+import Distribution.Simple.BuildPaths ( exeExtension )
 import Distribution.Simple.Program ( ProgramConfiguration,
                                      emptyProgramConfiguration,
                                      rawSystemProgramConf, ghcProgram )
@@ -57,10 +57,11 @@ import Data.Monoid		( Monoid(mempty) )
   --      dependencies here and building/installing the sub packages
   --      in the right order.
 setupWrapper :: 
-       [String] -- ^ Command-line arguments.
+       FilePath -- ^ "dist" prefix
+    -> [String] -- ^ Command-line arguments.
     -> Maybe FilePath -- ^ Directory to run in. If 'Nothing', the current directory is used.
     -> IO ()
-setupWrapper args mdir = inDir mdir $ do  
+setupWrapper distPref args mdir = inDir mdir $ do  
   let (flag_fn, _, _, errs) = getOpt' Permute opts args
   when (not (null errs)) $ die (unlines errs)
   let Flags { withCompiler = hc, withHcPkg = hcPkg, withVerbosity = verbosity
diff --git a/Distribution/Simple/SrcDist.hs b/Distribution/Simple/SrcDist.hs
index 05051c4547..1b522e7433 100644
--- a/Distribution/Simple/SrcDist.hs
+++ b/Distribution/Simple/SrcDist.hs
@@ -94,11 +94,13 @@ import System.FilePath
 sdist :: PackageDescription -- ^information from the tarball
       -> Maybe LocalBuildInfo -- ^Information from configure
       -> SDistFlags -- ^verbosity & snapshot
-      -> FilePath -- ^build prefix (temp dir)
-      -> FilePath -- ^TargetPrefix
+      -> (FilePath -> FilePath) -- ^build prefix (temp dir)
       -> [PPSuffixHandler]  -- ^ extra preprocessors (includes suffixes)
       -> IO ()
-sdist pkg mb_lbi flags tmpDir targetPref pps = do
+sdist pkg mb_lbi flags mkTmpDir pps = do
+  let distPref = fromFlag $ sDistDistPref flags
+      targetPref = distPref
+      tmpDir = mkTmpDir distPref
 
   -- do some QA
   printPackageProblems verbosity pkg
-- 
GitLab