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

On branch  : master

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

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

commit c418c69e242da9f29f12ca0e9b634d79ebef77e8
Author: Duncan Coutts <[email protected]>
Date:   Tue May 6 13:30:22 2008 +0000

    Add more info and debug messages at key parts of the install process
    If we're in verbose mode then always print what we're going to
    install, not just when the user specifies --dry-run.

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

 cabal-install/Hackage/Install.hs      |    8 ++++++--
 cabal-install/Hackage/SetupWrapper.hs |   15 ++++++++++-----
 2 files changed, 16 insertions(+), 7 deletions(-)

diff --git a/cabal-install/Hackage/Install.hs b/cabal-install/Hackage/Install.hs
index 7c9f457..6dbb78e 100644
--- a/cabal-install/Hackage/Install.hs
+++ b/cabal-install/Hackage/Install.hs
@@ -63,7 +63,7 @@ import Distribution.System
          ( buildOS, buildArch )
 import Distribution.Text
          ( display )
-import Distribution.Verbosity (Verbosity, showForCabal)
+import Distribution.Verbosity (Verbosity, showForCabal, verbose)
 import Distribution.Simple.BuildPaths ( exeExtension )
 
 data BuildResult = DependentFailed PackageIdentifier
@@ -155,12 +155,16 @@ installLocalPackage verbosity packageDB repos comp conf 
miscOptions configFlags
       --TODO: print the info again
       -- details <- mapM Info.infoPkg (Info.flattenResolvedDependencies 
resolvedDeps)
       -- info verbosity $ unlines (map ("  "++) (concat details))
+      info verbosity "Resolving dependencies..."
       case resolveDependencies buildOS buildArch (compilerId comp)
                              installed available' [localDependency] of
         Left missing -> die $ "Unresolved dependencies: " ++ showDependencies 
missing
         Right installPlan -> do
+            when (verbosity >= verbose || dryRun miscOptions) $
+              printDryRun verbosity installPlan
+
             if dryRun miscOptions
-              then printDryRun verbosity installPlan >> return []
+              then return []
               else executeInstallPlan verbosity scriptOptions miscOptions
                                       configFlags installPlan >> return []
 
diff --git a/cabal-install/Hackage/SetupWrapper.hs 
b/cabal-install/Hackage/SetupWrapper.hs
index 8cfdcdd..ba6f514 100644
--- a/cabal-install/Hackage/SetupWrapper.hs
+++ b/cabal-install/Hackage/SetupWrapper.hs
@@ -124,7 +124,8 @@ type SetupMethod = Verbosity -> BuildType -> [String] -> IO 
()
 
 internalSetupMethod :: SetupMethod
 internalSetupMethod verbosity bt args = do
-  debug verbosity $ "internalSetupMethod " ++ show bt ++ " " ++ show args
+  debug verbosity $ "Using internal setup method with build-type " ++ show bt
+                 ++ " and args:\n  " ++ show args
   buildTypeAction bt args
 
 buildTypeAction :: BuildType -> ([String] -> IO ())
@@ -140,10 +141,13 @@ buildTypeAction (UnknownBuildType _) = error 
"buildTypeAction UnknownBuildType"
 -- ------------------------------------------------------------
 
 externalSetupMethod :: SetupScriptOptions -> SetupMethod
-externalSetupMethod options verbosity bt args =
-      updateSetupScript verbosity bt
-  >>= compileSetupExecutable verbosity options
-  >>  invokeSetupScript verbosity args
+externalSetupMethod options verbosity bt args = do
+  debug verbosity $ "Using external setup method with build-type " ++ show bt
+                 ++ " and args:\n  " ++ show args
+  setupHs <- updateSetupScript verbosity bt
+  debug verbosity $ "Using " ++ setupHs ++ " as setup script."
+  compileSetupExecutable verbosity options setupHs
+  invokeSetupScript verbosity args
 
 -- | Decide which Setup.hs script to use, creating it if necessary.
 --
@@ -178,6 +182,7 @@ compileSetupExecutable :: Verbosity -> SetupScriptOptions 
-> FilePath -> IO ()
 compileSetupExecutable verbosity options setupHs = do
   outOfDate <- setupHs `moreRecentFile` setupProg
   when outOfDate $ do
+    debug verbosity "Setup script is out of date, compiling..."
     (comp, conf) <- case useCompiler options of
       Just comp -> return (comp, useProgramConfig options)
       Nothing -> configCompiler (Just GHC) Nothing Nothing



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

Reply via email to