Fri Sep 15 21:29:49 CEST 2006  [EMAIL PROTECTED]
  * Add preliminary support for haddock-ghc

Fri Dec 29 20:54:39 CET 2006  [EMAIL PROTECTED]
  * Make sure haddock-ghc really creates the output dir

Sun Dec 31 00:21:16 CET 2006  [EMAIL PROTECTED]
  * Add compilerPath to Paths_<pkg>

Fri Jan  5 22:22:24 CET 2007  [EMAIL PROTECTED]
  * Add -D__HADDOCK__ to haddock-ghc

Sat Jan  6 02:44:20 CET 2007  [EMAIL PROTECTED]
  * Generate GHC arguments usable for haddock-ghc

Sat Jan  6 02:48:01 CET 2007  [EMAIL PROTECTED]
  * Use -g option to send GHC arguments to haddock-ghc

Thu Jan 18 22:55:20 CET 2007  [EMAIL PROTECTED]
  * Don't send -cpp to haddock-ghc

Mon Feb  5 00:49:25 CET 2007  [EMAIL PROTECTED]
  * Synch Haddock-GHC changes with recent changes to Cabal

Mon Mar  5 17:53:42 CET 2007  [EMAIL PROTECTED]
  * Solve conflict

Mon Mar  5 20:00:45 CET 2007  [EMAIL PROTECTED]
  * Use only one haddock command
  This patch merges the haddock-ghc and haddock commands, treating the 
"haddock" 
  executable as haddock-ghc if the version is >= 2.0.

Fri Mar  9 14:08:37 CET 2007  [EMAIL PROTECTED]
  * Send GHC libdir to haddock-ghc and synch with recent changes
New patches:

[Add preliminary support for haddock-ghc
[EMAIL PROTECTED] {
hunk ./Distribution/Program.hs 58
+                           , haddockGHCProgram
hunk ./Distribution/Program.hs 106
+                              , haddockGHCProgram
hunk ./Distribution/Program.hs 186
+haddockGHCProgram :: Program
+haddockGHCProgram = simpleProgram "haddock-ghc"
+
hunk ./Distribution/Setup.hs 92
+            | HaddockGHCCmd           -- haddock-ghc
hunk ./Distribution/Setup.hs 381
-                        copyCmd, sdistCmd, testCmd, haddockCmd, programaticaCmd,
-                        registerCmd, unregisterCmd]
+                        copyCmd, sdistCmd, testCmd, haddockCmd, haddockGHCCmd, 
+                        programaticaCmd, registerCmd, unregisterCmd]
hunk ./Distribution/Setup.hs 606
+
+haddockGHCCmd :: Cmd a
+haddockGHCCmd = Cmd {
+        cmdName        = "haddock-ghc",
+        cmdHelp        = "Generate Haddock HTML code from Exposed-Modules, using haddock-ghc.",
+        cmdDescription = "Requires haddock-ghc.",
+        cmdOptions     = [cmd_help, cmd_verbose,
+                          Option "" ["hoogle"] (NoArg HaddockHoogle) "Generate a hoogle database"],
+        cmdAction      = HaddockGHCCmd
+        }
hunk ./Distribution/Simple/GHC.hs 47
-	build, installLib, installExe
+	build, installLib, installExe, constructGeneralGHCCmdLine
hunk ./Distribution/Simple/GHC.hs 340
-
-constructGHCCmdLine
-	:: LocalBuildInfo
+constructGeneralGHCCmdLine :: LocalBuildInfo
hunk ./Distribution/Simple/GHC.hs 343
-	-> Int				-- verbosity level
merger 0.0 (
hunk ./Distribution/Simple/GHC.hs 346
-     ++ (if verbose > 4 then ["-v"] else if verbose > 0 then [] else ["-v0"])
+     ++ (if verbose > 4 then      ["-v"]
+         else if verbose > 0 then []
+         else                     ["-w", "-v0"])
merger 0.0 (
hunk ./Distribution/Simple/GHC.hs 346
-     ++ (if verbose > 4 then ["-v"] else [])
+     ++ (if verbose > 4 then ["-v"] else if verbose > 0 then [] else ["-v0"])
hunk ./Distribution/Simple/GHC.hs 344
-constructGHCCmdLine lbi bi odir verbose = 
-        ["--make"]
-     ++ (if verbose > 4 then ["-v"] else [])
-	    -- Unsupported extensions have already been checked by configure
-     ++ (if compilerVersion (compiler lbi) > Version [6,4] []
-            then ["-hide-all-packages"]
-            else [])
+constructGeneralGHCCmdLine lbi bi odir =
+    (if compilerVersion (compiler lbi) > Version [6,4] []
+         then ["-hide-all-packages"]
+         else [])
)
)
hunk ./Distribution/Simple/GHC.hs 363
+constructGHCCmdLine
+	:: LocalBuildInfo
+        -> BuildInfo
+	-> FilePath
+	-> Int				-- verbosity level
+        -> [String]
+constructGHCCmdLine lbi bi odir verbose = 
+        ["--make"]
+     ++ (if verbose > 4 then ["-v"] else [])
+     ++ constructGeneralGHCCmdLine lbi bi odir
+
merger 0.0 (
hunk ./Distribution/Simple.hs 73
-                            haddockProgram, rawSystemProgram, defaultProgramConfiguration,
+                            haddockProgram, ghcPkgProgram, rawSystemProgram, defaultProgramConfiguration,
hunk ./Distribution/Simple.hs 73
-                            haddockProgram, rawSystemProgram, defaultProgramConfiguration,
-                            pfesetupProgram, updateProgram,  rawSystemProgramConf)
+                            haddockProgram, haddockGHCProgram, rawSystemProgram, 
+                            defaultProgramConfiguration, pfesetupProgram, updateProgram,
+                            rawSystemProgramConf)
)
hunk ./Distribution/Simple.hs 98
+import Distribution.Simple.GHC ( constructGeneralGHCCmdLine )
+
hunk ./Distribution/Simple.hs 210
+      -- |Hook to run before haddock command.  Second arg indicates verbosity level.
+     preGHCHaddock  :: Args -> HaddockFlags -> IO HookedBuildInfo,
+      -- |Hook to run after haddock command.  Second arg indicates verbosity level. 
+      -- |Over-ride this hook to get different behavior during haddock.
+     haddockGHCHook :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks -> HaddockFlags -> IO (),
+     postGHCHaddock :: Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO ExitCode,
+
hunk ./Distribution/Simple.hs 330
+            HaddockGHCCmd -> do
+                (verbose, _, args) <- parseHaddockArgs emptyHaddockFlags args []
+                pkg_descr <- hookOrInArgs preGHCHaddock args verbose
+                localbuildinfo <- getPersistBuildConfig
+
+                cmdHook haddockGHCHook pkg_descr localbuildinfo verbose
+                postHook postGHCHaddock args verbose pkg_descr localbuildinfo
+
merger 0.0 (
hunk ./Distribution/Simple.hs 405
+-- --------------------------------------------------------------------------
+-- Haddock support
+
hunk ./Distribution/Simple.hs 405
+haddockGHC :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks 
+              -> HaddockFlags -> IO ()
+haddockGHC pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
+    confHaddock <- do
+        let programConf = withPrograms lbi
+        let haddockGHCName = programName haddockGHCProgram
+        mHaddock <- lookupProgram haddockGHCName programConf
+        maybe (die "haddock-ghc command not found") return mHaddock
+
+    let tmpDir = joinPaths (buildDir lbi) "tmp"
+    createDirectoryIfMissing True tmpDir
+
+    setupMessage "Running Haddock for" pkg_descr
+
+    let showPkg = showPackageId (package pkg_descr)
+    let outputFlag = if hoogle then "--hoogle" else "--html"
+
+    withLib pkg_descr () $ \lib -> do
+        let bi = libBuildInfo lib
+        inFiles <- getModulePaths bi (exposedModules lib ++ otherModules bi)
+        let prologName = showPkg ++ "-haddock-prolog.txt"
+        writeFile prologName (description pkg_descr ++ "\n")
+
+        rawSystemProgram verbose confHaddock
+                (["--ghc-flags",
+                  outputFlag,
+                  "--odir=" ++ haddockPref,
+                  "--title=" ++ showPkg ++ ": " ++ synopsis pkg_descr,
+                  "--prologue=" ++ prologName]
+                 ++ programArgs confHaddock
+                 ++ (if verbose > 4 then ["--verbose"] else [])
+                 ++ inFiles
+                 ++ map ("--hide=" ++) (otherModules bi)
+                 ++ ["-package-name", showPackageId (package pkg_descr) ]
+                 ++ constructGeneralGHCCmdLine lbi bi tmpDir
+                )
+        removeFile prologName
+
+    removeDirectoryRecursive tmpDir
+
)
hunk ./Distribution/Simple.hs 627
-       postHaddock = res
-      }
+       postHaddock = res,
+       preGHCHaddock  = rn,
+       haddockGHCHook = ru,
+       postGHCHaddock = res
+       }
merger 0.0 (
hunk ./Distribution/Simple.hs 679
-       haddockHook = haddock,
hunk ./Distribution/Simple.hs 680
+       haddockGHCHook = haddockGHC,
)
}

