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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/8f70afee9246ec641fc0897ac0a118b60901363d

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

commit 8f70afee9246ec641fc0897ac0a118b60901363d
Author: Lemmih <[email protected]>
Date:   Sat Oct 6 09:33:13 2007 +0000

    Sensible defaults in case of missing or erroneous server lists.

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

 .../src/Network/Hackage/CabalInstall/Config.hs     |   15 +++++++++------
 1 files changed, 9 insertions(+), 6 deletions(-)

diff --git a/cabal-install/src/Network/Hackage/CabalInstall/Config.hs 
b/cabal-install/src/Network/Hackage/CabalInstall/Config.hs
index 72a15b8..8a426b2 100644
--- a/cabal-install/src/Network/Hackage/CabalInstall/Config.hs
+++ b/cabal-install/src/Network/Hackage/CabalInstall/Config.hs
@@ -25,7 +25,7 @@ module Network.Hackage.CabalInstall.Config
     ) where
 
 import Prelude hiding (catch)
-import Control.Exception (catch, Exception(IOException))
+import Control.Exception (catch, Exception(IOException),evaluate)
 import Control.Monad.Error (mplus, filterM) -- Using Control.Monad.Error to 
get the Error instance for IO.
 import qualified Data.ByteString.Lazy.Char8 as BS
 import Data.ByteString.Lazy.Char8 (ByteString)
@@ -134,9 +134,12 @@ parseRepoIndex repo s =
 
 getKnownServers :: ConfigFlags -> IO [Repo]
 getKnownServers cfg
-    = fmap readRepos (readFile (servList cfg))
-      `mplus` return []
-
+    = (evaluate =<< fmap readRepos (readFile (servList cfg)))
+      `catch` \e -> case e of
+                         IOException ioe | isDoesNotExistError ioe ->
+                           return defaultServs
+                         _ -> hPutStrLn stderr ("Failed to read server list: " 
++ (show e) ++ ". Using hackage.haskell.org.") >> return defaultServs
+          where defaultServs = [ Repo "hackage.haskell.org" 
"http://hackage.haskell.org/packages/archive"; ]
 readRepos :: String -> [Repo]
 readRepos = map (\ (n,u) -> Repo { repoName = n, repoURL = u }) . read
 
@@ -145,8 +148,8 @@ readRepos = map (\ (n,u) -> Repo { repoName = n, repoURL = 
u }) . read
 isValidConfigDir :: FilePath -> IO Bool
 isValidConfigDir path
     = do checks <- sequence
-                   [ checkFiles readable [ path
-                                         , path </> servListFile ]]
+                   [ checkFiles readable [ path ]]
+--                                         , path </> servListFile ]]
          return (and checks)
 
 -- |Picks the first valid config directory or throws an exception if none were 
found.



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

Reply via email to