Repository : ssh://darcs.haskell.org//srv/darcs/packages/Cabal

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/0ce34bd400bf578af451b3ac9e9f70fd34293b73

>---------------------------------------------------------------

commit 0ce34bd400bf578af451b3ac9e9f70fd34293b73
Author: bjorn <[email protected]>
Date:   Tue Oct 16 09:10:22 2007 +0000

    Set preifx to the global default when the config file says to do a global 
install. This still doesn't work if --global is given on the command line. 
Print the complete config if verbosity >= verbose. Don't save prefix to the 
config file, since that means we will use the user default even for global 
installs.

>---------------------------------------------------------------

 cabal-install/Hackage/Config.hs |   29 +++++++++++++++++++++--------
 cabal-install/Main.hs           |   10 ++++++++--
 2 files changed, 29 insertions(+), 10 deletions(-)

diff --git a/cabal-install/Hackage/Config.hs b/cabal-install/Hackage/Config.hs
index c1a3c6a..65d313d 100644
--- a/cabal-install/Hackage/Config.hs
+++ b/cabal-install/Hackage/Config.hs
@@ -20,6 +20,7 @@ module Hackage.Config
     , pkgURL
     , defaultConfigFile
     , loadConfig
+    , showConfig
     , findCompiler
     ) where
 
@@ -151,16 +152,24 @@ defaultCacheDir = do dir <- defaultCabalDir
 defaultCompiler :: CompilerFlavor
 defaultCompiler = fromMaybe GHC defaultCompilerFlavor
 
+defaultInstallDirs' :: CompilerFlavor -> Bool -> IO InstallDirTemplates
+defaultInstallDirs' compiler userInstall =
+    do installDirs <- defaultInstallDirs compiler True
+       if userInstall 
+        then do userPrefix <- defaultCabalDir
+                return $ installDirs { prefixDirTemplate = toPathTemplate 
userPrefix }
+        else return installDirs
+
+
 defaultConfigFlags :: IO ConfigFlags
 defaultConfigFlags = 
-    do defaultPrefix <- defaultCabalDir
-       installDirs <- defaultInstallDirs defaultCompiler True
+    do installDirs <- defaultInstallDirs' defaultCompiler True
        cacheDir    <- defaultCacheDir
        return $ ConfigFlags 
                { configCompiler    = defaultCompiler
                , configCompilerPath = Nothing
                , configHcPkgPath   = Nothing
-               , configInstallDirs = installDirs { prefixDirTemplate = 
toPathTemplate defaultPrefix }
+               , configInstallDirs = installDirs
                , configCacheDir    = cacheDir
                , configRepos       = [Repo "hackage.haskell.org" 
"http://hackage.haskell.org/packages/archive";]
                , configVerbose     = normal
@@ -184,9 +193,10 @@ loadConfig configFile =
                        ParseOk ws dummyConf -> 
                            do mapM_ (hPutStrLn stderr . ("Config file warning: 
" ++)) ws
                               -- There is a data dependency within the config 
file.
-                              -- The default installation paths depend on the 
compiler.
+                              -- The default installation paths depend on the 
compiler
+                              -- and on whether this is a user or global 
installation.
                               -- Hence we need to do two passes through the 
config file.
-                              installDirs <- defaultInstallDirs 
(configCompiler dummyConf) True
+                              installDirs <- defaultInstallDirs' 
(configCompiler dummyConf) (configUserInstall dummyConf)
                               let conf = defaultConf { configInstallDirs = 
installDirs }
                               case parseBasicStanza configFieldDescrs conf inp 
of
                                 ParseOk _ conf' -> return conf'
@@ -202,16 +212,20 @@ writeDefaultConfigFile file cfg =
     do createDirectoryIfMissing True (takeDirectory file)
        writeFile file $ showFields configWriteFieldDescrs cfg
 
+showConfig :: ConfigFlags -> String
+showConfig = showFields configFieldDescrs
+
 -- | All config file fields.
 configFieldDescrs :: [FieldDescr ConfigFlags]
-configFieldDescrs =
+configFieldDescrs = configWriteFieldDescrs ++
     [ installDirField "bindir" binDirTemplate (\d ds -> ds { binDirTemplate = 
d })
     , installDirField "libdir" libDirTemplate (\d ds -> ds { libDirTemplate = 
d })
     , installDirField "libexecdir" libexecDirTemplate (\d ds -> ds { 
libexecDirTemplate = d })
     , installDirField "datadir" dataDirTemplate (\d ds -> ds { dataDirTemplate 
= d })
     , installDirField "docdir" docDirTemplate (\d ds -> ds { docDirTemplate = 
d })
     , installDirField "htmldir" htmlDirTemplate (\d ds -> ds { htmlDirTemplate 
= d })
-    ] ++ configWriteFieldDescrs
+    , installDirField "prefix" prefixDirTemplate (\d ds -> ds { 
prefixDirTemplate = d })
+    ]
 
 
 -- | The subset of the config file fields that we write out
@@ -228,7 +242,6 @@ configWriteFieldDescrs =
                 (text . show)                  (readS_to_P reads)
                 configCacheDir    (\d cfg -> cfg { configCacheDir = d })
     , boolField "user-install" configUserInstall (\u cfg -> cfg { 
configUserInstall = u })
-    , installDirField "prefix" prefixDirTemplate (\d ds -> ds { 
prefixDirTemplate = d })
     ] 
 
 installDirField :: String 
diff --git a/cabal-install/Main.hs b/cabal-install/Main.hs
index ae66c26..95300cf 100644
--- a/cabal-install/Main.hs
+++ b/cabal-install/Main.hs
@@ -15,7 +15,8 @@ module Main where
 
 import Hackage.Types            (Action (..), Option(..))
 import Hackage.Setup            (parseGlobalArgs, parsePackageArgs, 
configFromOptions)
-import Hackage.Config           (defaultConfigFile, loadConfig, findCompiler)
+import Hackage.Config           (defaultConfigFile, loadConfig, findCompiler
+                                , message, showConfig)
 import Hackage.List             (list)
 import Hackage.Install          (install)
 import Hackage.Info             (info)
@@ -23,6 +24,8 @@ import Hackage.Update           (update)
 import Hackage.Fetch            (fetch)
 import Hackage.Clean            (clean)
 
+import Distribution.Verbosity   (verbose)
+
 import System.Environment       (getArgs)
 
 -- | Entry point
@@ -39,7 +42,10 @@ main = do
 
     let config = configFromOptions conf0 flags
 
-        runCmd f = do (globalArgs, pkgs) <- parsePackageArgs action args
+    message config verbose "Configuration:"
+    message config verbose (showConfig config)
+
+    let runCmd f = do (globalArgs, pkgs) <- parsePackageArgs action args
                       (comp, conf) <- findCompiler config
                       f config comp conf globalArgs pkgs
 



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to