[Make sure haddock-ghc really creates the output dir
[EMAIL PROTECTED] {
merger 0.0 (
merger 0.0 (
hunk ./Distribution/Simple.hs 405
+haddockGHC :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks 
+              -> HaddockFlags -> IO ()
+haddockGHC pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
+    confHaddock <- do
+        let programConf = withPrograms lbi
+        let haddockGHCName = programName haddockGHCProgram
+        mHaddock <- lookupProgram haddockGHCName programConf
+        maybe (die "haddock-ghc command not found") return mHaddock
+
+    let tmpDir = joinPaths (buildDir lbi) "tmp"
+    createDirectoryIfMissing True tmpDir
+
+    setupMessage "Running Haddock for" pkg_descr
+
+    let showPkg = showPackageId (package pkg_descr)
+    let outputFlag = if hoogle then "--hoogle" else "--html"
+
+    withLib pkg_descr () $ \lib -> do
+        let bi = libBuildInfo lib
+        inFiles <- getModulePaths bi (exposedModules lib ++ otherModules bi)
+        let prologName = showPkg ++ "-haddock-prolog.txt"
+        writeFile prologName (description pkg_descr ++ "\n")
+
+        rawSystemProgram verbose confHaddock
+                (["--ghc-flags",
+                  outputFlag,
+                  "--odir=" ++ haddockPref,
+                  "--title=" ++ showPkg ++ ": " ++ synopsis pkg_descr,
+                  "--prologue=" ++ prologName]
+                 ++ programArgs confHaddock
+                 ++ (if verbose > 4 then ["--verbose"] else [])
+                 ++ inFiles
+                 ++ map ("--hide=" ++) (otherModules bi)
+                 ++ ["-package-name", showPackageId (package pkg_descr) ]
+                 ++ constructGeneralGHCCmdLine lbi bi tmpDir
+                )
+        removeFile prologName
+
+    removeDirectoryRecursive tmpDir
+
hunk ./Distribution/Simple.hs 405
+-- --------------------------------------------------------------------------
+-- Haddock support
+
)
hunk ./Distribution/Simple.hs 416
-
+    createDirectoryIfMissing True haddockPref
+ 
)
}

[Add compilerPath to Paths_<pkg>
[EMAIL PROTECTED] {
hunk ./Distribution/Simple/Build.hs 148
-	"\tgetDataFileName\n"++
+	"\tgetDataFileName, compilerPath\n"++
hunk ./Distribution/Simple/Build.hs 155
+	"\ncompilerPath = " ++ (show . compilerPath . compiler) lbi ++
}

[Add -D__HADDOCK__ to haddock-ghc
[EMAIL PROTECTED] {
merger 0.0 (
merger 0.0 (
hunk ./Distribution/Simple.hs 416
-
+    createDirectoryIfMissing True haddockPref
+ 
merger 0.0 (
hunk ./Distribution/Simple.hs 405
+haddockGHC :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks 
+              -> HaddockFlags -> IO ()
+haddockGHC pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
+    confHaddock <- do
+        let programConf = withPrograms lbi
+        let haddockGHCName = programName haddockGHCProgram
+        mHaddock <- lookupProgram haddockGHCName programConf
+        maybe (die "haddock-ghc command not found") return mHaddock
+
+    let tmpDir = joinPaths (buildDir lbi) "tmp"
+    createDirectoryIfMissing True tmpDir
+
+    setupMessage "Running Haddock for" pkg_descr
+
+    let showPkg = showPackageId (package pkg_descr)
+    let outputFlag = if hoogle then "--hoogle" else "--html"
+
+    withLib pkg_descr () $ \lib -> do
+        let bi = libBuildInfo lib
+        inFiles <- getModulePaths bi (exposedModules lib ++ otherModules bi)
+        let prologName = showPkg ++ "-haddock-prolog.txt"
+        writeFile prologName (description pkg_descr ++ "\n")
+
+        rawSystemProgram verbose confHaddock
+                (["--ghc-flags",
+                  outputFlag,
+                  "--odir=" ++ haddockPref,
+                  "--title=" ++ showPkg ++ ": " ++ synopsis pkg_descr,
+                  "--prologue=" ++ prologName]
+                 ++ programArgs confHaddock
+                 ++ (if verbose > 4 then ["--verbose"] else [])
+                 ++ inFiles
+                 ++ map ("--hide=" ++) (otherModules bi)
+                 ++ ["-package-name", showPackageId (package pkg_descr) ]
+                 ++ constructGeneralGHCCmdLine lbi bi tmpDir
+                )
+        removeFile prologName
+
+    removeDirectoryRecursive tmpDir
+
hunk ./Distribution/Simple.hs 405
+-- --------------------------------------------------------------------------
+-- Haddock support
+
)
)
hunk ./Distribution/Simple.hs 431
+                  "-cpp",
+                  "-D__HADDOCK__",
)
}

[Generate GHC arguments usable for haddock-ghc
[EMAIL PROTECTED] {
merger 0.0 (
hunk ./Distribution/Simple/GHC.hs 359
+     ++ (if withOptimization lbi then ["-O"] else [])
hunk ./Distribution/Simple/GHC.hs 357
-     ++ [ "-odir",  odir, "-hidir", odir ]
-     ++ (concat [ ["-package", showPackageId pkg] | pkg <- packageDeps lbi ])
+     ++ [ "-odir " ++ odir, "-hidir " ++ odir ]
+     ++ (concat [ ["-package " ++ showPackageId pkg] | pkg <- packageDeps lbi ])
)
}

[Use -g option to send GHC arguments to haddock-ghc
[EMAIL PROTECTED] {
merger 0.0 (
merger 0.0 (
hunk ./Distribution/Simple.hs 431
+                  "-cpp",
+                  "-D__HADDOCK__",
merger 0.0 (
hunk ./Distribution/Simple.hs 416
-
+    createDirectoryIfMissing True haddockPref
+ 
merger 0.0 (
hunk ./Distribution/Simple.hs 405
+haddockGHC :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks 
+              -> HaddockFlags -> IO ()
+haddockGHC pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
+    confHaddock <- do
+        let programConf = withPrograms lbi
+        let haddockGHCName = programName haddockGHCProgram
+        mHaddock <- lookupProgram haddockGHCName programConf
+        maybe (die "haddock-ghc command not found") return mHaddock
+
+    let tmpDir = joinPaths (buildDir lbi) "tmp"
+    createDirectoryIfMissing True tmpDir
+
+    setupMessage "Running Haddock for" pkg_descr
+
+    let showPkg = showPackageId (package pkg_descr)
+    let outputFlag = if hoogle then "--hoogle" else "--html"
+
+    withLib pkg_descr () $ \lib -> do
+        let bi = libBuildInfo lib
+        inFiles <- getModulePaths bi (exposedModules lib ++ otherModules bi)
+        let prologName = showPkg ++ "-haddock-prolog.txt"
+        writeFile prologName (description pkg_descr ++ "\n")
+
+        rawSystemProgram verbose confHaddock
+                (["--ghc-flags",
+                  outputFlag,
+                  "--odir=" ++ haddockPref,
+                  "--title=" ++ showPkg ++ ": " ++ synopsis pkg_descr,
+                  "--prologue=" ++ prologName]
+                 ++ programArgs confHaddock
+                 ++ (if verbose > 4 then ["--verbose"] else [])
+                 ++ inFiles
+                 ++ map ("--hide=" ++) (otherModules bi)
+                 ++ ["-package-name", showPackageId (package pkg_descr) ]
+                 ++ constructGeneralGHCCmdLine lbi bi tmpDir
+                )
+        removeFile prologName
+
+    removeDirectoryRecursive tmpDir
+
hunk ./Distribution/Simple.hs 405
+-- --------------------------------------------------------------------------
+-- Haddock support
+
)
)
)
hunk ./Distribution/Simple.hs 429
+        let ghcArgs = ["-cpp", "-D__HADDOCK__", 
+                       "-package-name " ++ showPackageId (package pkg_descr)]
+                      ++ constructGeneralGHCCmdLine lbi bi tmpDir
+  
+        let ghcArgs' = "-g" : intersperse "-g" ghcArgs
+        
)
merger 0.0 (
merger 0.0 (
hunk ./Distribution/Simple.hs 429
+        let ghcArgs = ["-cpp", "-D__HADDOCK__", 
+                       "-package-name " ++ showPackageId (package pkg_descr)]
+                      ++ constructGeneralGHCCmdLine lbi bi tmpDir
+  
+        let ghcArgs' = "-g" : intersperse "-g" ghcArgs
+        
merger 0.0 (
hunk ./Distribution/Simple.hs 431
+                  "-cpp",
+                  "-D__HADDOCK__",
merger 0.0 (
hunk ./Distribution/Simple.hs 416
-
+    createDirectoryIfMissing True haddockPref
+ 
merger 0.0 (
hunk ./Distribution/Simple.hs 405
+haddockGHC :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks 
+              -> HaddockFlags -> IO ()
+haddockGHC pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
+    confHaddock <- do
+        let programConf = withPrograms lbi
+        let haddockGHCName = programName haddockGHCProgram
+        mHaddock <- lookupProgram haddockGHCName programConf
+        maybe (die "haddock-ghc command not found") return mHaddock
+
+    let tmpDir = joinPaths (buildDir lbi) "tmp"
+    createDirectoryIfMissing True tmpDir
+
+    setupMessage "Running Haddock for" pkg_descr
+
+    let showPkg = showPackageId (package pkg_descr)
+    let outputFlag = if hoogle then "--hoogle" else "--html"
+
+    withLib pkg_descr () $ \lib -> do
+        let bi = libBuildInfo lib
+        inFiles <- getModulePaths bi (exposedModules lib ++ otherModules bi)
+        let prologName = showPkg ++ "-haddock-prolog.txt"
+        writeFile prologName (description pkg_descr ++ "\n")
+
+        rawSystemProgram verbose confHaddock
+                (["--ghc-flags",
+                  outputFlag,
+                  "--odir=" ++ haddockPref,
+                  "--title=" ++ showPkg ++ ": " ++ synopsis pkg_descr,
+                  "--prologue=" ++ prologName]
+                 ++ programArgs confHaddock
+                 ++ (if verbose > 4 then ["--verbose"] else [])
+                 ++ inFiles
+                 ++ map ("--hide=" ++) (otherModules bi)
+                 ++ ["-package-name", showPackageId (package pkg_descr) ]
+                 ++ constructGeneralGHCCmdLine lbi bi tmpDir
+                )
+        removeFile prologName
+
+    removeDirectoryRecursive tmpDir
+
hunk ./Distribution/Simple.hs 405
+-- --------------------------------------------------------------------------
+-- Haddock support
+
)
)
)
)
hunk ./Distribution/Simple.hs 436
-                (["--ghc-flags",
-                  "-cpp",
-                  "-D__HADDOCK__",
-                  outputFlag,
+                ([outputFlag,
)
merger 0.0 (
merger 0.0 (
hunk ./Distribution/Simple.hs 436
-                (["--ghc-flags",
-                  "-cpp",
-                  "-D__HADDOCK__",
-                  outputFlag,
+                ([outputFlag,
merger 0.0 (
hunk ./Distribution/Simple.hs 429
+        let ghcArgs = ["-cpp", "-D__HADDOCK__", 
+                       "-package-name " ++ showPackageId (package pkg_descr)]
+                      ++ constructGeneralGHCCmdLine lbi bi tmpDir
+  
+        let ghcArgs' = "-g" : intersperse "-g" ghcArgs
+        
merger 0.0 (
hunk ./Distribution/Simple.hs 431
+                  "-cpp",
+                  "-D__HADDOCK__",
merger 0.0 (
hunk ./Distribution/Simple.hs 416
-
+    createDirectoryIfMissing True haddockPref
+ 
merger 0.0 (
hunk ./Distribution/Simple.hs 405
+haddockGHC :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks 
+              -> HaddockFlags -> IO ()
+haddockGHC pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
+    confHaddock <- do
+        let programConf = withPrograms lbi
+        let haddockGHCName = programName haddockGHCProgram
+        mHaddock <- lookupProgram haddockGHCName programConf
+        maybe (die "haddock-ghc command not found") return mHaddock
+
+    let tmpDir = joinPaths (buildDir lbi) "tmp"
+    createDirectoryIfMissing True tmpDir
+
+    setupMessage "Running Haddock for" pkg_descr
+
+    let showPkg = showPackageId (package pkg_descr)
+    let outputFlag = if hoogle then "--hoogle" else "--html"
+
+    withLib pkg_descr () $ \lib -> do
+        let bi = libBuildInfo lib
+        inFiles <- getModulePaths bi (exposedModules lib ++ otherModules bi)
+        let prologName = showPkg ++ "-haddock-prolog.txt"
+        writeFile prologName (description pkg_descr ++ "\n")
+
+        rawSystemProgram verbose confHaddock
+                (["--ghc-flags",
+                  outputFlag,
+                  "--odir=" ++ haddockPref,
+                  "--title=" ++ showPkg ++ ": " ++ synopsis pkg_descr,
+                  "--prologue=" ++ prologName]
+                 ++ programArgs confHaddock
+                 ++ (if verbose > 4 then ["--verbose"] else [])
+                 ++ inFiles
+                 ++ map ("--hide=" ++) (otherModules bi)
+                 ++ ["-package-name", showPackageId (package pkg_descr) ]
+                 ++ constructGeneralGHCCmdLine lbi bi tmpDir
+                )
+        removeFile prologName
+
+    removeDirectoryRecursive tmpDir
+
hunk ./Distribution/Simple.hs 405
+-- --------------------------------------------------------------------------
+-- Haddock support
+
)
)
)
)
)
hunk ./Distribution/Simple.hs 444
-                 ++ ["-package-name", showPackageId (package pkg_descr) ]
-                 ++ constructGeneralGHCCmdLine lbi bi tmpDir
+                 ++ ghcArgs'
)
}

[Don't send -cpp to haddock-ghc
[EMAIL PROTECTED] {
merger 0.0 (
merger 0.0 (
hunk ./Distribution/Simple.hs 444
-                 ++ ["-package-name", showPackageId (package pkg_descr) ]
-                 ++ constructGeneralGHCCmdLine lbi bi tmpDir
+                 ++ ghcArgs'
merger 0.0 (
hunk ./Distribution/Simple.hs 436
-                (["--ghc-flags",
-                  "-cpp",
-                  "-D__HADDOCK__",
-                  outputFlag,
+                ([outputFlag,
merger 0.0 (
hunk ./Distribution/Simple.hs 429
+        let ghcArgs = ["-cpp", "-D__HADDOCK__", 
+                       "-package-name " ++ showPackageId (package pkg_descr)]
+                      ++ constructGeneralGHCCmdLine lbi bi tmpDir
+  
+        let ghcArgs' = "-g" : intersperse "-g" ghcArgs
+        
merger 0.0 (
hunk ./Distribution/Simple.hs 431
+                  "-cpp",
+                  "-D__HADDOCK__",
merger 0.0 (
hunk ./Distribution/Simple.hs 416
-
+    createDirectoryIfMissing True haddockPref
+ 
merger 0.0 (
hunk ./Distribution/Simple.hs 405
+haddockGHC :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks 
+              -> HaddockFlags -> IO ()
+haddockGHC pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
+    confHaddock <- do
+        let programConf = withPrograms lbi
+        let haddockGHCName = programName haddockGHCProgram
+        mHaddock <- lookupProgram haddockGHCName programConf
+        maybe (die "haddock-ghc command not found") return mHaddock
+
+    let tmpDir = joinPaths (buildDir lbi) "tmp"
+    createDirectoryIfMissing True tmpDir
+
+    setupMessage "Running Haddock for" pkg_descr
+
+    let showPkg = showPackageId (package pkg_descr)
+    let outputFlag = if hoogle then "--hoogle" else "--html"
+
+    withLib pkg_descr () $ \lib -> do
+        let bi = libBuildInfo lib
+        inFiles <- getModulePaths bi (exposedModules lib ++ otherModules bi)
+        let prologName = showPkg ++ "-haddock-prolog.txt"
+        writeFile prologName (description pkg_descr ++ "\n")
+
+        rawSystemProgram verbose confHaddock
+                (["--ghc-flags",
+                  outputFlag,
+                  "--odir=" ++ haddockPref,
+                  "--title=" ++ showPkg ++ ": " ++ synopsis pkg_descr,
+                  "--prologue=" ++ prologName]
+                 ++ programArgs confHaddock
+                 ++ (if verbose > 4 then ["--verbose"] else [])
+                 ++ inFiles
+                 ++ map ("--hide=" ++) (otherModules bi)
+                 ++ ["-package-name", showPackageId (package pkg_descr) ]
+                 ++ constructGeneralGHCCmdLine lbi bi tmpDir
+                )
+        removeFile prologName
+
+    removeDirectoryRecursive tmpDir
+
hunk ./Distribution/Simple.hs 405
+-- --------------------------------------------------------------------------
+-- Haddock support
+
)
)
)
)
)
)
hunk ./Distribution/Simple.hs 429
-        let ghcArgs = ["-cpp", "-D__HADDOCK__", 
+        let ghcArgs = ["-D__HADDOCK__", 
)
}

[Synch Haddock-GHC changes with recent changes to Cabal
[EMAIL PROTECTED] {
hunk ./Distribution/Simple/GHC.hs 344
-constructGHCCmdLine lbi bi odir verbose = 
-        ["--make"]
-     ++ (if verbose > 4 then ["-v"] else [])
+constructGeneralGHCCmdLine lbi bi odir =
hunk ./Distribution/Simple/GHC.hs 346
-     ++ (if compilerVersion (compiler lbi) > Version [6,4] []
-            then ["-hide-all-packages"]
-            else [])
+     (if compilerVersion (compiler lbi) > Version [6,4] []
+         then ["-hide-all-packages"]
+         else [])
hunk ./Distribution/Simple/GHC.hs 368
-     ++ (if verbose > 4 then ["-v"] else [])
+     ++ (if verbose > 4 then      ["-v"]
+         else if verbose > 0 then []
+         else                     ["-w", "-v0"])
hunk ./Distribution/Simple.hs 211
-     preGHCHaddock  :: Args -> HaddockFlags -> IO HookedBuildInfo,
+     preHaddockGHC  :: Args -> HaddockFlags -> IO HookedBuildInfo,
hunk ./Distribution/Simple.hs 215
-     postGHCHaddock :: Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO ExitCode,
+     postHaddockGHC :: Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO ExitCode,
hunk ./Distribution/Simple.hs 331
-                (verbose, _, args) <- parseHaddockArgs emptyHaddockFlags args []
-                pkg_descr <- hookOrInArgs preGHCHaddock args verbose
-                localbuildinfo <- getPersistBuildConfig
-
-                cmdHook haddockGHCHook pkg_descr localbuildinfo verbose
-                postHook postGHCHaddock args verbose pkg_descr localbuildinfo
+                command (parseHaddockArgs emptyHaddockFlags) haddockVerbose 
+                        preHaddockGHC haddockGHCHook postHaddockGHC
+                        getPersistBuildConfig
hunk ./Distribution/Simple.hs 402
+-- --------------------------------------------------------------------------
+-- Haddock support
+
+haddockGHC :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks 
+              -> HaddockFlags -> IO ()
+haddockGHC pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
+    putStrLn "KOMMER HIT"
+    confHaddock <- do
+        let programConf = withPrograms lbi
+        let haddockGHCName = programName haddockGHCProgram
+        mHaddock <- lookupProgram haddockGHCName programConf
+        maybe (die "haddock-ghc command not found") return mHaddock
+
+    let tmpDir = joinPaths (buildDir lbi) "tmp"
+    createDirectoryIfMissing True tmpDir
+    createDirectoryIfMissing True haddockPref
+ 
+    setupMessage verbose "Running Haddock for" pkg_descr
+
+    let showPkg = showPackageId (package pkg_descr)
+    let outputFlag = if hoogle then "--hoogle" else "--html"
+
+    withLib pkg_descr () $ \lib -> do
+        let bi = libBuildInfo lib
+        inFiles <- getModulePaths bi (exposedModules lib ++ otherModules bi)
+        let prologName = showPkg ++ "-haddock-prolog.txt"
+        writeFile prologName (description pkg_descr ++ "\n")
+
+        let ghcArgs = ["-D__HADDOCK__", 
+                       "-package-name " ++ showPackageId (package pkg_descr)]
+                      ++ constructGeneralGHCCmdLine lbi bi tmpDir
+  
+        let ghcArgs' = "-g" : intersperse "-g" ghcArgs
+        let haddockFile = joinFileName haddockPref (haddockName pkg_descr)
+         
+        rawSystemProgram verbose confHaddock
+                ([outputFlag,
+                  "--odir=" ++ haddockPref,
+                  "--title=" ++ showPkg ++ ": " ++ synopsis pkg_descr,
+                  "--prologue=" ++ prologName,
+                  "--dump-interface=" ++ haddockFile]
+                 ++ programArgs confHaddock
+                 ++ (if verbose > 4 then ["--verbose"] else [])
+                 ++ inFiles
+                 ++ map ("--hide=" ++) (otherModules bi)
+                 ++ ghcArgs'
+                )
+        removeFile prologName
+
+    removeDirectoryRecursive tmpDir
+
hunk ./Distribution/Simple.hs 676
-       preGHCHaddock  = rn,
+       preHaddockGHC  = rn,
hunk ./Distribution/Simple.hs 678
-       postGHCHaddock = res
+       postHaddockGHC = res
hunk ./Distribution/Simple.hs 697
+       haddockGHCHook = haddockGHC,
hunk ./Distribution/Simple.hs 729
+       haddockGHCHook = haddockGHC,
}

[Solve conflict
[EMAIL PROTECTED] {
hunk ./Distribution/Simple/GHC.hs 355
-     ++ [ "-odir",  odir, "-hidir", odir ]
-     ++ (concat [ ["-package", showPackageId pkg] | pkg <- packageDeps lbi ])
+     ++ [ "-odir " ++ odir, "-hidir " ++ odir ]
+     ++ (concat [ ["-package " ++ showPackageId pkg] | pkg <- packageDeps lbi ])
+     ++ (if withOptimization lbi then ["-O"] else [])
}

[Use only one haddock command
[EMAIL PROTECTED]
 This patch merges the haddock-ghc and haddock commands, treating the "haddock" 
 executable as haddock-ghc if the version is >= 2.0.
] {
hunk ./Distribution/Program.hs 58
-                           , haddockGHCProgram
hunk ./Distribution/Program.hs 105
-                              , haddockGHCProgram
hunk ./Distribution/Program.hs 184
-haddockGHCProgram :: Program
-haddockGHCProgram = simpleProgram "haddock-ghc"
-
merger 0.0 (
merger 0.0 (
hunk ./Distribution/Simple.hs 73
-                            haddockProgram, rawSystemProgram, defaultProgramConfiguration,
-                            pfesetupProgram, updateProgram,  rawSystemProgramConf)
+                            haddockProgram, haddockGHCProgram, rawSystemProgram, 
+                            defaultProgramConfiguration, pfesetupProgram, updateProgram,
+                            rawSystemProgramConf)
hunk ./Distribution/Simple.hs 73
-                            haddockProgram, rawSystemProgram, defaultProgramConfiguration,
+                            haddockProgram, ghcPkgProgram, rawSystemProgram, defaultProgramConfiguration,
)
hunk ./Distribution/Simple.hs 73
-                            haddockProgram, haddockGHCProgram, rawSystemProgram, 
+                            haddockProgram, rawSystemProgram, 
)
merger 0.0 (
hunk ./Distribution/Simple.hs 88
-                                     configure, writePersistBuildConfig, localBuildInfoFile)
+                                     configure, writePersistBuildConfig, localBuildInfoFile,
+                                     haddockVersion)
hunk ./Distribution/Simple.hs 88
-                                     configure, writePersistBuildConfig, localBuildInfoFile)
+                                     configure, writePersistBuildConfig, localBuildInfoFile,
+                                     haddockVersion)
)
hunk ./Distribution/Simple.hs 209
-      -- |Hook to run before haddock command.  Second arg indicates verbosity level.
-     preHaddockGHC  :: Args -> HaddockFlags -> IO HookedBuildInfo,
-      -- |Hook to run after haddock command.  Second arg indicates verbosity level. 
-      -- |Over-ride this hook to get different behavior during haddock.
-     haddockGHCHook :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks -> HaddockFlags -> IO (),
-     postHaddockGHC :: Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO ExitCode,
-
hunk ./Distribution/Simple.hs 322
-            HaddockGHCCmd -> do
-                command (parseHaddockArgs emptyHaddockFlags) haddockVerbose 
-                        preHaddockGHC haddockGHCHook postHaddockGHC
-                        getPersistBuildConfig
-
hunk ./Distribution/Simple.hs 392
-haddockGHC :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks 
-              -> HaddockFlags -> IO ()
-haddockGHC pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
-    putStrLn "KOMMER HIT"
-    confHaddock <- do
-        let programConf = withPrograms lbi
-        let haddockGHCName = programName haddockGHCProgram
-        mHaddock <- lookupProgram haddockGHCName programConf
-        maybe (die "haddock-ghc command not found") return mHaddock
+haddock :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks -> HaddockFlags -> IO ()
+haddock pkg_descr lbi hooks hflags = do
+  confHaddock <- do 
+    let programConf = withPrograms lbi
+    let haddockPath = programName haddockProgram
+    mHaddock <- lookupProgram haddockPath programConf
+    maybe (die "haddock command not found") return mHaddock
hunk ./Distribution/Simple.hs 400
+  version <- haddockVersion lbi
+  if versionBranch version < [2,0] 
+    then oldHaddock confHaddock pkg_descr lbi hooks hflags 
+    else ghcHaddock confHaddock pkg_descr lbi hooks hflags
+ 
+ghcHaddock confHaddock pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
hunk ./Distribution/Simple.hs 444
-haddock :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks -> HaddockFlags -> IO ()
-haddock pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
+oldHaddock confHaddock pkg_descr lbi hooks (HaddockFlags hoogle verbose) = do
hunk ./Distribution/Simple.hs 446
-    confHaddock <- do let programConf = withPrograms lbi
-                      let haddockPath = programName haddockProgram
-                      mHaddock <- lookupProgram haddockPath programConf
-                      maybe (die "haddock command not found") return mHaddock
-
hunk ./Distribution/Simple.hs 660
-       postHaddock = res,
-       preHaddockGHC  = rn,
-       haddockGHCHook = ru,
-       postHaddockGHC = res
+       postHaddock = res
hunk ./Distribution/Simple.hs 679
-       haddockGHCHook = haddockGHC,
hunk ./Distribution/Simple.hs 710
-       haddockGHCHook = haddockGHC,
}

[Send GHC libdir to haddock-ghc and synch with recent changes
[EMAIL PROTECTED] {
hunk ./Distribution/Simple/Configure.hs 79
-import Distribution.Simple.Utils (die, warn, withTempFile,maybeExit)
+import Distribution.Simple.Utils (die, warn, withTempFile,maybeExit, systemCaptureStdout)
hunk ./Distribution/Simple/Configure.hs 367
-systemCaptureStdout :: Int -> String -> IO String
-systemCaptureStdout verbose cmd = do
-   withTempFile "." "" $ \tmp -> do
-      let cmd_line  = cmd ++ " >" ++ tmp
-      when (verbose > 0) $ putStrLn cmd_line
-      res <- system cmd_line
-      case res of
-        ExitFailure _ -> die ("executing external program failed: "++cmd_line)
-        ExitSuccess   -> do str <- readFile tmp
-                            let ev [] = ' '; ev xs = last xs
-                            ev str `seq` return str
-
hunk ./Distribution/Simple/Utils.hs 55
+        systemCaptureStdout,
hunk ./Distribution/Simple/Utils.hs 93
+import System.Cmd
hunk ./Distribution/Simple/Utils.hs 203
+systemCaptureStdout :: Int -> String -> IO String
+systemCaptureStdout verbose cmd = do
+   withTempFile "." "" $ \tmp -> do
+      let cmd_line  = cmd ++ " >" ++ tmp
+      when (verbose > 0) $ putStrLn cmd_line
+      res <- system cmd_line
+      case res of
+        ExitFailure _ -> die ("executing external program failed: "++cmd_line)
+        ExitSuccess   -> do str <- readFile tmp
+                            let ev [] = ' '; ev xs = last xs
+                            ev str `seq` return str
+
hunk ./Distribution/Simple.hs 73
-                            haddockProgram, rawSystemProgram, defaultProgramConfiguration,
+                            haddockProgram, ghcPkgProgram, rawSystemProgram, defaultProgramConfiguration,
hunk ./Distribution/Simple.hs 88
-                                     configure, writePersistBuildConfig, localBuildInfoFile)
+                                     configure, writePersistBuildConfig, localBuildInfoFile,
+                                     haddockVersion)
hunk ./Distribution/Simple.hs 96
-                                  moduleToFilePath, findFile, warn)
+                                  moduleToFilePath, findFile, warn, 
+                                  systemCaptureStdout)
hunk ./Distribution/Simple.hs 400
-    maybe (die "haddock command not found") return mHaddock
+    maybe (die "haddock not found") return mHaddock
hunk ./Distribution/Simple.hs 408
+    -- we have to check for the configured compiler, because Program.ghcProgram 
+    -- doesn't work yet
+    ghcPath <- case compiler lbi of 
+      Compiler GHC _ path _ -> return path
+      _ -> die "the configured compiler is not GHC"
+
+    ghcLibDir <- getGhcLibDir ghcPath
+
hunk ./Distribution/Simple.hs 418
-    createDirectoryIfMissing True haddockPref
+    createDirectoryIfMissing True $ haddockPref pkg_descr
hunk ./Distribution/Simple.hs 436
-        let haddockFile = joinFileName haddockPref (haddockName pkg_descr)
+        let haddockFile = joinFileName (haddockPref pkg_descr) 
+                                       (haddockName pkg_descr)
hunk ./Distribution/Simple.hs 440
-                ([outputFlag,
-                  "--odir=" ++ haddockPref,
+                (["-B",
+                  ghcLibDir,
+                  outputFlag,
+                  "--odir=" ++ haddockPref pkg_descr,
hunk ./Distribution/Simple.hs 456
+  where
+    getGhcLibDir ghcPath = do
+      let cmd = ghcPath ++ " --print-libdir"
+      str <- systemCaptureStdout 0 cmd
+      case lines str of 
+        (libdir:_) -> return libdir
+        _ -> die $ "bad output from command: " ++ cmd
}

Context:

[Tweaks to make Cabal play nicer with haddock
Ian Lynagh <[EMAIL PROTECTED]>**20070308155718
 
 The path for the html docs now includes the package name at the end,
 which works nicer for multiple packages sharing a contents/index.
 
 Use --ghc-pkg when available (in haddock darcs only currently) to tell
 haddock which ghc-pkg to use.
 
 Use --allow-missing-html when available (in haddock darcs only
 currently) to tell haddock not to worry if it can't find the HTML for
 packages we depend on. This is necessary when haddocking a group of
 packages before moving them all into place.
] 
[Cope with ghc-pkg telling us packages are broken
Ian Lynagh <[EMAIL PROTECTED]>**20070307193131] 
[Tell GHC to use .hs mode when we want it to cpp something for us
Ian Lynagh <[EMAIL PROTECTED]>**20070307143612] 
[Add parentheses so expressions are parsed correctly
Ian Lynagh <[EMAIL PROTECTED]>**20070307131941] 
[minor refactoring
Ross Paterson <[EMAIL PROTECTED]>**20070301002731] 
[fix \begin{code typo
Ross Paterson <[EMAIL PROTECTED]>**20070301002557] 
[document the --with-compiler / --with-hc inconsistency
Ross Paterson <[EMAIL PROTECTED]>**20070225115601] 
[Clarify documentation on --with-compiler and --with-hc-pkg
[EMAIL PROTECTED] 
[minor markup tweaks
Ross Paterson <[EMAIL PROTECTED]>**20070218104622] 
[This usePackages stuff is haddock-specific so name it as such
Duncan Coutts <[EMAIL PROTECTED]>**20070213201434] 
[{en,dis}able-use-packages, -optP-P only if haddock<0.8
Conal Elliott <[EMAIL PROTECTED]>**20070204061106] 
[cabal-upload: Added command-line options for username, password, checking instead of uploading. Added ability to get login from file, and to get password from the terminal. Added still unused verbosity options. Bumped version number to 0.2.
[EMAIL PROTECTED] 
[exclude Setup.lhs
Ross Paterson <[EMAIL PROTECTED]>**20070212193608
 
 This was generating a useless Main entry in the lib doc index.
 (good for STABLE)
] 
[Add recent Cabal modules to nhc98 build system.
[EMAIL PROTECTED] 
[Compatibility with Haskell'98.
[EMAIL PROTECTED]
 Import Distribution.Compat.Exception instead of Control.Exception.
 Fix illegal indentation of cascaded do-blocks.
] 
[add --enable-optimization/--disable-optimization config options (on by default)
Ross Paterson <[EMAIL PROTECTED]>**20070212004513] 
[cabal-upload: nicer output.
[EMAIL PROTECTED] 
[Send Accept header.
[EMAIL PROTECTED] 
[Allow uploading multiple packages.
[EMAIL PROTECTED] 
[Changed HTTP dependency to >= 1.0. 
[EMAIL PROTECTED] 
[cabal-upload: Removed build-simple since hackage doesn't seem to accept it for non-lib packages.
[EMAIL PROTECTED] 
[Added URL for cabal-upload wiki page.
[EMAIL PROTECTED] 
[Added usage message to cabal-upload.
[EMAIL PROTECTED] 
[Added a small hacky first version of cabal-upload.
[EMAIL PROTECTED] 
[cabal-setup doesn't need -cpp
Ross Paterson <[EMAIL PROTECTED]>**20070115154724] 
[Refactorings only
Simon Marlow <[EMAIL PROTECTED]>**20070114203741
 Here are a batch of refactorings to clean up parsing and parts of the
 simple build system.  This patch originated in a patch sent to
 [email protected] with an intial implementation of
 configurations.  Since then we decided to go a different route with
 configurations, so I have separated the refactoring from the
 configurations patch.
 
 At this point, 2 tests fail for me, but I get the same 2 failures
 without this patch.
] 
[pass arguments through when performing the setup actions ourselves
Ross Paterson <[EMAIL PROTECTED]>**20070113133211] 
[separate option for the compiler for Setup.hs
Ross Paterson <[EMAIL PROTECTED]>**20070113133000
 
 This need not be the same compiler as used to build the package
] 
[Ignoring user packages when installing locally doesn't make sense.
Lemmih <[EMAIL PROTECTED]>**20070112150318] 
[cabal-install now caches downloaded packages in the directory for the package, and with .tar.gz extension.
[EMAIL PROTECTED] 
[cabal-install.cabal: Added build-type field. Change hs-source-dir to hs-source-dirs (hs-source-dir has been deprecated for some time).
[EMAIL PROTECTED] 
[cabal-install --user now keeps package cache and package list in ~/.cabal-install
[EMAIL PROTECTED] 
[fix ghc-options (not a listField)
[EMAIL PROTECTED] 
[add a Build-Type field, and use it in setupWrapper
Ross Paterson <[EMAIL PROTECTED]>**20070111233018
 
 As discussed on the libraries list (Nov 2006), add a field Build-Type
 which can be used to declare that this package uses one of the boilerplate
 setup scripts.  This allows setupWrapper (used by cabal-setup and
 cabal-install) to bypass the setup script in this case and perform
 the setup actions itself.
] 
[remove a use of null+head
Ross Paterson <[EMAIL PROTECTED]>**20070111182430] 
[remove two fromJust's
Ross Paterson <[EMAIL PROTECTED]>**20070111182401] 
[pass CABAL_VERSION to Hugs
Ross Paterson <[EMAIL PROTECTED]>**20070111182216] 
[cabal-install now puts the package list in /var/lib/cabal-install and the tarballs in /var/cache/cabal-install by default. Added command-line options for changing those.
[EMAIL PROTECTED] 
[Track verbosity argument changes
Ian Lynagh <[EMAIL PROTECTED]>**20070111180601] 
[Testsuite quietening
Ian Lynagh <[EMAIL PROTECTED]>**20070111175329] 
[cabal-install: Output usage info for the right command when pasrsing the package name arguments fails.
[EMAIL PROTECTED] 
[SetupWrapper now passes verbosity to other functions, as required by Igloo's patch.
[EMAIL PROTECTED] 
[Make cabal-install use setupWrapper (the library version of cabal-setup).
[EMAIL PROTECTED] 
[Moved the cabal-setup code to Distribution.SetupWrapper, so that cabal-install can use it. CabalSetup.hs now just calls the setupWrapper function.
[EMAIL PROTECTED] 
[Quieten the testsuite more
Ian Lynagh <[EMAIL PROTECTED]>**20070111155957] 
[Pass verbosity info down to warn
Ian Lynagh <[EMAIL PROTECTED]>**20070111154526] 
[Derive Show on various datatypes
Ian Lynagh <[EMAIL PROTECTED]>**20070111140220] 
[Give feedback in runTests.sh
Ian Lynagh <[EMAIL PROTECTED]>**20070111132654] 
[Be less verbose at verbosity level 1
Ian Lynagh <[EMAIL PROTECTED]>**20070111131228] 
[Fix warning
Ian Lynagh <[EMAIL PROTECTED]>**20070111130928] 
[No need for -fno-warn-unused-matches any more
Ian Lynagh <[EMAIL PROTECTED]>**20070111130824] 
[Always pass Hooks around, not Maybe Hooks
Ian Lynagh <[EMAIL PROTECTED]>**20070111124234] 
[Make Makefile use the right ghc/ghc-pkg
Ian Lynagh <[EMAIL PROTECTED]>**20070111122833] 
[Add -Wall to GHCFLAGS
Ian Lynagh <[EMAIL PROTECTED]>**20070111102742] 
[Updated cabal-install test scripts to use the main Cabal repo.
[EMAIL PROTECTED] 
[Added cabal-install test scripts.
[EMAIL PROTECTED] 
[Added cabal-install Makefile.
[EMAIL PROTECTED] 
[Added HTTP package code used by cabal-install.
[EMAIL PROTECTED] 
[Imported all the cabal-install sources.
[EMAIL PROTECTED] 
[Added cabal-install dep on regex-compat.
[EMAIL PROTECTED] 
[Removed old CabalInstall.hs (it has moved to cabal-install/src in one of the pataches I pulled in).
[EMAIL PROTECTED] 
[Pulling in cabal-install: changed default Hackage DB URL.
[EMAIL PROTECTED] 
[Pulling cabal-with-install into Cabal: cabal-install.cabal changes.
[EMAIL PROTECTED] 
[Pulling changes from cabal-with-install: Multiple repositories.
[EMAIL PROTECTED]
 Original patch:
 Sat Sep  2 00:13:40 CEST 2006  Paolo Martini <[EMAIL PROTECTED]>
   * Multiple repositories.
] 
[Pulling changes from cabal-with-install: Stripping off the dependencies, only HTTP left
[EMAIL PROTECTED]
 Original patch:
 Sun Aug 20 19:01:03 CEST 2006  Paolo Martini <[EMAIL PROTECTED]>
   * Stripping off the dependencies, only HTTP left
] 
[Resolve Makefile conflict from importing Cabal-with-install patches.
[EMAIL PROTECTED] 
[a program to test download & install a bunch of cabal packages
[EMAIL PROTECTED] 
[added --inplace trick to cabal build so that cabal-install can build on machines without cabal.
[EMAIL PROTECTED] 
[First attempt to make a new repository (url in the configuration)
Paolo Martini <[EMAIL PROTECTED]>**20060820180342] 
[Tarball index format support
Paolo Martini <[EMAIL PROTECTED]>**20060816223509] 
[Quieten a test
Ian Lynagh <[EMAIL PROTECTED]>**20070110175223] 
[Pass 0 verbosity on to GHC when building
Ian Lynagh <[EMAIL PROTECTED]>**20070110174050] 
[More verbosity tweaking
Ian Lynagh <[EMAIL PROTECTED]>**20070110172956] 
[Rejig verbosity levels a bit; 1 is now the default (was 0)
Ian Lynagh <[EMAIL PROTECTED]>**20070110165149] 
[Make system tweaks to avoid cabal thinking it isn't bootstrapped when running the testsuite
Ian Lynagh <[EMAIL PROTECTED]>**20070110162940] 
[Typo
Ian Lynagh <[EMAIL PROTECTED]>**20070110154617] 
[Refer to the right variables
Ian Lynagh <[EMAIL PROTECTED]>**20070110151326] 
[Give unrecognised flags more clearly
Ian Lynagh <[EMAIL PROTECTED]>**20070110144650] 
[Beautify
Ian Lynagh <[EMAIL PROTECTED]>**20070110143711] 
[Retab
Ian Lynagh <[EMAIL PROTECTED]>**20070110143103] 
[Remove some chatter from the test scripts
Ian Lynagh <[EMAIL PROTECTED]>**20070110142756] 
[Eliminate more warnings
Ian Lynagh <[EMAIL PROTECTED]>**20070110142114] 
[More -Wall clean fixes
Ian Lynagh <[EMAIL PROTECTED]>**20070110135838] 
[Improve cleaning
Ian Lynagh <[EMAIL PROTECTED]>**20070110134230] 
[-Wall clean fixes
Ian Lynagh <[EMAIL PROTECTED]>**20070110125523
 
 This patch is sponsored by Hac 07.
 Have you hacked a lambda today?
] 
[Fix non-fatal problem with 'setup haddock' for an exe package
Simon Marlow <[EMAIL PROTECTED]>**20070109133751
 For some unknown reason, we were passing --use-package=P to haddock,
 where P is the name of the current executable package.  This can never
 work, since P is not a library and will not be installed.  Fortunately
 Haddock ignores the error and continues anyway.
 
] 
[Set the Cabal version when building via the fptools build system
[EMAIL PROTECTED]
 
 Without this patch, Cabal is effectively "version-less" and all .cabal
 files with a version requirement are unusable. Therefore I think that
 this patch (or at least something equivalent) should be pushed to the
 6.6.1 branch, too.
] 
[added --save-configure flag to clean. got some complaints that there was no way to avoid reconfiguring after a clean.  now if you use --save-configure, you should be able to.
[EMAIL PROTECTED] 
[tiny mod to License comments
[EMAIL PROTECTED] 
[improving help output
[EMAIL PROTECTED]
 As suggested by Claus Reinke in this ticket:
 http://hackage.haskell.org/trac/hackage/ticket/105
] 
[fix ./Setup unregister --help, which was giving the help for register
Simon Marlow <[EMAIL PROTECTED]>**20061215165000] 
[Fix the links in the user guide to the API docs
Duncan Coutts <[EMAIL PROTECTED]>*-20061129131633] 
[Fix the links in the user guide to the API docs
Duncan Coutts <[EMAIL PROTECTED]>**20061129131633] 
[haddock comments for SrcDist.hs
[EMAIL PROTECTED] 
[some haddock comments for LocalBuildInfo.hs
[EMAIL PROTECTED] 
[a little comment for JHC.hs
[EMAIL PROTECTED] 
[some comments for Install.hs
[EMAIL PROTECTED] 
[some comments for Hugs.hs
[EMAIL PROTECTED] 
[haddock comments for GHC and GHCPackageConig
[EMAIL PROTECTED] 
[some comments for Configure.hs
[EMAIL PROTECTED] 
[some comments for Build.hs
[EMAIL PROTECTED] 
[minor comments and cleanup for Setup.hs
[EMAIL PROTECTED] 
[some haddock explanation of preprocessors
[EMAIL PROTECTED] 
[some comments for Package.hs
[EMAIL PROTECTED] 
[haddockizing some comments from Make.hs
[EMAIL PROTECTED] 
[adding comments to Program.hs
[EMAIL PROTECTED] 
[comments for the Program module
[EMAIL PROTECTED] 
[don't return an error code just because there's no library to register
[EMAIL PROTECTED] 
[Purely cosmetic; have '--<FOO>-args' use ARGS on their RHS rather than PATH in usage output
[EMAIL PROTECTED] 
[parse executable field as a token (as documented), rather than free text
Ross Paterson <[EMAIL PROTECTED]>**20061120093400] 
[trim trailing spaces (including CRs) from all input lines
Ross Paterson <[EMAIL PROTECTED]>**20061120092526] 
[help nhc98 find the import of programLocation
[EMAIL PROTECTED] 
[sdist: make it work on Windows platforms by simplifying 'tar' invocation. Hopefully not at the cost of other plats (i.e., as-yet untested there..)"
[EMAIL PROTECTED] 
[build: consult and use any user-provided settings for 'ld' and 'ar'
[EMAIL PROTECTED] 
[defaultUserHooks.sDistHook: pass in optional LBI to SrcDist.sdist
[EMAIL PROTECTED] 
[defaultProgramConfiguration: add 'ld' and 'tar' entries
[EMAIL PROTECTED] 
[revise Paths module for the Hugs target
Ross Paterson <[EMAIL PROTECTED]>**20061108223349
 
 When targetting Hugs, the Paths module now uses prefix-independent
 paths relative to the location of the Main module of the program,
 on all platforms.
 
 For the Hugs target, this replaces the code using GetModuleFileNameA(),
 which never worked.  Behaviour under GHC should be unchanged.
] 
[Hugs: fix location of installed package info
Ross Paterson <[EMAIL PROTECTED]>**20061021144613] 
[Fix escaping of ' chars in register.sh script.
Duncan Coutts <[EMAIL PROTECTED]>**20061016215459] 
[Tidy up command comments
Duncan Coutts <[EMAIL PROTECTED]>**20061013211158] 
[Fix getDataDir etc. when bindir=$prefix
Simon Marlow <[EMAIL PROTECTED]>**20061013100941] 
[Update text on the front page: packages can now overlap in GHC 6.6
Simon Marlow <[EMAIL PROTECTED]>**20061012114601
 
] 
[New unlit code "ported" from cpphs-1.2
Lennart Kolmodin <[EMAIL PROTECTED]>**20061009192609] 
[Share one more place where the cabal version is defined.
Duncan Coutts <[EMAIL PROTECTED]>**20061010140027] 
[Fix spelling error in error message.
Duncan Coutts <[EMAIL PROTECTED]>**20061010140013] 
[Centeralise the places that know that Cabal version number
Duncan Coutts <[EMAIL PROTECTED]>**20061010135918] 
[Remove spurious debug message.
Duncan Coutts <[EMAIL PROTECTED]>**20061010125643] 
[Bump to next unstable development version
Duncan Coutts <[EMAIL PROTECTED]>**20061010125602] 
[Make cabal know it's own version number correctly
Duncan Coutts <[EMAIL PROTECTED]>**20061010130939
 This is an unpleasent way of doing it.
 Will have to fix once and for all in the next version.
] 
[TAG 1.1.6
Duncan Coutts <[EMAIL PROTECTED]>**20061009123801] 
Patch bundle hash:
606d342d7d70b56c25c5030f2ae99a264f96662c
_______________________________________________
cabal-devel mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cabal-devel

Reply via email to