Wed Jan 28 18:11:15 GMT 2009 Duncan Coutts * Add Distribution.Compat.CopyFile module 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 Wed Jan 28 19:41:43 GMT 2009 Duncan Coutts * Use copyOrdinaryFile and copyExecutableFile instead of copyFile This is a minimal patch for the Cabal-1.6 branch only. New patches: [Add Distribution.Compat.CopyFile module Duncan Coutts **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 ] { hunk ./Cabal.cabal 109 + Distribution.Compat.CopyFile, addfile ./Distribution/Compat/CopyFile.hs hunk ./Distribution/Compat/CopyFile.hs 1 +{-# OPTIONS -cpp #-} +-- OPTIONS required for ghc-6.4.x compat, and must appear first +{-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -cpp #-} +{-# OPTIONS_NHC98 -cpp #-} +{-# OPTIONS_JHC -fcpp #-} +-- #hide +module Distribution.Compat.CopyFile ( + copyFile, + copyOrdinaryFile, + copyExecutableFile + ) where + +#ifdef __GLASGOW_HASKELL__ + +import Prelude hiding ( catch ) +import Control.Monad + ( when ) +import Control.Exception + ( throw, try, catch, bracket, bracketOnError, Exception(IOException) ) +import System.IO.Error + ( ioeSetLocation ) +import System.Directory + ( renameFile, removeFile ) +import Distribution.Compat.TempFile + ( openBinaryTempFile ) +import System.FilePath + ( takeDirectory ) +import System.IO + ( openBinaryFile, IOMode(ReadMode), hClose, hGetBuf, hPutBuf ) +import Foreign + ( allocaBytes ) + +#ifndef mingw32_HOST_OS +import System.Posix.Types + ( FileMode ) +import System.Posix.Internals + ( c_chmod ) +import Foreign.C + ( withCString, throwErrnoPathIfMinus1_ ) +#endif +#endif + + +copyOrdinaryFile, copyExecutableFile :: FilePath -> FilePath -> IO () + +#if defined(__GLASGOW_HASKELL__) && !defined(mingw32_HOST_OS) +copyOrdinaryFile fromFPath toFPath = do + copyFile fromFPath toFPath + setFileMode toFPath 0o644 -- file perms -rw-r--r-- + +copyExecutableFile fromFPath toFPath = do + copyFile fromFPath toFPath + setFileMode toFPath 0o755 -- file perms -rwxr-xr-x + +setFileMode :: FilePath -> FileMode -> IO () +setFileMode name m = + withCString name $ \s -> do + throwErrnoPathIfMinus1_ "setFileMode" name (c_chmod s m) +#else +copyOrdinaryFile = copyFile +copyExecutableFile = copyFile +#endif + +copyFile :: FilePath -> FilePath -> IO () +#ifdef __GLASGOW_HASKELL__ +copyFile fromFPath toFPath = + copy `catch` (\e -> case e of + IOException ioe -> + throw $ IOException $ ioeSetLocation ioe "copyFile" + _ -> throw e) + where copy = bracket (openBinaryFile fromFPath ReadMode) hClose $ \hFrom -> + bracketOnError openTmp cleanTmp $ \(tmpFPath, hTmp) -> + do allocaBytes bufferSize $ copyContents hFrom hTmp + hClose hTmp + renameFile tmpFPath toFPath + openTmp = openBinaryTempFile (takeDirectory toFPath) ".copyFile.tmp" + cleanTmp (tmpFPath, hTmp) = do try $ hClose hTmp + try $ removeFile tmpFPath + bufferSize = 4096 + + copyContents hFrom hTo buffer = do + count <- hGetBuf hFrom buffer bufferSize + when (count > 0) $ do + hPutBuf hTo buffer count + copyContents hFrom hTo buffer +#else +copyFile fromFPath toFPath = readFile fromFPath >>= writeFile toFPath +#endif hunk ./Makefile 16 -SOURCES=Distribution/*.hs Distribution/Simple/*.hs Distribution/PackageDescription/*.hs Distribution/Simple/GHC/*.hs Distribution/Simple/Build/*.hs +SOURCES=Distribution/*.hs Distribution/Simple/*.hs Distribution/PackageDescription/*.hs Distribution/Simple/GHC/*.hs Distribution/Simple/Build/*.hs Distribution/Compat/*.hs } [Use copyOrdinaryFile and copyExecutableFile instead of copyFile Duncan Coutts **20090128194143 This is a minimal patch for the Cabal-1.6 branch only. ] { hunk ./Distribution/Simple/GHC.hs 129 +import Distribution.Compat.CopyFile + ( copyExecutableFile ) hunk ./Distribution/Simple/GHC.hs 933 - copyFileVerbose verbosity + copyExe verbosity hunk ./Distribution/Simple/GHC.hs 970 +copyExe :: Verbosity -> FilePath -> FilePath -> IO () +copyExe verbosity src dest = do + info verbosity ("copy " ++ src ++ " to " ++ dest) + copyExecutableFile src dest + hunk ./Distribution/Simple/Haddock.hs 97 - removeDirectoryRecursive, copyFile) - + removeDirectoryRecursive) +import Distribution.Compat.CopyFile + ( copyFile ) hunk ./Distribution/Simple/Utils.hs 141 - ( copyFile, createDirectoryIfMissing, renameFile, removeDirectoryRecursive ) + ( createDirectoryIfMissing, renameFile, removeDirectoryRecursive ) hunk ./Distribution/Simple/Utils.hs 168 +import Distribution.Compat.CopyFile + ( copyOrdinaryFile ) hunk ./Distribution/Simple/Utils.hs 501 - copyFile src dest + copyOrdinaryFile src dest } Context: [Update changelog for 1.6.0.2 Duncan Coutts **20090123175629] [Fix installIncludeFiles to create target directories properly Duncan Coutts **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 **20090122014425 Fixes #317. Based on a patch by gleb.alexeev@gmail.com ] [Fix openNewBinaryFile on Windows with ghc-6.6 Duncan Coutts **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 **20090118141949] [Improve runE parse error message Duncan Coutts **20090116133214 Only really used in parsing config files derived from command line flags. ] [Ban ghc-options: --make Duncan Coutts **20081223170621 I dunno, some people... ] [Update changelog for 1.6.0.2 release Duncan Coutts **20081211142202] [Fix configCompilerAux to consider user-supplied program flags Duncan Coutts **20081209193320 This fixes a bug in cabal-install ] [Swap the order of global usage messages Duncan Coutts **20090113191810 Put the more important one first. ] [Enable the global command usage to be set Duncan Coutts **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 **20081210231021] [Fake support for NamedFieldPuns in ghc-6.8 Duncan Coutts **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 **20081208175815] [Distributing a package with no synopsis and no description is inexcusable Duncan Coutts **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 **20081203000824] [Fix #396 and add let .Haddock find autogen modules Andrea Vezzosi **20081201114853] [Fix the date in the LICENSE file Duncan Coutts **20081202161457] [Improve the error on invalid file globs slightly Duncan Coutts **20081202135335] [Update changelog for 1.6.0.x fixes Duncan Coutts **20081122145758] [Make auto-generated *_paths.hs module warning-free. Thomas Schilling **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 **20081103151931 Fixes ticket #389 ] [Simplify previous pkg-config fix Duncan Coutts **20081101200309] [Fix bug where we'd try to configure an empty set of pkg-config packages Duncan Coutts **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 **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 **20081019141408] [Release kind is now rc Duncan Coutts **20081011183201] [TAG 1.6.0.1 Duncan Coutts **20081011182516] [Bump version to 1.6.0.1 Duncan Coutts **20081011182459] [Do not use the new meta-data fields yet Duncan Coutts **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 **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 **20081011002819] [Update release procedure in Makefile Duncan Coutts **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 **20081010061435] [Bump version number to 1.6.0.0 Duncan Coutts **20081010052409] [Update changelog Duncan Coutts **20081010052354] [Remove the releaseNotes file Duncan Coutts **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 **20081010052020] [Fix haddock comment for haddock-0.8 Duncan Coutts **20081010050913] [Fix parsing of ld,cc,cpp-options for flags containing ',' Duncan Coutts **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 **20081009223429] [Bump devel version number to 1.5.6 Duncan Coutts **20081009223350 To make easier to track recent Cabal / cabal-install changes ] [Update changelog Duncan Coutts **20081009223330] [Update the README Duncan Coutts **20081009221851] [Make sdist work for libs that use the Paths_pkgname module Duncan Coutts **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 **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 * 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 **20081008154410] [add missing exeExtension when stripping an executable Simon Marlow **20081007134757] [Add -no-auto-link-packages also to Makefile driven build Clemens Fruhwirth **20081007095454] [Also install dynamically linked executable (when present) Clemens Fruhwirth **20081006095107] [Use "-no-auto-link-packages" when using GHC to link Ian Lynagh **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 **20081007214120 Thanks to Dimitry and Ross for identifying the problem. ] [Relax dependencyInconsistencies to allow the base-3,4 thing Duncan Coutts **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 **20081001042635] [Add bug-reports field to Cabal.cabal Duncan Coutts **20081001035605] [Add bug-reports url field Duncan Coutts **20081001035516 Ticket #323 ] [Update the package description a bit Duncan Coutts **20081001034350] [Specify a source repository for Cabal in Cabal.cabal Duncan Coutts **20081001034325] [Document the source-repository stuff Duncan Coutts **20081001033928] [Add some checks on the repository sections Duncan Coutts **20081001033755] [Use unknown rather than specific other repo kinds Duncan Coutts **20081001033637 We can still add more as necessary ] [Add support for specifying source repos in .cabal files Duncan Coutts **20080930222708 Ticket #58. Does not yet include checking. ] [Simplify parsing sections in the .cabal file Duncan Coutts **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 **20080920212207 6.10.x was giving us 601 rather than 610. ] [Treat "cabal --flag command" as "cabal command --flag" Duncan Coutts **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 **20080920175306] [Correct the version number in the Makefile Ian Lynagh **20080920175105] [Update build-deps Ian Lynagh **20080920175053] [Fix building with GHC 6.6 Ian Lynagh **20080920162927] [TAG 6.10 branch has been forked Ian Lynagh **20080919123438] [TAG GHC 6.10 fork Ian Lynagh **20080919005020] [Rename --distdir flag to --builddir Duncan Coutts **20080920180326 Old aliases kept for compatibility ] [TAG 1.5.5 Duncan Coutts **20080919142307] [Bump version number to 1.5.5 Duncan Coutts **20080919140130 Ready to make the 1.6 branch ] [filter mingw include directories out of rts's installDirs Ian Lynagh **20080918142958 GHC < 6.10 put "$topdir/include/mingw" in rts's installDirs. This breaks when you want to use a different gcc, so we need to filter it out. ] [Tell gcc on Windows where include/mingw is Ian Lynagh **20080918135718 We need to tell the gcc bundled with GHC on Windows where its mingw include directory is ] [On windows, fail if ghc's gcc or ld are not found Duncan Coutts **20080917235745] [Allow addKnownProgram to be used as an update, not just insert Duncan Coutts **20080917225856 ie preserves any existing user-supplied path and args ] [Cope with gcc.exe and ld.exe not being where ex expect on Windows Ian Lynagh **20080917221228] [Implement openNewBinaryFile in a Compat module Ian Lynagh **20080917171257 This is like openBinaryTempFile except it doesn't mark the permissions with 600. This means datafailes get the right permissions when they are installed. This should really be in the base package. ] [Generalise the type of onException Ian Lynagh **20080917171233 Now it matches Control.Exception's type ] [Yet another go at making gcc -B work properly on windows Duncan Coutts **20080916232553 This time it should work on linux too! But more significantly it should work when the user specifies a particular gcc. It would be very bad if the user gave an alternative gcc but we still gave it -B for the lib files of ghc's gcc. This go is rather cleaner as it uses the new program post-conf system. ] [Pass any additional gcc options through to gcc when calling hsc2hs Duncan Coutts **20080916232502] [Add an additional program post-conf action Duncan Coutts **20080916210642 The post-conf action gets given the configured program and is allowed to do more IO and can add any extra required program args. Should make it easier to do the gcc -B thing or ld -x ] [Make the new permissions compat module compile Duncan Coutts **20080916210550 Needs cpp pragma as it has to work with just ghc --make Did I ever mention I that hate cpp and compat modules? ] [Fix the env var names used in the Paths module Duncan Coutts **20080916093525 Convert any '-' in the package name to '_' when generating the path env var as most shells do not allow '-' in env var names. ] [Check for -optl-s as well as an alias of the more common -optl-Wl,-s Duncan Coutts **20080913005432] [pass -B flag to help gcc find libraries on Windows dias@eecs.harvard.edu**20080827124436] [workaround for nhc98, which does not have System.Posix.Internals Malcolm.Wallace@cs.york.ac.uk**20080915092747] [Set GHCI_LIB to "" in "Setup makefile" if GHC libs are disabled Ian Lynagh **20080913144040] [In "Setup makefile", don't build the vanilla way if it's disabled Ian Lynagh **20080913143132 This needs a bit of a kludge, as the vanilla way doesn't really exist as far as the build system is concerned. It's just the absence of way. ] [Fix the permission that we give wrapper scripts Ian Lynagh **20080913124445] [Documentation only: more typos/punctuation Tim Chevalier **20080914051331] [Documentation only: grammar fix in comment Tim Chevalier **20080914051008] [Documentation only: fix typo in comment Tim Chevalier **20080913214843] [Remove unused 'breaks' util function Duncan Coutts **20080910235804] [follow library changes Ian Lynagh **20080903223608] [Fix to compile with base-1.0:Data.List Duncan Coutts **20080904233126 which did not have isInfixOf ] [Fix cabal_macros.h for package names containing '-' Duncan Coutts **20080903220116 As with the Paths_pkgname module, we map '-' to '_' as the former is not a valid character in cpp macro identifiers. Fixes cpp redefinition warnings. First reported by gwern. ] [Pass the interfaces for the transitive set of dependencies to haddock Ian Lynagh **20080903123813 Otherwise we don't get links to types from packages that we don't directly depend on. ] [Update CPP-Options in Cabal.cabal to define CABAL_VERSION=1,5,4 Ian Lynagh **20080902170348 It was still defining CABAL_VERSION=1,5,3 ] [Add more detail to the -Werror and -fvia-C checks Duncan Coutts **20080902171413 Also, ban rather than just warn about the -optl-Wl,-s hack now that Cabal strips exes by default. ] [Haddock 2: #include Simon Marlow **20080901145843] [package concurrent not available in nhc98 Malcolm.Wallace@cs.york.ac.uk**20080902092802] [Display the right message for sdist --snapshot Duncan Coutts **20080831221756] [Bump the version number to 1.5.4 Duncan Coutts **20080831220418 due to the PackageSet/Index api changes ] [Use a hopefully more robust method of determining the gcc version Duncan Coutts **20080831220145] [Simplify the handling of --with-prog= in build/haddock commands. Duncan Coutts **20080831215551 We allow extra rgs and the location of programs to be given to the build and haddock commands, not just at configure time. The code to do this is now simpler and more general. This should not be the default use mode however since it involves configuring the programs each time where as doing it at configure time allows it to be done once and saved. Further, specifying a different version of the program at build time than at configure time is likely to fail, especially for the compiler programs. Changing the compiler really requires reconfiguring. ] [Update the haddock command help text Duncan Coutts **20080831215325 The haddock command now supports --haddock-options= ] [Add flags to build command for specifying program paths Duncan Coutts **20080831215135 So we're going to allow --with-PROG for the build and haddock commands, in addition to the existing --PROG-options= flags. ] [Use the new Program utils to simplify code in Configure Duncan Coutts **20080831215054] [Add some more handy Program utils Duncan Coutts **20080831214813 Mostly for dealing with lists of programs so that client code doesn't need quite to much flip foldl' (flip thing) Add specific helpers for reconfiguring programs and restoring a full ProgramConfiguration after usign read. ] [Don't redundantly pass programArgs in when calling programs. Duncan Coutts **20080831212526 That's already done by the Program framework so we were passing those extra args in twice. ] [Merge PackageSet and PackageIndex Duncan Coutts **20080830130250 Have just a single module that provides both the case sensitive and insensitive operations. Turns out we hardly use the case insensitive operations, and the places where we do are not performance sensitive at all. So we use the PackageSet implementation which stores the packages case sensitively and tack on the case insensitive operations but with linear time implementations rather than log time. For the merged module/type name use PackageIndex because that is what older released versions exported, so less needless client breakage. ] [Add checkPackageFileNames function to check portability of file names Duncan Coutts **20080827082349 Windows has restrictions on names of files and portable tar archives have some weird length restrictions too. Not yet used but should be used in sdist and hackage. ] [In wrappers, $executablename needs to expand to something with DESTDIR Ian Lynagh **20080828155554 The installed wrapper needs to call the executable in its final place, not inside the DESTDIR where we are constructing a package. ] [Allow passing haddock's location and options to "Setup haddock" Ian Lynagh **20080828142424] [We need to pass the CPP options to haddock 2 Ian Lynagh **20080828142303] [Add support for manually en/disabled flags Ian Lynagh **20080827170105 The immediate use for these is so that, in haddock, we can require ghc-paths normally, but in the GHC build we can manually turn off a flag so that this dependency isn't needed. We can't use a normal flag, or in the normal build Cabal would infer that the flag needs to be turned off if ghc-paths isn't available. ] [Add release date of 1.4.0.2 Duncan Coutts **20080826204810] [Ban package names that are not valid windows file names Duncan Coutts **20080826005502 At least for the purposes of distribution. So if you're on unix then you can call your package 'LPT1' if you feel you must, but you cannot distribute a package with this name. ] [Separate out and export installDirsOptions Duncan Coutts **20080826003240 The InstallDirs is a separate type so it's handy to have the command line and config file options for it available separately. It'd be useful in cabal-install for one thing. ] [Note the per-user install path on Windows in the README Duncan Coutts **20080824203923] [More changelog updates for 1.4.0.2 Duncan Coutts **20080824203744] [Teach Cabal about the PackageImports extension Ian Lynagh **20080825132352] [Rename --distpref to --distdir Duncan Coutts **20080825164258 It's more consistent with the other flag names for dirs. Kept the old name too, but it's not shown by --help. ] [We now depend on concurrent (split off from base) Ian Lynagh **20080824135145] [Bump version number to 1.5.3 Duncan Coutts **20080822160918] [Update changelog for recent 1.5.x changes Duncan Coutts **20080822160828] [Update changelog Duncan Coutts **20080802135452] [Don't pass cc-options to Haskell compilations Simon Marlow **20080821133421 This has no effect with GHC 6.9, and with earlier GHC's it was a misuse of cc-options. ] [Don't propagate cc-options to the InstalledPackageInfo Simon Marlow **20080821132551 cc-options is for options to be passed to C compilations in the current package. If we propagate those options to the InstalledPackageInfo, they get passed to C compilations in any package that depends on this one, which could be disastrous. I've seen cc-options like these: cc-options: -optc-std=c99 cc-options: -D_FILE_OFFSET_BITS=64 Cc-options: -Wall these are all clearly intended to be local, but are in fact currently propagated to all dependent packages. ] [Fix spelling of compatibility Duncan Coutts **20080818194951 At request of gwern who found that it was driving him nuts. ] [Minor info and help message improvements Duncan Coutts **20080813124957] [unbreak for non-GHC Malcolm.Wallace@cs.york.ac.uk**20080814182558] [Catch exit exceptions as well as IO exceptions after running programs Ian Lynagh **20080813213035 We need to catch IO exceptions for things like "couldn't find the program", but we also need to catch exit exceptions as Cabal uses them to signal what the program returned. ] [Fix for #333, "Setup sdist --snapshot fails" Duncan Coutts **20080821154913 Credit to Spencer Janssen. This is just a slight alternative to the fix he proposed. It simplifies prepareSnapshotTree. ] [Move Paths_pkgname and cabal_macros.h generation into their own modules Duncan Coutts **20080813193245] [fix imports for nhc98 Malcolm.Wallace@cs.york.ac.uk**20080813132112] [Add util rewriteFile :: FilePath -> String -> IO () Duncan Coutts **20080813192017 Write a file but only if it would have new content. If we would be writing the same as the existing content then leave the file as is so that we do not update the file's modification time. ] [Don't warn about missing strip.exe on Windows Duncan Coutts **20080812220415 We don't expect Windows systems to have the strip program anyway. ] [Flush stdout when printing debugging messages Duncan Coutts **20080812212236] [Add auto-generated CPP macros for package version testing Simon Marlow **20080811173016 Now when using CPP you get MIN_VERSION_(A,B,C) for each in build-depends, which is true if the version of in use is >= A.B.C, using the normal ordering on version numbers. This is done by auto-generating a header file dist/build/autogen/cabal_macros.h, and passing a -include flag when running CPP. ] [allow Cabal to use base-4 Simon Marlow **20080806130512] [Fix warnings in Windows Paths_pkgname module Duncan Coutts **20080812211349] [Fix the config-file field name of the install command's packagedb option Duncan Coutts **20080812171207] [Add alias type PackageId = PackageIdentifier Duncan Coutts **20080812171006] [Add data Platform = Platform Arch OS Duncan Coutts **20080812160941 Since we tend to pass them around together rather a lot. Also add a Text instance with a format like "i386-linux" ] [Don't use tab characters in the generated Paths module Duncan Coutts **20080812160731] [Make binary-dist do nothing in doc/Makefile, for now Ian Lynagh **20080810005135] [When running "Setup makefile", put "default: all" at the top of the Makefile Ian Lynagh **20080809211148 This make "make" work even if Makefile.local contains any targets. ] [Use 'ghc-pkg dump' instead of 'ghc-pkg describe *' David Waern**20080807190307 Does not implement lazy parsing of the output of ghc-pkg dump, so this is only a partial fix of #311. For more information about why we want to use ghc-pkg dump, see GHC ticket #2201. ] [Simplify InstalledPackageInfo parser and pretty printer Duncan Coutts **20080806122807 Using the new utils in ParseUtils. ] [Add parsse utils for simple flat formats. Duncan Coutts **20080806122613 Should help to simplify the InstalledPackageInfo parser and also for similar formats in cabal-install. ] [Tidy up the ppFields function and uses Duncan Coutts **20080806121315 Put the arguments in a more sensible order: ppFields :: [FieldDescr a] -> a -> Doc and make the implementation clearer. clean up the use of it in the PackageDescription.Parse module ] [Windows fixes Ian Lynagh **20080803201253] [setup makefile: put the source-dir suffix rules after the distdir suffix rules Simon Marlow **20080806130309 This matches the behaviour of 'setup build' works, and is robust to people accidentally having old preprocessed sources lying around in the source dir. ] [Generalise checkPackageFiles to any monad, not just IO Duncan Coutts **20080806001547 This is to let us use the same checks for virtual or in-memory file systems, like tarball contents. ] [Move parseFreeText into ParseUtils and use it more widely Duncan Coutts **20080806001352] [Document and refactor 'parsePackageDescription'. Thomas Schilling **20080804190324 Hopefully this makes this function more understandable and easier to modify. ] [Adjust registration to allow packages with no modules or objects Duncan Coutts **20080804155826 So ghc-pkg does not complain about missing files and dirs. ] [Don't try to install libHSfoo.a if the lib had no object files Duncan Coutts **20080804143817 To allow meta-packages. ] [Fix instance Monoid ConfigFlags for configStripExes Duncan Coutts **20080802002045] [Fix the Windows build Ian Lynagh **20080731194841] [Remove unused imports Ian Lynagh **20080730194526] [Make Cabal compatible with extensible exceptions Ian Lynagh **20080730183910 The code is now also more correct, e.g. when we are ignoring IO exceptions while trying to delete something, we don't also ignore timeout exceptions. ] [Document the "exposed" .cabal file field Duncan Coutts **20080731162807] [Remove unused imports Duncan Coutts **20080730182957] [Remove unused inDir util function Duncan Coutts **20080730165031] [Add an "exposed" field to the .cabal file library section Duncan Coutts **20080730164516 It's a bool flag that says if by default the library should be registered with the compiler as exposed/unhidden (for compilers which have such a concept, ie ghc). You might want to do this for packages which would otherwise pollute the module namespace or clash with other common packages. It should be very rarely used. The only current examples we know of are the ghc api package and the dph packages. ] [Rearrange the Monoid instances for Library, Executable, BuildInfo Duncan Coutts **20080730163432 No functional change, just moving code about. We now define the Monoid methods directly rather than in terms of emptyLibrary, unionLibrary etc. ] [Do the ghc rts ldOptions hack in a slightly more hygenic way Duncan Coutts **20080729195714] [Pass the right -F and --framework flags when running hsc2hs on OS X Ian Lynagh **20080729172757] [Tweak a test to not go via the pretty printer Ian Lynagh **20080729172750] [Fix linking with hsc2hs on OS X Ian Lynagh **20080729170215 We don't tell hsc2hs to link the actual Haskell packages, so with GHC's rts package we need to also filter out the -u flags. ] [Tweak whitespace Ian Lynagh **20080729163729] [Fix uses of verbosity > deafening to use >= Duncan Coutts **20080729191855 The maximum verbosity value is deafening so >= the correct test. This primarily affected haddock. ] [Do not use ',' as a list separator for the cpp/cc/ld-options fields Duncan Coutts **20080729170556 It breaks for some options like "ld-options: -Wl,-z,now" No existing .cabal files on hackage were using ',' as a list separator so this should not break anything. ] [Move docs for build-depends into the build information section Duncan Coutts **20080729162024 Since it is shared between libs and exes. Extend the documentation to describe the syntax of version constraints, including the new version range syntax "build-depends: foo ==1.2.*". ] [Remove references to cabal-setup from the documentation Duncan Coutts **20080729160950 Change to runhaskell Setup or cabal-install as appropriate. ] [Move the docs for the buildable field to a better place. Duncan Coutts **20080729160808 It doesn't need to be right up near the top. ] [Document more clearly that every modules must be listed Duncan Coutts **20080729160308 in one of the fields exposed-modules, other-modules or main-is Add an extra note to the section on the Paths_pkgname module as the fact that it's automatically generated confuses people. ] [Document the wildcard behaviour in data-files and extra-source-files fields Duncan Coutts **20080729155920] [Document the $os and $arch install path vars Duncan Coutts **20080729155654] [File globs must match at least one file or it's an error. Duncan Coutts **20080729154050] [Fix the semantics of the simple file globbing to be sane Duncan Coutts **20080729152624 I realised when I started to document it that the behaviour was not terribly consistent or sensible. The meaning now is: The limitation is that * wildcards are only allowed in place of the file name, not in the directory name or file extension. In particular, wildcards do not include directories contents recursively. Furthermore, if a wildcard is used it must be used with an extension, so "data-files: data/*" is not allowed. When matching a wildcard plus extension, a file's full extension must match exactly, so "*.gz" matches "foo.gz" but not "foo.tar.gz". The reason for providing only a very limited form of wildcard is to concisely express the common case of a large number of related files of the same file type without making it too easy to accidentally include unwanted files. ] [Allow $arch and $os in install paths. Duncan Coutts **20080729151952 Fixes ticket #312. For example a user could use: cabal configure --libsubdir="$pkgid/$compiler/$arch" if they wanted to have packages for multiple architectures co-exist in the same filestore area. ] [Use "pkg == 1.2.*" as the version wildcard syntax Duncan Coutts **20080729151612 Rather than "pkg ~ 1.2.*". This seemed to be the consensus. The syntax "pkg == 1.2.*" means "pkg >= 1.2 && < 1.3" and it is to encourage people to put upper bounds on api versions. ] [disambiguate Control.Exception.catch for nhc98 Malcolm.Wallace@cs.york.ac.uk**20080728164506] [more import qualification to help nhc98 Malcolm.Wallace@cs.york.ac.uk**20080728153629] [help nhc98's module disambiguator a bit Malcolm.Wallace@cs.york.ac.uk**20080724165753] [Pass -no-user-package-conf to ghc when not using UserPackageDB Duncan Coutts **20080729145040 Should eliminate the corner case where we're doing a global install but the user package db contains the exact same version as in the global package db. Perhaps we should warn in that case anyway since it's likely to go wrong later. ] [Substitute for $topdir when we read GHC's InstalledPackageInfo's Ian Lynagh **20080723112232] [Fix the location of gcc.exe in a Windows GHC installation Ian Lynagh **20080723101848] [Don't need the complex code in detecting hsc2hs anymore Duncan Coutts **20080720234019 Since we do not need to know if hsc2hs uses ghc or gcc as cc by default since in either case we now tell it to use gcc. ] [Always use gcc as cc with hsc2hs Duncan Coutts **20080720233759 Lookup what flags to use from the package index. Previously this was done by calling ghc as cc and passing -package flags to ghc. ghc would then lookup what extra flags to pass to gcc. We now do that ourselves directly and it's a good deal simpler and it's portable to the other haskell implementations. This is only a first go, the flags may not all be exactly right. Needs testing. ] [Add gccProgram Duncan Coutts **20080720232818 on Windows we have to find ghc's private copy of gcc.exe ] [Add PackageSet.topologicalOrder and reverseTopologicalOrder Duncan Coutts **20080720223731 with type :: PackageFixedDeps pkg => PackageSet pkg -> [pkg] ] [Change some PackageSet functions to return the package rather than the id Duncan Coutts **20080720221702 dependencyGraph and reverseDependencyClosure now return the full package rather than just the PackageIdentifier ] [Convert from PackageIndex to PackageSet Duncan Coutts **20080720194924 Turns out the feature to do case-insensitive lookups was only needed in cabal-install (and only in one little part) and elsewhere it causes problems. So use PackageSet instead. ] [If we have GHC >= 6.9 then use the new -optdep replacement flags Ian Lynagh **20080722163346] [And exitcode of 2 from ghc-pkg when doing describe '*' means no packages Ian Lynagh **20080722125759 This is a bit of a kludge around GHC's #2201, until Cabal is updated to use ghc-pkg dump. ] [Fix warnings and add a comment explaining why we pass -x to strip on OS X Ian Lynagh **20080720220851] [Pass -x to strip on OSX Duncan Coutts **20080720204609] [Generate expanded makefile rules directly, rather than using $(eval ...) Ian Lynagh **20080720194801 We used to do this with $(eval ...) and $(call ...) in the Makefile, but make 3.79.1 (which is what comes with msys) doesn't understand $(eval ...), so now we just stick the expanded loop directly into the Makefile we generate. ] [Put GHC's programArgs in GHC_OPTS when making a Makefile Ian Lynagh **20080715132429] [Pass -package-conf foo when using GHC as CC Ian Lynagh **20080713123958] [If we are using ghc as hsc2hs's cc, then tell it where package.conf is Ian Lynagh **20080713110548 if we have been told to use a specific one with --package-db ] [Fix installing datafiles Ian Lynagh **20080712173934 If datadir is foo and the datafile is bar then we should install it to $datadir/bar, not $datadir/foo/bar. ] [Fix the "Setup makefile" rules for C files Ian Lynagh **20080712173851] [If install is given a distPref, pass it on to copy and register Ian Lynagh **20080712121916] [derive Eq for ConfiguredProgram Duncan Coutts **20080711160138 a request from Saizan ] [Simplify ghc version test slightly Duncan Coutts **20080711142026] [Add a hack to copy .hs-boot files into dist/... Ian Lynagh **20080711000826 When a preprocessor generates a .hs file we need to put the .hs-boot file next to it so that GHC can find it. ] [Teach "Setup makefile" how to cope with multiple hs-source-dirs Ian Lynagh **20080711000726] [Fix some whitespace in Makefile.in Ian Lynagh **20080710231519] [In Makefile.in, put all the rules that mentions srcdir together Ian Lynagh **20080710231415] [Fix haddocking (with old haddocks?) Ian Lynagh **20080703154714] [Correct the order of args given by --PROG-options Duncan Coutts **20080710181437 They were getting reversed. Problem located by Igloo. ] [Remove the need for a compat Data.Map module Duncan Coutts **20080710154600 Stop using Map.alter, use the same solution as the PackageIndex module. ] [fix #if __GLASGOW_HASKELL__ test Ross Paterson **20080705105048 The problem is that #if __GLASGOW_HASKELL__ < NNN is also true for non-GHC. It should be #if __GLASGOW_HASKELL__ && __GLASGOW_HASKELL__ < NNN ] [help nhc98's import overlap resolver Malcolm.Wallace@cs.york.ac.uk**20080704140613] [massage a pattern-with-context around nhc98's typechecker Malcolm.Wallace@cs.york.ac.uk**20080704140541] [Fix using specified package databases Ian Lynagh **20080703001216 If we are using a specified package database, we need to tell GHC what it is when building ] [Fix the build with GHC 6.4.2: Data.Map.alter doesn't exist Ian Lynagh **20080703001151] [Allow installing executables in-place, and using shell script wrappers Ian Lynagh **20080629164939 GHC-only currently. ] [haddock typo Ian Lynagh **20080629114342] [Fix a haddock typo Ian Lynagh **20080629114239] [Update .darcs-boring Ian Lynagh **20080627182013] [TAG 2008-05-28 Ian Lynagh **20080528004259] [Remove the SetupWrapper module Duncan Coutts **20080628173010 It's not used in Cabal itself and while cabal-install used it previously, it now has its own extended implementation. ] [Update module headers Duncan Coutts **20080628172550 Use cabal-devel@haskell.org as the maintainer in most cases except for a few which were pre-existing modules copied from elsewhere or modules like L.H.Extension which really belong to libraries@haskell.org Remove the useless stability module. We have more detailed information on stability elsewhere (in the version number and user guide). Add more top level module documentation, taken from the source guide. ] [Whitespace changes, convert tabs to spaces Duncan Coutts **20080626200933] [Remove a couple old deprecated empty modules Duncan Coutts **20080626195204] [Add ModuleName as a new type instead of using String everywhere Duncan Coutts **20080626192939] [Tweaks to the readme, hopefully will reduce confusion Duncan Coutts **20080625232051] [Add compat InstalledPackageInfo types for older GHCs Duncan Coutts **20080621013727 We need these types for their Read instances so that we can still read older GHCs package db files when we make changes to the current InstalledPackageInfo type, or the types contained in it, like PackageIdentifier or License. ] [Add simple file name globbing (*) to data-files and extra-source-files Duncan Coutts **20080626171424] [Use conservative render style for display Duncan Coutts **20080619222258] [Include trailing newline in hscolour command description Duncan Coutts **20080619220940] [Add PackageSet, like PackageIndex but case sensitive Duncan Coutts **20080614003705 Actually it turns out that we don't need case insensitivity in many cases, mosty just for simple lookups in the UI. For everything else the ordinary Ord instance is much simpler. The fact that listing the contents of a PackageIndex doesn't come out in Ord order actually causes real problems in cabal-install and necessitates re-sorting. So we should move to using PackageSet in most cases and just leave the search and lookup operations in PackageIndex. ] [Add PackageName as a newtype Duncan Coutts **20080614002926] [No more need for the distinction between null and emptyBuildInfo Duncan Coutts **20080614001654 Now that we have removed the hsSourceDirs = [currentDir] default from emptyBuildInfo it is now equal to nullBuildInfo. ] [Add version wildcard syntax Duncan Coutts **20080619175006 build-depends: foo ~1.2.* means: build-depends: foo >=1.2 && <1.3 It's also valid everywhere else version ranges are used. ] [haddock-2.2 and later do now support the --hoogle flag Duncan Coutts **20080613205445] ['.' should not always be in hs-source dirs Duncan Coutts **20080613230352 We changed the parsing of list fields in the .cabal file so that it adds to the current value rather than replacing it. This allows you to put multiple entries for a list field and they all get concatenated. However that means that the '.' in the hsSourceDirs of emptyBuildInfo is always added to and not replaced like we did previously. That's not what we want in this case. We want to use '.' for hsSourceDirs *only* if hsSourceDirs is otherwise null. As it happens, due to the way the configurations code works, we're already filling in the default if it'd otherwise be null so we do not need '.' in the emptyBuildInfo at all. ] [Fix css location in generation of user guide Duncan Coutts **20080617133811] [Update changelog for 1.4.0.1 Duncan Coutts **20080617130434] [Makefile tweak, setup depends on Setup.hs Duncan Coutts **20080616175446] [force results inside withHaskellFile Ross Paterson **20080614160707 withUTF8FileContents now closes the file, so we need to force what we're computing from the contents before it's gone. ] [construct InstalledPackageInfo from scratch rather than by overriding Duncan Coutts **20080616171505 It means we catch any fields that get added. As it happens we were missing a field, though its value is supposed to be just [] which is the same value as we got from the default emptyInstalledPackageInfo. ] [Include the readme and the changelog in the tarball Duncan Coutts **20080612190558] [Move the mkGHCMakefile.sh out of the root dir Duncan Coutts **20080612190317 Having it there confuses people. They think they have to run it as part of the install process. ] [Put upper bounds on all the build-depends Duncan Coutts **20080612174958] [Add the 1.4.0.0 release to the changelog Duncan Coutts **20080612164242] [Add the 1.2.4.0 release to the changelog Duncan Coutts **20080612164144] [Update the README and convert it to markdown syntax Duncan Coutts **20080612162906] [Update the release notes Duncan Coutts **20080612154624] [Update copyright and authors list in the .cabal file Duncan Coutts **20080612154444] [base-1.0 does not have Data.Map.alter so use insertWith instead Duncan Coutts **20080612154309] [Lift the restriction that libraries must have exposed-modules Duncan Coutts **20080612092924 This allows libs that have only private modules or C code. This might be used to make libs that have non-exposed modules and only export C APIs. It could also be used to make packages that consist only of C code. That might be useful for bindings where it may make sense to split the C and Haskell code into separate packages. ] [Use the standard autogenModulesDir rather than a local copy Duncan Coutts **20080612092855] [Fix the register --gen-pkg-config flag Duncan Coutts **20080612092425 When specified without any file name it is supposed to use a default file name rather than be ignored completely. ] [Filter out the Paths_pkgname file in sdist Duncan Coutts **20080612091810 Fixes ticket #187 finally (I hope). ] [Switch the hugs code to safe file reading and writing Duncan Coutts **20080610180947] [Use writeFileAtomic everywhere instead of writeFile Duncan Coutts **20080610180727] [Switch to scoped file reading rather than lazy readFile Duncan Coutts **20080610180528] [Close the package.conf file after reading it Duncan Coutts **20080610180217 We had a bug on windows where we open and read ghc's package.conf database but because we did not consume the final newline we did not close the file. Then when we called ghc-pkg to register a package it failed because it could not rename the open file. ] [Add withFileContents and withUTF8FileContents Duncan Coutts **20080610180150 Safe block scoped reading of files. These guarantee that the file gets closed. ] [Fix pre-processing for haddock and executables Duncan Coutts **20080609233609 Now look in the right place to find the pre-processed source files belongign to executables. Fixes ticket #252. ] [Fail better when using haddock 2.x and the --hoogle flag Duncan Coutts **20080609190555 Fixes ticket #249 ] [Install haddock interface only when generated Duncan Coutts **20080609190251 This is actually Andrea Rossato's patch but it didn't merge cleanly due to more recent changes. Fixes ticket #250. ] [Install license file into the right place Duncan Coutts **20080609185840 even if the license file was kept in a subdir of the src tree. The canonical example was: license-file: debian/copyright It was being installed into $docdir/debian/ and failing since that dir did not exist. It's now installed into just $docdir. ] [Bump version due to api changes Duncan Coutts **20080529104714] [Put spaces round || and && when displaying version range expressions Duncan Coutts **20080529104214 This makes them much more readable. ] [Change the PackageIndex invariant so the buckets are ordered Duncan Coutts **20080529095346 Each bucket holds packages with the same name case-insensitively. Previously each buckets was internally unordered. Now they're ordered by the full package id which means first by package name case-sensitively and then by version. ] [Add thisPackageVersion and notThisPackageVersion Duncan Coutts **20080529092607 Util functions for makeing dependencies from package identifiers. thisPackageVersion (foo-1.0) = foo ==1.0 notThisPackageVersion (foo-1.0) = foo /=1.0 The latter is handy as a constraint in dependency resolution. ] [Add notThisVersion :: Version -> VersionRange Duncan Coutts **20080529092244 Opposite of ThisVersion, it means /= x.y but is actually implemented as > x.y || < x.y as we do not have not or not equal as primitives. ] [Note compatability issue in deprecation message for defaultUserHooks Duncan Coutts **20080527135830] [Write out Bool config values correctly Duncan Coutts **20080521153420 Used by cabal-install when writing the default ~/.cabal/config file. Previously it was using show for type Maybe Bool and writing out "Just True" when of course it should just be "True". ] [Rename doc/fptools.css to avoid the ghc build system cleaning it Duncan Coutts **20080520191700 The user guide gets built in two different ways. There's a target in Cabal's the top level Makefile and there is also the stuff that the ghc build system uses. The ghc build system expects to copy in doc/fptools.css and then delete it again on make clean. We want a persistent copy so that we can make the docs when we've just got a standalone Cabal build tree, so that's now kept as doc/Cabal.css. ] [Remove gnerated file (doc/fptools.css) Ian Lynagh *-20080511130035] [document data-dir field Bertram Felgenhauer **20080509131306] [add data-dir field to package config Bertram Felgenhauer **20080509130448 Cabal will look for data files to install relative to the directory given in the data-dir field, allowing package authors to better structure their source tree. There's no behavioural change by default. ] [Allow the bindir, libdir and libexec dir to be specified via env vars too Duncan Coutts **20080519173808 Same as for the datadir. Eg for package Foo, you'd use Foo_bindir=... Foo_datadir=... Foo_libexecdir=... ./Foo The next step would be generating a wrapper script that allows running the program inplace. It should also work for a library. ] [Remove unused import Duncan Coutts **20080513094301] [Do not display version tags Duncan Coutts **20080509094455] [Remove Distribution.Compat.Exception from other-modules Duncan Coutts **20080514171822] [Add PackageIndex.lookupPackageName and extra deletion functions Duncan Coutts **20080514162954] [Check invariant on every construction and elide on lookups Duncan Coutts **20080514154104] [Remove redundant Char test in parseBuildToolName Duncan Coutts **20080514153343 It was made redundant after the isSymbol test was removed. Spotted by Igloo. ] [Eliminate use of bracketOnError, use handle instead Duncan Coutts **20080514153206 It's actually more appropriate anyway. This means we don't need any Distribution.Compat.Exception. ] [Define bracketOnError in compat; fixes the build for GHC 6.4 Ian Lynagh *-20080514003919] [Add in {-# OPTIONS #-} for the benefit of ghc-6.4.x Duncan Coutts **20080514144728 Which do not grok OPTIONS_GHC or LANGUAGE pragmas ] [fix scope errors in non-GHC branch of an #ifdef Malcolm.Wallace@cs.york.ac.uk**20080514112530] [Prefix the datadir env var with the package name Duncan Coutts **20080514094203 Partly as it is more likely not to clash with other users and since in general different libs within a program may need different paths. ] [Made it possible to run executeables with data files in place. Johan Tibell **20080413134155 Added an environment variable, DATA_DIR, that is checked before the installation data directory is used. ] [Don't use Data.Char.isSymbol as it doesn't exist in base-1.0 Duncan Coutts **20080514083405 This is an alternative fix to creating a Distribution.Compat.Char ] [Modules that use cpp have to have cpp language prama to say so Duncan Coutts **20080514082913 Otherwise we cannot compile with just ghc --make which is actually essential for bootstrapping. ] [Make Distribution.Compat.Char for isSymbol; fixes the build with GHC 6.4 Ian Lynagh *-20080514004703] [Add new compat modules to Cabal file Ian Lynagh **20080514022119] [Make Distribution.Compat.Char for isSymbol; fixes the build with GHC 6.4 Ian Lynagh **20080514004703] [Hack around lack of Read for Map in GHC 6.4 Ian Lynagh **20080514004400 This is made worse by Show on Map being strange in GHC 6.4. The code could be better, but it works, and all the ugliness is in #if's that we can remove at some point down the line. ] [Define bracketOnError in compat; fixes the build for GHC 6.4 Ian Lynagh **20080514003919] [Print exit code and stderr for failing progs at debug level verbosity Duncan Coutts **20080513094055 Also adjust the verbosity level we get during configure at -v3 Should make it a bit easier to track down failing calls. ] [Remove a hardcoded "dist" Ian Lynagh **20080511181305] [Make the "dist" directory configurable Ian Lynagh **20080511155640] [Remove gnerated file (doc/fptools.css) Ian Lynagh **20080511130035] [Fix a bug in the unlitter Ian Lynagh **20080510233852 If we see a birdtrack while we are in latex mode, then we stay in latex mode - don't change into bird mode! ] [Display Cabal version in configure output with -v Duncan Coutts **20080509163507 eg "Using Cabal-1.5.1 compiled by ghc-6.8" Annoyingly ghc doesn't give us its full version number. ] [Add PackageIndex.reverseDependencyClosure Duncan Coutts **20080506234902 It's similar to dependencyClosure but looks at reverse dependencies. For example it's useful to find all packages that depend on broken packages and are thus themselves broken. ] [Improve style and performance of PackageIndex.dependencyClosure Duncan Coutts **20080506234447 Keep the completed set as another PackageIndex rather than a list. We want to return an index at the end anyway and in the mean time we want to do lots of lookups to see if we've visited previously. ] [Add PackageIndex.dependencyGraph that builds a Graph Duncan Coutts **20080506234326 Useful for some more tricky queries. ] [Remove a test for the specific kind of exception for nhc98 compatibility Duncan Coutts **20080506102804 This was the check for ghc-pkg failing. We cannot check for the exception being an ExitException since that assumes ghc's representation of the Exception type, whereas nhc98 defines: type Exception = IOError ] [Add PackageIndex.delete Duncan Coutts **20080506131603 We occasionally need to remove packages from an index eg to restrict the choices of a dependency resolver. ] [Cope better with ghc bug #2201, display a better error message Duncan Coutts **20080505085746 Otherwise it can (and does) really confuse people. The problem is that the command $ ghc-pkg-6.9 describe '*' --user returns a non-zero exit code if the user package db is empty. ghc-pkg intends this exit code to tell us if the query returned any results (one can use more complex queries as tests) but Cabal interprets it as failure. Indeed we cannot distinguish it from any other kind of failure from ghc-pkg. ] [Add PackageIndex.dependencyCycles Duncan Coutts **20080504131626 Finds any cycles (strongly connected components) in the dependencies of set of packages. This is useful for checking the correctness of installation plans. ] [Change dependencyInconsistencies to not take the pseudo top package Duncan Coutts **20080504130802 The one case where we need the pseudo top package we can use PackageIndex.insert instead to get the same effect and there are other cases in cabal-install where we do not want a pseudo top package. ] [Reverse the order of the args to PackageIndex.insert Duncan Coutts **20080504130317 To take the index last like the other functions and like Data.Map. It is actually more convenient that way round. ] [Revert the change about the --internal flag and a warning about haddock Duncan Coutts **20080501223131 Just a bit of confusion over the behaviour of the --executable flag. ] [Document --internal in Cabal.xml Joachim Breitner **20080501153356] [With --executable, --internal just adds --ignore-all-exports Joachim Breitner **20080501152544] [Implement --internal flag Joachim Breitner **20080501152421 Passing --internal to the haddock stage does these things: * Does not pass --hide parameter to haddock * Passes --ignore-all-exports parameter * Appends "(internal documentation)" to the title ] [Add an --internal flag to HaddockFlags Joachim Breitner **20080501145103] [Revert the other `fmap` to (.) Malcolm.Wallace@cs.york.ac.uk**20080501110006 To avoid needing a non-H'98 instance of Functor for (->). ] [Revert one change of (.) to fmap. It was not necessary and broke nhc98. Duncan Coutts **20080501104620 The other one was needed as we changed a type from Bool to Maybe Bool. ] [Add help command as per ticket #272 Duncan Coutts **20080430133740 "cabal help" behaves like "cabal --help" "cabal help cmd" behaves like "cabal cmd --help" Should still work with command line completion. ] [Change handling of bool command line args to allow an unset state Duncan Coutts **20080429201123 For bool valued flags we were always producing the command line string corresponding to a false flag value, even if the flag was not set. For example we'd always get "--disable-shared". It is important for cabal-install to be able to take an empty set of flags, override a few flags and turn the flags back into command line strings without getting a lot of extra defaults. Partly this is because we have to work with older versions of the Cabal library command line which does not recognise the new options. ] [Remove the feature for highlighting the default cases in --help output Duncan Coutts **20080429191206 Turns out it doesn't help us much because in many cases the initial/default flags are actually empty so we cannot identify the default values. ] [Make the old test code compile Duncan Coutts **20080428225729 Still a lot of bit rot, many of the full tests fail due to changed paths ] [Fix license parsing Duncan Coutts **20080428192255 Spotted by the testsuite which I'm trying to resurrect. ] [Fix fix for #224. Thomas Schilling **20080426164537 Changing from list of Dependencies to Maps resulted in the wrong Monoid instance being used. I'd still like to be able to run a test suite on this but that'd require a lot more work to do properly... ] [When multiple specifying list fields in the same section combine them Duncan Coutts **20080423201519 eg if you had: extensions: Foo extensions: Bar, Baz then previously we only ended up with [Bar, Baz]. Now we get them all. Only applies to list fields, for single fields the second value is taken and the first is silently discarded. This isn't good of course but the fix is harder since we're not in a context where we can report errors. Really we should just declare up front what kind of field it is and inherit the right behaviour automagically, either duplicates disallowed or allowed and combined with mappend. ] [Normalise file names in warning messages Duncan Coutts **20080423190457 We already do this for error messages. ] [Fix the check for -XFooBar ghc-options flags to be more permissive Duncan Coutts **20080423190243 Previously we rejected all such flags but that posed the problem that older versions of Cabal, like 1.1.6 did not understand new extensions so we could not actually follow the advice and use the extenion. So now we only warn about -X flags if they refer to old extensions that Cabal 1.1.6 knew about. If the .cabal file specifies cabal-version: >= 1.2 or similar (anything that excludes 1.1.6) then we warn about all -X flags. ] [Add checks for unknown OS Arch and Compiler names Duncan Coutts **20080423151410 They're ok locally but for distribution they need to be known. ] [Package check now take a GenericPackageDescription Duncan Coutts **20080423150354 Unfortunately in some cases we only have a already-configured PackageDescription to we have to expose a checkConfiguredPackage. We should refactor things so that we keep all the information even in a configured PackageDescription. ] [fix import for nhc98 Malcolm.Wallace@cs.york.ac.uk**20080422133009] [Make warning messages show the file name Duncan Coutts **20080422141909] [Update UTF8 code Duncan Coutts **20080422141539 Some code and test cases taken from the utf8-string package. Updated copyright notice appropriately (I think). ] [Don't nub extra-libs in unionBuildInfo Duncan Coutts **20080420192312 It's possible that we sometimes need to list the same library more than once if there are circular symbol references. ] [Fix unionBuildInfo Duncan Coutts **20080420180520 Fix ticket #264 to use nub only on the fields which are treated as sets. Probably we should be using the right types and mappend for each field. Change to construct a new value from scratch rather than overriding one of the two args. This helps to make sure we're updating all the field as we get a warning if we miss any. Turns out we were missing the ghc profiling and shared libs options which meant they were getting dropped. That had the effect of ghc-prof-options: in .cabal files being ignored. Thanks to 'midfield' from #haskell for spotting this. ] [Add newtype FlagName and FlagAssignment type alias Duncan Coutts **20080415204854 and use them in the appropriate places. ] [Add PackageIndex.insert and reverse merge/mappend Duncan Coutts **20080415203637 Packages in the second argument to merge now mask those in the first. ] [Make finalizePackageDescription use CompilerId type Duncan Coutts **20080413224111 Use the proper data type rather than a tuple (CompilerFlavor, Version) ] [Fix #224. We do not yet warn if the user specified a dependency that Thomas Schilling **20080413182659 did not occur in the package (it is just silently ignored.) ] [Add 'readP_to_E' function that takes the longest parse. Thomas Schilling **20080413182042] [Add simple test case for the dependency resolution case. This should Thomas Schilling **20080413132002 go into the test suite one day. ] [Fix/Add documentation. Thomas Schilling **20080413131839] [Change dependency resolution algorithm. Thomas Schilling **20080413131807 There were two reasons to do this. Firstly, this formulation makes it easier to add the --constraint command line flag that adds additional constraints on the packages that should be used. Secondly, with the orgininal algorithm it was possible to satisfy the constraint "foo < 1, foo > 2" if we had two versions of package "foo" which each satisfy one constraint. This patch fixes this by requiring the same package to satisfy both constraints (which of course is impossible in this case). ] [expose ghcOptions jeanphilippe.bernardy@gmail.com**20080417211221 This helps finding the options to pass to GHC API in various tools ] [expose tryGetConfigStateFile jeanphilippe.bernardy@gmail.com**20080417180248 This is needed by Yi to (try to) load an arbitrary project. ] [fix for #187 -- directory of Paths_packagename is included when looking for source files Andres Loeh **20080412204904] [Check for the required cabal version early in parsing Duncan Coutts **20080409154655 Previously we only checked the "cabal-version" field after parsing and all other configure processing. If the package really needs a later Cabal version it is of course highly likely that parsing or configure are going to fail and the user is not going to get the helpful error message about the version of Cabal required. So now we do the check early during parsing. If a later version is required and parsing subsequently fails, we now report the version issue, not the subsequent parse error. If parsing succeeds we still issue a warning which should be a useful hint to the user if subsequent configure processing fails. ] [Use relative file paths in .cabal parse error messages Duncan Coutts **20080409154030 Do this by normalising the file path in the error message and when looking for .cabal files, by looking in '.' rather than the absolute path of the current directory. ] [Remove unused import Duncan Coutts **20080409073352] [Fix for detecting ~/.cabal/ dir as a .cabal file Duncan Coutts **20080409073236 Which happened if you use cabal configure in your home dir. Now produced the right error message, or if you actually put a cabal project in your home dir, it might actually work. Also, do the same fix for findHookedPackageDesc. ] [Fix spelling in error message Duncan Coutts **20080408134610] [Fix names of profiling libs Duncan Coutts **20080407013449 I broke this recently when refactoring. Restore the original behaviour. Was generating "libHSfoo_p-1.0.a" when it should be "libHSfoo-1.0_p.a". ] [TAG 1.5.1 Duncan Coutts **20080329181329] Patch bundle hash: f9e7afe8e10496cf0d5a2e9421700180af2ac8a6