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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/e6ad7fc59742e1f4128655838a57e2ec75fc92c5

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

commit e6ad7fc59742e1f4128655838a57e2ec75fc92c5
Author: Duncan Coutts <[email protected]>
Date:   Thu May 3 19:23:03 2007 +0000

    Tweak where the default config lives and where we keep the package list
    This should make it all "Just Work"tm. We no longer need a Makefile
    to do the installation. The point is, don't bother trying to use
    /etc/cabal-install/srve.list as the global list. That's hard to do
    because it involves installing that file, and we only want to do that
    for global installs, so it's even more complex. Instead we should just
    use cabal's facility to install data files. That way it ends up in
    /usr/local/share/cabal-install-x.y/
    or somewhere similar for a user install. But either way, cabal handles it.
    The per-user config sill overrides this one, so it's still possible to edit
    the list even if /usr/local/share/ is read-only. Also, we always use
    $HOME/.cabal-install/ for the per-user config and package cache.
    The one downside is that if an admin wants to use /etc/ and /var rather
    than /root/.cabal-install/ then this is a tad harder. But the point is
    at the moment it'll at least work for most people without fiddling,
    including windows users.

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

 .../src/Network/Hackage/CabalInstall/Config.hs     |   35 ++++++++++++--------
 .../src/Network/Hackage/CabalInstall/Configure.hs  |   31 ++++++------------
 .../src/Network/Hackage/CabalInstall/Setup.hs      |    7 ++--
 3 files changed, 34 insertions(+), 39 deletions(-)

