Mon Feb 16 03:46:40 NZDT 2009 [email protected] * Add flag to disable linking in build This is usefull when you just want to find compiler errors (eg. for background compilation while editing). Only implemented for GHC (others will die with an error if linking is disabled).
New patches:
[Add flag to disable linking in build [email protected]**20090215144640 Ignore-this: cedab58b8a2f4af0494fc39b3d11051d This is usefull when you just want to find compiler errors (eg. for background compilation while editing). Only implemented for GHC (others will die with an error if linking is disabled). ] { hunk ./Distribution/Simple/Build.hs 112 build pkg_descr lbi flags suffixes = do let distPref = fromFlag (buildDistPref flags) verbosity = fromFlag (buildVerbosity flags) + linking = fromFlag (buildLinking flags) initialBuildSteps distPref pkg_descr lbi verbosity suffixes setupMessage verbosity "Building" (packageId pkg_descr) case compilerFlavor (compiler lbi) of hunk ./Distribution/Simple/Build.hs 116 - GHC -> GHC.build pkg_descr lbi verbosity - JHC -> JHC.build pkg_descr lbi verbosity - Hugs -> Hugs.build pkg_descr lbi verbosity - NHC -> NHC.build pkg_descr lbi verbosity + GHC -> GHC.build pkg_descr lbi verbosity linking + JHC -> JHC.build pkg_descr lbi verbosity linking + Hugs -> Hugs.build pkg_descr lbi verbosity linking + NHC -> NHC.build pkg_descr lbi verbosity linking _ -> die ("Building is not supported with this compiler.") makefile :: PackageDescription -- ^mostly information from the .cabal file hunk ./Distribution/Simple/GHC.hs 461 -- |Building for GHC. If .ghc-packages exists and is readable, add -- it to the command-line. -build :: PackageDescription -> LocalBuildInfo -> Verbosity -> IO () -build pkg_descr lbi verbosity = do +build :: PackageDescription -> LocalBuildInfo -> Verbosity -> Bool -> IO () +build pkg_descr lbi verbosity linking = do let pref = buildDir lbi pkgid = packageId pkg_descr runGhcProg = rawSystemProgramConf verbosity ghcProgram (withPrograms lbi) hunk ./Distribution/Simple/GHC.hs 516 | filename <- cSources libBi] -- link: - info verbosity "Linking..." - let cObjs = map (`replaceExtension` objExtension) (cSources libBi) - cSharedObjs = map (`replaceExtension` ("dyn_" ++ objExtension)) (cSources libBi) - vanillaLibFilePath = libTargetDir </> mkLibName pkgid - profileLibFilePath = libTargetDir </> mkProfLibName pkgid - sharedLibFilePath = libTargetDir </> mkSharedLibName pkgid - (compilerId (compiler lbi)) - ghciLibFilePath = libTargetDir </> mkGHCiLibName pkgid + when linking $ do + info verbosity "Linking..." + let cObjs = map (`replaceExtension` objExtension) (cSources libBi) + cSharedObjs = map (`replaceExtension` ("dyn_" ++ objExtension)) (cSources libBi) + vanillaLibFilePath = libTargetDir </> mkLibName pkgid + profileLibFilePath = libTargetDir </> mkProfLibName pkgid + sharedLibFilePath = libTargetDir </> mkSharedLibName pkgid + (compilerId (compiler lbi)) + ghciLibFilePath = libTargetDir </> mkGHCiLibName pkgid hunk ./Distribution/Simple/GHC.hs 526 - stubObjs <- fmap catMaybes $ sequence - [ findFileWithExtension [objExtension] [libTargetDir] - (ModuleName.toFilePath x ++"_stub") - | x <- libModules pkg_descr ] - stubProfObjs <- fmap catMaybes $ sequence - [ findFileWithExtension ["p_" ++ objExtension] [libTargetDir] - (ModuleName.toFilePath x ++"_stub") - | x <- libModules pkg_descr ] - stubSharedObjs <- fmap catMaybes $ sequence - [ findFileWithExtension ["dyn_" ++ objExtension] [libTargetDir] - (ModuleName.toFilePath x ++"_stub") - | x <- libModules pkg_descr ] + stubObjs <- fmap catMaybes $ sequence + [ findFileWithExtension [objExtension] [libTargetDir] + (ModuleName.toFilePath x ++"_stub") + | x <- libModules pkg_descr ] + stubProfObjs <- fmap catMaybes $ sequence + [ findFileWithExtension ["p_" ++ objExtension] [libTargetDir] + (ModuleName.toFilePath x ++"_stub") + | x <- libModules pkg_descr ] + stubSharedObjs <- fmap catMaybes $ sequence + [ findFileWithExtension ["dyn_" ++ objExtension] [libTargetDir] + (ModuleName.toFilePath x ++"_stub") + | x <- libModules pkg_descr ] hunk ./Distribution/Simple/GHC.hs 539 - hObjs <- getHaskellObjects pkg_descr libBi lbi - pref objExtension True - hProfObjs <- - if (withProfLib lbi) - then getHaskellObjects pkg_descr libBi lbi - pref ("p_" ++ objExtension) True - else return [] - hSharedObjs <- - if (withSharedLib lbi) - then getHaskellObjects pkg_descr libBi lbi - pref ("dyn_" ++ objExtension) False - else return [] + hObjs <- getHaskellObjects pkg_descr libBi lbi + pref objExtension True + hProfObjs <- + if (withProfLib lbi) + then getHaskellObjects pkg_descr libBi lbi + pref ("p_" ++ objExtension) True + else return [] + hSharedObjs <- + if (withSharedLib lbi) + then getHaskellObjects pkg_descr libBi lbi + pref ("dyn_" ++ objExtension) False + else return [] hunk ./Distribution/Simple/GHC.hs 552 - unless (null hObjs && null cObjs && null stubObjs) $ do - -- first remove library files if they exists - sequence_ - [ removeFile libFilePath `catchIO` \_ -> return () - | libFilePath <- [vanillaLibFilePath, profileLibFilePath - ,sharedLibFilePath, ghciLibFilePath] ] + unless (null hObjs && null cObjs && null stubObjs) $ do + -- first remove library files if they exists + sequence_ + [ removeFile libFilePath `catchIO` \_ -> return () + | libFilePath <- [vanillaLibFilePath, profileLibFilePath + ,sharedLibFilePath, ghciLibFilePath] ] hunk ./Distribution/Simple/GHC.hs 559 - let arVerbosity | verbosity >= deafening = "v" - | verbosity >= normal = "" - | otherwise = "c" - arArgs = ["q"++ arVerbosity] - ++ [vanillaLibFilePath] - arObjArgs = - hObjs - ++ map (pref </>) cObjs - ++ stubObjs - arProfArgs = ["q"++ arVerbosity] - ++ [profileLibFilePath] - arProfObjArgs = - hProfObjs - ++ map (pref </>) cObjs - ++ stubProfObjs - ldArgs = ["-r"] - ++ ["-o", ghciLibFilePath <.> "tmp"] - ldObjArgs = - hObjs - ++ map (pref </>) cObjs - ++ stubObjs - ghcSharedObjArgs = - hSharedObjs - ++ map (pref </>) cSharedObjs - ++ stubSharedObjs - -- After the relocation lib is created we invoke ghc -shared - -- with the dependencies spelled out as -package arguments - -- and ghc invokes the linker with the proper library paths - ghcSharedLinkArgs = - [ "-no-auto-link-packages", - "-shared", - "-dynamic", - "-o", sharedLibFilePath ] - ++ ghcSharedObjArgs - ++ ["-package-name", display pkgid ] - ++ (concat [ ["-package", display pkg] | pkg <- packageDeps lbi ]) - ++ ["-l"++extraLib | extraLib <- extraLibs libBi] - ++ ["-L"++extraLibDir | extraLibDir <- extraLibDirs libBi] + let arVerbosity | verbosity >= deafening = "v" + | verbosity >= normal = "" + | otherwise = "c" + arArgs = ["q"++ arVerbosity] + ++ [vanillaLibFilePath] + arObjArgs = + hObjs + ++ map (pref </>) cObjs + ++ stubObjs + arProfArgs = ["q"++ arVerbosity] + ++ [profileLibFilePath] + arProfObjArgs = + hProfObjs + ++ map (pref </>) cObjs + ++ stubProfObjs + ldArgs = ["-r"] + ++ ["-o", ghciLibFilePath <.> "tmp"] + ldObjArgs = + hObjs + ++ map (pref </>) cObjs + ++ stubObjs + ghcSharedObjArgs = + hSharedObjs + ++ map (pref </>) cSharedObjs + ++ stubSharedObjs + -- After the relocation lib is created we invoke ghc -shared + -- with the dependencies spelled out as -package arguments + -- and ghc invokes the linker with the proper library paths + ghcSharedLinkArgs = + [ "-no-auto-link-packages", + "-shared", + "-dynamic", + "-o", sharedLibFilePath ] + ++ ghcSharedObjArgs + ++ ["-package-name", display pkgid ] + ++ (concat [ ["-package", display pkg] | pkg <- packageDeps lbi ]) + ++ ["-l"++extraLib | extraLib <- extraLibs libBi] + ++ ["-L"++extraLibDir | extraLibDir <- extraLibDirs libBi] hunk ./Distribution/Simple/GHC.hs 598 - runLd ldLibName args = do - exists <- doesFileExist ldLibName - -- This method is called iteratively by xargs. The - -- output goes to <ldLibName>.tmp, and any existing file - -- named <ldLibName> is included when linking. The - -- output is renamed to <libName>. - rawSystemProgramConf verbosity ldProgram (withPrograms lbi) - (args ++ if exists then [ldLibName] else []) - renameFile (ldLibName <.> "tmp") ldLibName + runLd ldLibName args = do + exists <- doesFileExist ldLibName + -- This method is called iteratively by xargs. The + -- output goes to <ldLibName>.tmp, and any existing file + -- named <ldLibName> is included when linking. The + -- output is renamed to <libName>. + rawSystemProgramConf verbosity ldProgram (withPrograms lbi) + (args ++ if exists then [ldLibName] else []) + renameFile (ldLibName <.> "tmp") ldLibName hunk ./Distribution/Simple/GHC.hs 608 - runAr = rawSystemProgramConf verbosity arProgram (withPrograms lbi) + runAr = rawSystemProgramConf verbosity arProgram (withPrograms lbi) hunk ./Distribution/Simple/GHC.hs 610 - --TODO: discover this at configure time or runtime on unix - -- The value is 32k on Windows and posix specifies a minimum of 4k - -- but all sensible unixes use more than 4k. - -- we could use getSysVar ArgumentLimit but that's in the unix lib - maxCommandLineSize = 30 * 1024 + --TODO: discover this at configure time or runtime on unix + -- The value is 32k on Windows and posix specifies a minimum of 4k + -- but all sensible unixes use more than 4k. + -- we could use getSysVar ArgumentLimit but that's in the unix lib + maxCommandLineSize = 30 * 1024 hunk ./Distribution/Simple/GHC.hs 616 - ifVanillaLib False $ xargs maxCommandLineSize - runAr arArgs arObjArgs + ifVanillaLib False $ xargs maxCommandLineSize + runAr arArgs arObjArgs hunk ./Distribution/Simple/GHC.hs 619 - ifProfLib $ xargs maxCommandLineSize - runAr arProfArgs arProfObjArgs + ifProfLib $ xargs maxCommandLineSize + runAr arProfArgs arProfObjArgs hunk ./Distribution/Simple/GHC.hs 622 - ifGHCiLib $ xargs maxCommandLineSize - (runLd ghciLibFilePath) ldArgs ldObjArgs + ifGHCiLib $ xargs maxCommandLineSize + (runLd ghciLibFilePath) ldArgs ldObjArgs hunk ./Distribution/Simple/GHC.hs 625 - ifSharedLib $ runGhcProg ghcSharedLinkArgs + ifSharedLib $ runGhcProg ghcSharedLinkArgs -- build any executables withExe pkg_descr $ \...@executable { exeName = exeName', modulePath = modPath } -> do hunk ./Distribution/Simple/GHC.hs 680 -- with profiling. This is because the code that TH needs to -- run at compile time needs to be the vanilla ABI so it can -- be loaded up and run by the compiler. - when (withProfExe lbi && TemplateHaskell `elem` extensions exeBi) + when (linking && withProfExe lbi && TemplateHaskell `elem` extensions exeBi) (runGhcProg (binArgs False False)) hunk ./Distribution/Simple/GHC.hs 683 - runGhcProg (binArgs True (withProfExe lbi)) + runGhcProg (binArgs linking (withProfExe lbi)) -- | Filter the "-threaded" flag when profiling as it does not -- work with ghc-6.8 and older. hunk ./Distribution/Simple/Hugs.hs 136 -- Building -- |Building a package for Hugs. -build :: PackageDescription -> LocalBuildInfo -> Verbosity -> IO () -build pkg_descr lbi verbosity = do +build :: PackageDescription -> LocalBuildInfo -> Verbosity -> Bool -> IO () +build pkg_descr lbi verbosity linking = do + -- TODO use linking flag to enable/disable linking + unless linking $ die "Disabling link stage is not supported by cabal for JHC" let pref = scratchDir lbi createDirectoryIfMissingVerbose verbosity True pref withLib pkg_descr () $ \ l -> do hunk ./Distribution/Simple/JHC.hs 83 import Distribution.Compat.ReadP ( readP_to_S, many, skipSpaces ) +import Control.Monad ( unless ) import Data.List ( nub ) import Data.Char ( isSpace ) hunk ./Distribution/Simple/JHC.hs 135 -- | Building a package for JHC. -- Currently C source files are not supported. -build :: PackageDescription -> LocalBuildInfo -> Verbosity -> IO () -build pkg_descr lbi verbosity = do +build :: PackageDescription -> LocalBuildInfo -> Verbosity -> Bool -> IO () +build pkg_descr lbi verbosity linking = do + -- TODO use linking flag to enable/disable linking + unless linking $ die "Disabling link stage is not supported by cabal for JHC" let Just jhcProg = lookupProgram jhcProgram (withPrograms lbi) withLib pkg_descr () $ \lib -> do info verbosity "Building library..." hunk ./Distribution/Simple/NHC.hs 135 -- |FIX: For now, the target must contain a main module. Not used -- ATM. Re-add later. -build :: PackageDescription -> LocalBuildInfo -> Verbosity -> IO () -build pkg_descr lbi verbosity = do +build :: PackageDescription -> LocalBuildInfo -> Verbosity -> Bool -> IO () +build pkg_descr lbi verbosity linking = do let conf = withPrograms lbi Just nhcProg = lookupProgram nhcProgram conf withLib pkg_descr () $ \lib -> do hunk ./Distribution/Simple/NHC.hs 174 (commonCcArgs ++ ["-c", cfile, "-o", ofile]) -} -- link: - info verbosity "Linking..." - let --cObjs = [ targetDir </> cFile `replaceExtension` objExtension - -- | cFile <- cSources bi ] - libFilePath = targetDir </> mkLibName (packageId pkg_descr) - hObjs = [ targetDir </> ModuleName.toFilePath m <.> objExtension - | m <- modules ] + when linking $ do + info verbosity "Linking..." + let --cObjs = [ targetDir </> cFile `replaceExtension` objExtension + -- | cFile <- cSources bi ] + libFilePath = targetDir </> mkLibName (packageId pkg_descr) + hObjs = [ targetDir </> ModuleName.toFilePath m <.> objExtension + | m <- modules ] hunk ./Distribution/Simple/NHC.hs 182 - unless (null hObjs {-&& null cObjs-}) $ do - -- first remove library if it exists - removeFile libFilePath `catchIO` \_ -> return () + unless (null hObjs {-&& null cObjs-}) $ do + -- first remove library if it exists + removeFile libFilePath `catchIO` \_ -> return () hunk ./Distribution/Simple/NHC.hs 186 - let arVerbosity | verbosity >= deafening = "v" - | verbosity >= normal = "" - | otherwise = "c" + let arVerbosity | verbosity >= deafening = "v" + | verbosity >= normal = "" + | otherwise = "c" hunk ./Distribution/Simple/NHC.hs 190 - rawSystemProgramConf verbosity arProgram (withPrograms lbi) $ - ["q"++ arVerbosity, libFilePath] - ++ hObjs --- ++ cObjs + rawSystemProgramConf verbosity arProgram (withPrograms lbi) $ + ["q"++ arVerbosity, libFilePath] + ++ hObjs +-- ++ cObjs withExe pkg_descr $ \exe -> do when (dropExtension (modulePath exe) /= exeName exe) $ hunk ./Distribution/Simple/NHC.hs 210 srcDirs = nub (map takeDirectory (modulePath exe : inFiles)) destDirs = map (exeDir </>) srcDirs mapM_ (createDirectoryIfMissingVerbose verbosity True) destDirs + -- TODO use linking flag to enable/disable linking + unless linking $ die "Disabling link stage is not supported by cabal for NHC" rawSystemProgramConf verbosity hmakeProgram conf $ ["-hc=" ++ programPath nhcProg] ++ nhcVerbosityOptions verbosity hunk ./Distribution/Simple/Setup.hs 1155 buildProgramPaths :: [(String, FilePath)], buildProgramArgs :: [(String, [String])], buildDistPref :: Flag FilePath, - buildVerbosity :: Flag Verbosity + buildVerbosity :: Flag Verbosity, + buildLinking :: Flag Bool } deriving Show hunk ./Distribution/Simple/Setup.hs 1169 buildProgramPaths = mempty, buildProgramArgs = [], buildDistPref = Flag defaultDistPref, - buildVerbosity = Flag normal + buildVerbosity = Flag normal, + buildLinking = Flag True } buildCommand :: ProgramConfiguration -> CommandUI BuildFlags hunk ./Distribution/Simple/Setup.hs 1181 longDesc = Nothing options showOrParseArgs = optionVerbosity buildVerbosity (\v flags -> flags { buildVerbosity = v }) + + : option "" ["linking"] + "linking stage" + buildLinking (\v flags -> flags { buildLinking = v }) + (boolOpt [] []) + : optionDistPref buildDistPref (\d flags -> flags { buildDistPref = d }) showOrParseArgs hunk ./Distribution/Simple/Setup.hs 1205 buildProgramPaths = mempty, buildProgramArgs = mempty, buildVerbosity = mempty, - buildDistPref = mempty + buildDistPref = mempty, + buildLinking = mempty } mappend a b = BuildFlags { buildProgramPaths = combine buildProgramPaths, hunk ./Distribution/Simple/Setup.hs 1212 buildProgramArgs = combine buildProgramArgs, buildVerbosity = combine buildVerbosity, - buildDistPref = combine buildDistPref + buildDistPref = combine buildDistPref, + buildLinking = combine buildLinking } where combine field = field a `mappend` field b } Context: [Only print message about ignoring -threaded if its actually present Duncan Coutts <[email protected]>**20090206174707] [Filter ghc-options -threaded for libs too Duncan Coutts <[email protected]>**20090125145035] [Don't build ghci lib if we're not making vanilla libs Duncan Coutts <[email protected]>**20090206173914 As the .o files will not exist. ] [Correct docdir -> mandir in InstallDirs Samuel Bronson <[email protected]>**20090203043338] [Fix compat functions for setting file permissions on windows Duncan Coutts <[email protected]>**20090205224415 Spotted by Dominic Steinitz ] [Improve the error message for missing foreign libs and make it fatal Duncan Coutts <[email protected]>**20090131184813 The check should now be accurate enough that we can make it an error rather than just a warning. ] [Use the cc, cpp and ld options when checking foreign headers and libs Duncan Coutts <[email protected]>**20090131184016 In partiular this is needed for packages that use ./configure scripts to write .buildinfo files since they typically do not split the cpp/cc/ldoptions into the more specific fields. ] [#262 iterative tests for foreign dependencies Gleb Alexeyev <[email protected]>**20090130120228 Optimize for succesful case. First try all libs and includes in one command, proceed with further tests only if the first test fails. The same goes for libs and headers: look for an offending one only when overall test fails. ] [Do the check for foreign libs after running configure Duncan Coutts <[email protected]>**20090131182213 This lets us pick up build info discovered by the ./configure script ] [Warn if C dependencies not found (kind of fixes #262) [email protected]**20090126185832 This is just a basic check - generate a sample program and check if it compiles and links with relevant flags. Error messages (warning messages, actually) could use some improvement. ] [move imports outside ifdef GHC Ross Paterson <[email protected]>**20090130153505] [Make the Compat.CopyFile module with with old and new ghc Duncan Coutts <[email protected]>**20090129225423] [Export setFileOrdinary and setFileExecutable from Compat.CopyFile Duncan Coutts <[email protected]>**20090129173413] [Use copyOrdinaryFile and copyExecutableFile instead of copyFile Duncan Coutts <[email protected]>**20090128194143 This is a minimal patch for the Cabal-1.6 branch only. ] [Add Distribution.Compat.CopyFile module Duncan Coutts <[email protected]>**20090128181115 This is to work around the file permissions problems with the standard System.Directory.copyFile function. When installing files we do not want to copy permissions or attributes from the source files. On unix we want to use specific permissions and on windows we want to inherit default permissions. On unix: copyOrdinaryFile sets the permissions to -rw-r--r-- copyExecutableFile sets the permissions to -rwxr-xr-x ] [Update changelog for 1.6.0.2 Duncan Coutts <[email protected]>**20090123175629] [Fix installIncludeFiles to create target directories properly Duncan Coutts <[email protected]>**20090122004836 Previously for 'install-includes: subdir/blah.h' we would not create the subdir in the target location. ] [filter -threaded when profiling is on Duncan Coutts <[email protected]>**20090122014425 Fixes #317. Based on a patch by [email protected] ] [Fix openNewBinaryFile on Windows with ghc-6.6 Duncan Coutts <[email protected]>**20090122172100 fdToHandle calls fdGetMode which does not work with ghc-6.6 on windows, the workaround is not to call fdToHandle, but call openFd directly. Bug reported by Alistair Bayley, ticket #473. ] [Make 'ghc-options: -O0' a warning rather than an error Duncan Coutts <[email protected]>**20090118141949] [Improve runE parse error message Duncan Coutts <[email protected]>**20090116133214 Only really used in parsing config files derived from command line flags. ] [Ban ghc-options: --make Duncan Coutts <[email protected]>**20081223170621 I dunno, some people... ] [Update changelog for 1.6.0.2 release Duncan Coutts <[email protected]>**20081211142202] [Fix configCompilerAux to consider user-supplied program flags Duncan Coutts <[email protected]>**20081209193320 This fixes a bug in cabal-install ] [Swap the order of global usage messages Duncan Coutts <[email protected]>**20090113191810 Put the more important one first. ] [Enable the global command usage to be set Duncan Coutts <[email protected]>**20090113181303 extend it rather than overriding it. Also rearrange slightly the default global --help output. ] [Bump version number to 1.6.0.2 Duncan Coutts <[email protected]>**20081210231021] [Fake support for NamedFieldPuns in ghc-6.8 Duncan Coutts <[email protected]>**20081208180018 Implement it in terms of the -XRecordPuns which was accidentally added in ghc-6.8 and deprecates in 6.10 in favor of NamedFieldPuns So this is for compatability so we can tell package authors always to use NamedFieldPuns instead. ] [Make getting ghc supported language extensions its own function Duncan Coutts <[email protected]>**20081208175815] [Distributing a package with no synopsis and no description is inexcusable Duncan Coutts <[email protected]>**20081205160719 Previously if one or the other or both were missing we only warned. Now if neither are given it's an error. We still warn about either missing. ] [Remove accidentally added bianry file Duncan Coutts <[email protected]>**20081203000824] [Fix #396 and add let .Haddock find autogen modules Andrea Vezzosi <[email protected]>**20081201114853] [Fix the date in the LICENSE file Duncan Coutts <[email protected]>**20081202161457] [Improve the error on invalid file globs slightly Duncan Coutts <[email protected]>**20081202135335] [Update changelog for 1.6.0.x fixes Duncan Coutts <[email protected]>**20081122145758] [Make auto-generated *_paths.hs module warning-free. Thomas Schilling <[email protected]>**20081106142734 On newer GHCs using {-# OPTIONS_GHC -fffi #-} gives a warning which can lead to a compile failure when -Werror is activated. We therefore emit this option if we know that the LANGUAGE pragma is supported (ghc >= 6.6.1). ] [Escape ld-options with the -optl prefix when passing them to ghc Duncan Coutts <[email protected]>**20081103151931 Fixes ticket #389 ] [Simplify previous pkg-config fix Duncan Coutts <[email protected]>**20081101200309] [Fix bug where we'd try to configure an empty set of pkg-config packages Duncan Coutts <[email protected]>**20081101195512 This happened when the lib used pkg-config but the exe did not. It cropped up in hsSqlite3-0.0.5. ] [Ensure that the lib target directory is present when installing Duncan Coutts <[email protected]>**20081017004437 Variant on a patch from Bryan O'Sullivan ] [Add GHC 6.10.1's extensions to the list in Language.Haskell.Extension Ian Lynagh <[email protected]>**20081019141408] [Release kind is now rc Duncan Coutts <[email protected]>**20081011183201] [TAG 1.6.0.1 Duncan Coutts <[email protected]>**20081011182516] [Bump version to 1.6.0.1 Duncan Coutts <[email protected]>**20081011182459] [Do not use the new meta-data fields yet Duncan Coutts <[email protected]>**20081011182307 Avoid chicken and egg problem. We cannot upload Cabsl-1.6 to hackage until hackage is using Cabal-1.6 if it uses features that are introduced in 1.6. So just comment them out for now. ] [Export a compat function for older Setup.hs scripts Duncan Coutts <[email protected]>**20081011182131 Makes it possible for alex and happy to work with cabal-1.2 -> 1.6 ] [Fix instructions in README for building with 6.6 and filepath Duncan Coutts <[email protected]>**20081011002819] [Update release procedure in Makefile Duncan Coutts <[email protected]>**20081010181445 Building the haddock docs requires building first. Arguably this is a Cabal bug. It should probably generate the "autogen" files for haddock and not just for build. ] [TAG 1.6.0.0 Duncan Coutts <[email protected]>**20081010061435] [Bump version number to 1.6.0.0 Duncan Coutts <[email protected]>**20081010052409] [Update changelog Duncan Coutts <[email protected]>**20081010052354] [Remove the releaseNotes file Duncan Coutts <[email protected]>**20081010052101 It did not actually contain any release notes and just duplicated information in the README which was confusing. ] [Merge the info from the releaseNotes file into the README file Duncan Coutts <[email protected]>**20081010052020] [Fix haddock comment for haddock-0.8 Duncan Coutts <[email protected]>**20081010050913] [Fix parsing of ld,cc,cpp-options for flags containing ',' Duncan Coutts <[email protected]>**20081010050829 The ',' character is not used as a separator and is allowed within flag tokens. Fixes at least HsPerl5. ] [Update versions in regression check script Duncan Coutts <[email protected]>**20081009223429] [Bump devel version number to 1.5.6 Duncan Coutts <[email protected]>**20081009223350 To make easier to track recent Cabal / cabal-install changes ] [Update changelog Duncan Coutts <[email protected]>**20081009223330] [Update the README Duncan Coutts <[email protected]>**20081009221851] [Make sdist work for libs that use the Paths_pkgname module Duncan Coutts <[email protected]>**20081009214507 Do it by just filtering that module out of the package description before running sdist etc. This isn't lovely because it steals that module name from the module namespace but at least it now works. Thanks to Jean-Philippe Bernardy for the first iteration of this patch. ] [xargs -s breaks solaris Duncan Coutts <[email protected]>**20081008185041 Hopefully we can figure out a better fix for recent cygwin versions of xargs which are apparently broken. rolling back: Wed Oct 8 08:44:10 PDT 2008 Clemens Fruhwirth <[email protected]> * Also respect the max. command line size in Makefile driven builds M ./Distribution/Simple/GHC.hs -7 +13 M ./Distribution/Simple/GHC/Makefile.hs -1 +1 M ./Distribution/Simple/GHC/Makefile.in -1 +1 ] [Also respect the max. command line size in Makefile driven builds Clemens Fruhwirth <[email protected]>**20081008154410] [add missing exeExtension when stripping an executable Simon Marlow <[email protected]>**20081007134757] [Add -no-auto-link-packages also to Makefile driven build Clemens Fruhwirth <[email protected]>**20081007095454] [Also install dynamically linked executable (when present) Clemens Fruhwirth <[email protected]>**20081006095107] [Use "-no-auto-link-packages" when using GHC to link Ian Lynagh <[email protected]>**20081004111103 When making packages like ghc-prim we need GHC to not automatically try to link with base and haskell98. ] [Add a few type sigs to help hugs and as documentation Duncan Coutts <[email protected]>**20081007214120 Thanks to Dimitry and Ross for identifying the problem. ] [Relax dependencyInconsistencies to allow the base-3,4 thing Duncan Coutts <[email protected]>**20081002074142 Previously we said a package graph was inconsistent if two dependencies on the same package name specified different versions. Now we say that two such dependencies on different versions are ok if there is a direct dependency between those two package versions. So if your package graph ends up with both base 3 and base 4 in it, then that's ok because base 3 directly depends on base 4, so we declare it not to be an inconsistency. This removes the scary warnings at configure time (fixing ticket #366) and also adjusts the invariant and assertion of the InstallPlan ADT in cabal-install. ] [Document the bug-reports field Duncan Coutts <[email protected]>**20081001042635] [Add bug-reports field to Cabal.cabal Duncan Coutts <[email protected]>**20081001035605] [Add bug-reports url field Duncan Coutts <[email protected]>**20081001035516 Ticket #323 ] [Update the package description a bit Duncan Coutts <[email protected]>**20081001034350] [Specify a source repository for Cabal in Cabal.cabal Duncan Coutts <[email protected]>**20081001034325] [Document the source-repository stuff Duncan Coutts <[email protected]>**20081001033928] [Add some checks on the repository sections Duncan Coutts <[email protected]>**20081001033755] [Use unknown rather than specific other repo kinds Duncan Coutts <[email protected]>**20081001033637 We can still add more as necessary ] [Add support for specifying source repos in .cabal files Duncan Coutts <[email protected]>**20080930222708 Ticket #58. Does not yet include checking. ] [Simplify parsing sections in the .cabal file Duncan Coutts <[email protected]>**20080930215509 Allow flags, lib and exes in any order and handle unknown sections better. ] [Fix how Cabal makes the value for __GLASGOW_HASKELL__ Ian Lynagh <[email protected]>**20080920212207 6.10.x was giving us 601 rather than 610. ] [Treat "cabal --flag command" as "cabal command --flag" Duncan Coutts <[email protected]>**20080928070627 eg "cabal -v configure" to mean "cabal configure -v" For flags that are not recognised as global flags, pass them on to the sub-command. ] [Update the version number in the Makefile Ian Lynagh <[email protected]>**20080920175306] [Correct the version number in the Makefile Ian Lynagh <[email protected]>**20080920175105] [Update build-deps Ian Lynagh <[email protected]>**20080920175053] [Fix building with GHC 6.6 Ian Lynagh <[email protected]>**20080920162927] [TAG 6.10 branch has been forked Ian Lynagh <[email protected]>**20080919123438] [TAG GHC 6.10 fork Ian Lynagh <[email protected]>**20080919005020] [Rename --distdir flag to --builddir Duncan Coutts <[email protected]>**20080920180326 Old aliases kept for compatibility ] [TAG 1.5.5 Duncan Coutts <[email protected]>**20080919142307] Patch bundle hash: 5f734f6d0f25355e830fcf3e7486560cad474bde
_______________________________________________ cabal-devel mailing list [email protected] http://www.haskell.org/mailman/listinfo/cabal-devel
