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

On branch  : master

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

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

commit f395a5a89506c18e997680ca5617030fb886eedc
Author: Duncan Coutts <[email protected]>
Date:   Mon May 10 05:48:24 2010 +0000

    Remove redundant dry-run support from world file code

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

 cabal-install/Distribution/Client/Install.hs |    3 +--
 cabal-install/Distribution/Client/World.hs   |   19 ++++++++-----------
 2 files changed, 9 insertions(+), 13 deletions(-)

diff --git a/cabal-install/Distribution/Client/Install.hs 
b/cabal-install/Distribution/Client/Install.hs
index 376675b..8d5f76f 100644
--- a/cabal-install/Distribution/Client/Install.hs
+++ b/cabal-install/Distribution/Client/Install.hs
@@ -467,7 +467,7 @@ postInstallActions verbosity
   targets installPlan = do
 
   unless oneShot $
-    World.insert verbosity dryRun worldFile targets'
+    World.insert verbosity worldFile targets'
 
   let buildReports = BuildReports.fromInstallPlan installPlan
   BuildReports.storeLocal (installSummaryFile installFlags) buildReports
@@ -486,7 +486,6 @@ postInstallActions verbosity
   where
     reportingLevel = fromFlag (installBuildReports installFlags)
     logsDir        = fromFlag (globalLogsDir globalFlags)
-    dryRun         = fromFlag (installDryRun installFlags)
     oneShot        = fromFlag (installOneShot installFlags)
     worldFile      = fromFlag $ globalWorldFile globalFlags
     targets'       = filter (not . World.isWorldTarget) targets
diff --git a/cabal-install/Distribution/Client/World.hs 
b/cabal-install/Distribution/Client/World.hs
index 3708033..5c53512 100644
--- a/cabal-install/Distribution/Client/World.hs
+++ b/cabal-install/Distribution/Client/World.hs
@@ -43,7 +43,6 @@ import Distribution.Verbosity ( Verbosity )
 import Distribution.Simple.Utils ( die, info, chattyTry )
 import Data.List( unionBy, deleteFirstsBy, nubBy )
 import Data.Maybe( isJust, fromJust )
-import Control.Monad( unless )
 import System.IO.Error( isDoesNotExistError, )
 import qualified Data.ByteString.Lazy.Char8 as B
 import Prelude hiding ( getContents )
@@ -51,13 +50,13 @@ import Prelude hiding ( getContents )
 -- | Adds packages to the world file; creates the file if it doesn't
 -- exist yet. Version constraints and flag assignments for a package are
 -- updated if already present. IO errors are non-fatal.
-insert :: Verbosity -> Bool -> FilePath -> [UnresolvedDependency] -> IO ()
+insert :: Verbosity -> FilePath -> [UnresolvedDependency] -> IO ()
 insert = modifyWorld $ unionBy equalUDep
 
 -- | Removes packages from the world file.
 -- Note: Currently unused as there is no mechanism in Cabal (yet) to
 -- handle uninstalls. IO errors are non-fatal.
-delete :: Verbosity -> Bool -> FilePath -> [UnresolvedDependency] -> IO ()
+delete :: Verbosity -> FilePath -> [UnresolvedDependency] -> IO ()
 delete = modifyWorld $ flip (deleteFirstsBy equalUDep)
 
 -- | UnresolvedDependency values are considered equal if they refer to
@@ -75,12 +74,11 @@ modifyWorld :: ([UnresolvedDependency] -> 
[UnresolvedDependency]
                         -- the list of user packages are merged with
                         -- existing world packages.
             -> Verbosity
-            -> Bool                   -- ^ Dry-run?
             -> FilePath               -- ^ Location of the world file
             -> [UnresolvedDependency] -- ^ list of user supplied packages
             -> IO ()
-modifyWorld _ _         _      _     []   = return ()
-modifyWorld f verbosity dryRun world pkgs =
+modifyWorld _ _         _     []   = return ()
+modifyWorld f verbosity world pkgs =
   chattyTry "Error while updating world-file. " $ do
     pkgsOldWorld <- getContents world
     -- Filter out packages that are not in the world file:
@@ -89,11 +87,10 @@ modifyWorld f verbosity dryRun world pkgs =
     -- equivalence the awkward way:
     if not (all (`elem` pkgsOldWorld) pkgsNewWorld &&
             all (`elem` pkgsNewWorld) pkgsOldWorld)
-      then
-        unless dryRun $ do
-          writeFileAtomic world $ unlines
-              [ (display pkg) | pkg <- pkgsNewWorld]
-          info verbosity "Updating world file..."
+      then do
+        info verbosity "Updating world file..."
+        writeFileAtomic world $ unlines
+            [ (display pkg) | pkg <- pkgsNewWorld]
       else
         info verbosity "World file is already up to date."
 



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

Reply via email to