diff --git a/cabal-install/src/Network/Hackage/CabalInstall/Config.hs 
b/cabal-install/src/Network/Hackage/CabalInstall/Config.hs
index 6289b91..6bbdc22 100644
--- a/cabal-install/src/Network/Hackage/CabalInstall/Config.hs
+++ b/cabal-install/src/Network/Hackage/CabalInstall/Config.hs
@@ -12,9 +12,10 @@
 -----------------------------------------------------------------------------
 module Network.Hackage.CabalInstall.Config
     ( packagesDirectory
-    , defaultConfDir
-    , defaultCacheDir
-    , defaultPkgListDir
+    , getDefaultConfigDir
+    , getLocalConfigDir
+    , getLocalCacheDir
+    , getLocalPkgListDir
     , getKnownServers
     , getKnownPackages
     , writeKnownPackages
@@ -37,17 +38,23 @@ import System.Directory
 
 import Network.Hackage.CabalInstall.Types (ConfigFlags (..), PkgInfo (..))
 
-defaultConfDir, defaultCacheDir, defaultPkgListDir :: FilePath
-
-#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
-defaultConfDir    = "/" </> "etc" </> "cabal-install" --FIXME
-defaultCacheDir   = unsafePerformIO getTemporaryDirectory
-defaultPkgListDir = unsafePerformIO (getAppUserDataDirectory "cabal-install")
-#else
-defaultConfDir    = "/" </> "etc" </> "cabal-install"
-defaultCacheDir   = "/" </> "var" </> "cache" </> "cabal-install"
-defaultPkgListDir = "/" </> "var" </> "lib" </> "cabal-install"
-#endif
+import Paths_cabal_install (getDataDir)
+
+-- |Compute the global config directory
+-- (eg '/usr/local/share/cabal-install-0.3.0/' on Linux).
+getDefaultConfigDir :: IO FilePath
+getDefaultConfigDir = getDataDir
+
+-- |Compute the local config directory ('~/.cabal-install' on Linux).
+getLocalConfigDir :: IO FilePath
+getLocalConfigDir
+    = getAppUserDataDirectory "cabal-install"
+
+getLocalCacheDir :: IO FilePath
+getLocalCacheDir = getLocalConfigDir
+
+getLocalPkgListDir :: IO FilePath
+getLocalPkgListDir = getLocalConfigDir
 
 pkgListFile :: FilePath
 pkgListFile = "pkg.list"
diff --git a/cabal-install/src/Network/Hackage/CabalInstall/Configure.hs 
b/cabal-install/src/Network/Hackage/CabalInstall/Configure.hs
index 237f347..3299e4e 100644
--- a/cabal-install/src/Network/Hackage/CabalInstall/Configure.hs
+++ b/cabal-install/src/Network/Hackage/CabalInstall/Configure.hs
@@ -19,8 +19,9 @@ import Control.Monad (guard, mplus, when)
 
 import Network.Hackage.CabalInstall.Types (ConfigFlags (..), OutputGen (..)
                                       , TempFlags (..), ResolvedPackage (..))
-import Network.Hackage.CabalInstall.Config (defaultConfDir, defaultCacheDir, 
defaultPkgListDir,
-                                            getKnownServers, 
selectValidConfigDir)
+import Network.Hackage.CabalInstall.Config
+         (getDefaultConfigDir, getLocalConfigDir, getLocalCacheDir,
+          getLocalPkgListDir, getKnownServers, selectValidConfigDir)
 
 import qualified Distribution.Simple.Configure as Configure (findProgram, 
configCompiler)
 import Distribution.ParseUtils (showDependency)
@@ -94,17 +95,6 @@ localPrefix
     = do home <- getHomeDirectory
          return (home </> "usr")
 
--- |Compute the local config directory ('~/.cabal-install' on Linux).
-localConfigDir :: IO FilePath
-localConfigDir
-    = getAppUserDataDirectory "cabal-install"
-
-localCacheDir :: IO FilePath
-localCacheDir = localConfigDir
-
-localPkgListDir :: IO FilePath
-localPkgListDir = localConfigDir
-
 {-|
   Give concrete answers to questions like:
 
@@ -122,18 +112,17 @@ mkConfigFlags cfg
          tarProg <- findProgramOrDie "tar" (tempTarPath cfg)
          comp <- Configure.configCompiler (tempHcFlavor cfg) (tempHcPath cfg) 
(tempHcPkg cfg) (tempVerbose cfg)
          let userIns = tempUserIns cfg
-         localConfig <- localConfigDir
          prefix <- if userIns
                       then fmap Just (maybe localPrefix return (tempPrefix 
cfg))
                       else return Nothing
+         defaultConfigDir <- getDefaultConfigDir
+         localConfigDir   <- getLocalConfigDir
+         localCacheDir    <- getLocalCacheDir
+         localPkgListDir  <- getLocalPkgListDir
          confDir <- selectValidConfigDir ( maybe id (:) (tempConfDir cfg)
-                                           [defaultConfDir, localConfig] )
-         cacheDir <- if userIns
-                        then maybe localCacheDir return (tempCacheDir cfg)
-                        else return $ fromMaybe defaultCacheDir (tempCacheDir 
cfg)
-         pkgListDir <- if userIns
-                        then maybe localPkgListDir return (tempPkgListDir cfg)
-                        else return $ fromMaybe defaultPkgListDir 
(tempPkgListDir cfg)
+                                           [localConfigDir, defaultConfigDir] )
+         let cacheDir   = fromMaybe localCacheDir   (tempCacheDir cfg)
+             pkgListDir = fromMaybe localPkgListDir (tempPkgListDir cfg)
          when (tempVerbose cfg > 1) $ do printf "Using config dir: %s\n" 
confDir
                                          printf "Using cache dir: %s\n" 
cacheDir
                                          printf "Using pkglist dir: %s\n" 
pkgListDir
diff --git a/cabal-install/src/Network/Hackage/CabalInstall/Setup.hs 
b/cabal-install/src/Network/Hackage/CabalInstall/Setup.hs
index 981a347..3d4f3d8 100644
--- a/cabal-install/src/Network/Hackage/CabalInstall/Setup.hs
+++ b/cabal-install/src/Network/Hackage/CabalInstall/Setup.hs
@@ -26,7 +26,6 @@ import System.Console.GetOpt (ArgDescr (..), ArgOrder (..), 
OptDescr (..), usage
 import System.Exit (exitWith, ExitCode (..))
 import System.Environment (getProgName)
 
-import Network.Hackage.CabalInstall.Config (defaultConfDir, defaultCacheDir, 
defaultPkgListDir)
 import Network.Hackage.CabalInstall.Types (TempFlags (..), Action (..)
                                       , UnresolvedDependency (..))
 
@@ -64,11 +63,11 @@ globalOptions =
     , Option "s" ["with-server"] (ReqArg (\url t -> t { tempServers = 
url:tempServers t }) "URL")
                  "give the URL to a Hackage server"
     , Option "c" ["config-dir"] (ReqArg (\path t -> t { tempConfDir = Just 
path }) "PATH")
-                 ("give the path to the config dir. Default is " ++ 
defaultConfDir)
+                 ("override the path to the config dir.")
     , Option "" ["cache-dir"] (ReqArg (\path t -> t { tempCacheDir = Just path 
}) "PATH")
-                 ("give the path to the package cache dir. Default is " ++ 
defaultCacheDir)
+                 ("override the path to the package cache dir.")
     , Option "" ["pkglist-dir"] (ReqArg (\path t -> t { tempPkgListDir = Just 
path }) "PATH")
-                 ("give the path to the package list dir. Default is " ++ 
defaultPkgListDir)
+                 ("override the path to the package list dir.")
     , Option "" ["tar-path"] (ReqArg (\path t -> t { tempTarPath = Just path 
}) "PATH")
                  "give the path to tar"
     , Option "w" ["with-compiler"] (ReqArg (\path t -> t { tempHcPath = Just 
path }) "PATH")



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

Reply via email to