darcs patch: Split ConfVar into ConfFlag and ConfVar and one more

Esa Ilari Vuokko eivuokko at gmail.com
Wed Aug 15 20:39:00 EDT 2007


Hi,

I went hunting the few last warnings I see on Cabal build;
In Configuration.hs, resolveWithFlags, env has no case for
ConfVar's Impl.  I started adding signatures, and then
it occured to me, is there actually two types of ConfVar?

One that is one flag.
data ConfFlag = Flag String

And one that has the other cases as well
data ConfVar = OS String
             | Arch String
             | Impl String VersionRange
             | ConfFlag ConfFlag

That leads to changing some d -> Maybe Bool to d -> Either d2 Bool
and so on.  Does this sound sensible?  This is what the main part (Split
ConfVar) of the patch bundle does.

I tested by compiling Cabal's setup with changes, and compiling Cabal
afterwards.  I realize this isn't good enough test case;  But it appears
that the test in Configuration.hs aren't run;  Maybe I am missing
something with my fix-tests patch or running "make tests" doesn't work
(possibly only under msys shell)?

Best regards,
Esa


Thu Aug 16 03:20:09 FLE Daylight Time 2007  Esa Ilari Vuokko
<ei at vuokko.info>
  * Make 'make tests' runnable again

Thu Aug 16 03:31:05 FLE Daylight Time 2007  Esa Ilari Vuokko
<ei at vuokko.info>
  * Split ConfVar into ConfFlag and ConfVar

-------------- next part --------------

New patches:

[Make 'make tests' runnable again
Esa Ilari Vuokko <ei at vuokko.info>**20070816002009] {
hunk ./Distribution/Simple/Register.hs 52
-        hunitTests
+        hunitTests, installedPkgConfigFile
hunk ./tests/ModuleTest.hs 56
-import Distribution.Compiler (CompilerFlavor(..), Compiler(..))
+import Distribution.Compiler (CompilerFlavor(..), Compiler(..), compilerVersion)
}

[Split ConfVar into ConfFlag and ConfVar
Esa Ilari Vuokko <ei at vuokko.info>**20070816003105] {
hunk ./Distribution/Configuration.hs 82
+-- | A @ConfFlag@ represents an user-defined flag
+data ConfFlag = ConfFlag String
+    deriving Eq
+
hunk ./Distribution/Configuration.hs 89
-             | Flag String
+             | Flag ConfFlag
hunk ./Distribution/Configuration.hs 96
-    show (Flag f) = "flag(" ++ f ++ ")"
+    show (Flag (ConfFlag f)) = "flag(" ++ f ++ ")"
hunk ./Distribution/Configuration.hs 120
-                  -> (c -> Maybe Bool)   -- ^ (partial) variable assignment
-                  -> (Condition c, [c])
+                  -> (c -> Either d Bool)   -- ^ (partial) variable assignment
+                  -> (Condition d, [d])
hunk ./Distribution/Configuration.hs 125
-      Var v   -> maybe (Var v) Lit (i v)
+      Var v   -> either Var Lit (i v)
hunk ./Distribution/Configuration.hs 155
-                         (Condition ConfVar, [String])
+                         (Condition ConfFlag, [String])
hunk ./Distribution/Configuration.hs 159
-    interp (OS name)   = Just $ name == os
-    interp (Arch name) = Just $ name == arch
-    interp (Impl i vr) = Just $ impl == i && implVer `withinRange` vr
-    interp _           = Nothing
-    flags = [ fname | Flag fname <- fvs ]
+    interp (OS name)   = Right $ name == os
+    interp (Arch name) = Right $ name == arch
+    interp (Impl i vr) = Right $ impl == i && implVer `withinRange` vr
+    interp (Flag  f)   = Left f
+    flags = [ fname | ConfFlag fname <- fvs ]
hunk ./Distribution/Configuration.hs 194
-    flagCond = string "flag" >> sp >> inparens flagIdent >>= return . Var . Flag 
+    flagCond = string "flag" >> sp >> inparens flagIdent >>= return . Var . Flag . ConfFlag
hunk ./Distribution/Configuration.hs 331
-    env _ (OS o)     = Just $ o == os
-    env _ (Arch a)   = Just $ a == arch
-    env flags (Flag n) = lookup n flags
+    env flags flag@(ConfFlag n) = maybe (Left flag) Right . lookup n $ flags 
hunk ./Distribution/Configuration.hs 354
-                    (v -> Maybe Bool) 
+                    (v -> Either v Bool) 
hunk ./Distribution/Configuration.hs 392
-              [ (CNot (Var (Flag "a")), 
+              [ (CNot (Var (Flag (ConfFlag "a"))), 
hunk ./Distribution/Configuration.hs 395
-              , (CAnd (Var (Flag "b")) (Var (Flag "c")),
+              , (CAnd (Var (Flag (ConfFlag "b"))) (Var (Flag (ConfFlag "c"))),
hunk ./Distribution/Configuration.hs 407
-                  (CAnd (Var (Flag "debug")) (Var (OS darwin)))
+                  (CAnd (Var (Flag (ConfFlag "debug"))) (Var (OS darwin)))
hunk ./Distribution/Configuration.hs 435
-test_simpCondTree = simplifyCondTree (flip lookup flags) tstTree
+test_simpCondTree = simplifyCondTree env tstTree
hunk ./Distribution/Configuration.hs 437
-    flags = [(Flag "a",False), (Flag "b",False), (Flag "c", True)] 
+    env x = maybe (Left x) Right (lookup x flags)
+    flags = [(mkFlag "a",False), (mkFlag "b",False), (mkFlag "c", True)] 
+    mkFlag = Flag . ConfFlag
}

Context:

[Fix Paths_pkg.hs generation
Esa Ilari Vuokko <ei at vuokko.info>**20070814204557] 
[Warning police: Add type signatures and rename arg
Esa Ilari Vuokko <ei at vuokko.info>**20070814160830] 
[Warning police: Remove unused statement and import
Esa Ilari Vuokko <ei at vuokko.info>**20070814143057] 
[Warning police: provide fallback pattern match
Esa Ilari Vuokko <ei at vuokko.info>**20070814143008] 
[Reorder, make explicit and beautify imports
Esa Ilari Vuokko <ei at vuokko.info>**20070814142000] 
[Refactor the code for managing installation directories
Duncan Coutts <duncan at haskell.org>**20070814092320
 New types for the collection of installation directory templates and a
 separate type for the collection of actual real install FilePaths.
 The templates are represented with a PathTemplate adt.
 Dir templates can now be relative to each other, eg $htmldir to $docdir
 Default install dir templates are now specified compactly in one place.
 Adding new dirs should be considerably simpler than previously.
 This patch should not actualy change where anything is installed.
] 
[ghc only supports the -x flag in 6.6 and above
Duncan Coutts <duncan at haskell.org>**20070814090557] 
[update ghc-pkg field parse error message
Duncan Coutts <duncan at haskell.org>**20070812170800] 
[Clean up import ordering and format
Esa Ilari Vuokko <ei at vuokko.info>**20070811113227] 
[Explicit imports
Esa Ilari Vuokko <ei at vuokko.info>**20070811111518] 
[Use existing parsers to handle ghc-pkg field output
Esa Ilari Vuokko <ei at vuokko.info>**20070809041153] 
[Never generate empty language extension flags
Duncan Coutts <duncan at haskell.org>**20070808235240
 Needed because some compilers support some language extensions by default
 so need no flag to turn those extensions on.
] 
[Cabal now depends on teh containers package
Ian Lynagh <igloo at earth.li>**20070801235622] 
[fix build with GHC 6.2.x
Simon Marlow <simonmar at microsoft.com>**20070809102844] 
[Parse the output of ghc --supported-languages correctly
Magnus Jonsson <magnus at smartelectronix.com>**20070808204523] 
[Oops, fix deprecated Distribution.Extension module
Duncan Coutts <duncan at haskell.org>**20070807172125
 it no longer exports the internal per-compiler extension to flags functions
 as they are no longer exist and the equivalents are internal.
] 
[remove unused local vars
Duncan Coutts <duncan at haskell.org>**20070807171235] 
[Add compilerExtensions field to Compiler and make each compiler fill it in
Duncan Coutts <duncan at haskell.org>**20070807170653
 It's just a list of supported extensions and the corresponding compiler flags.
 For most compilers this is currently just a static list. For ghc 6.7 and above
 we query ghc to find the list of language extensions it supports.
 In each case the code has moved out into the compiler-specific modules and the
 core code treats it generically.
 The extensionsToFlags function has been split into two:
 extensionsToFlags which now returns the flags for the supported extensions and
 unsupportedExtensions which does what it says it does. This is because the two
 roles of the previous function were always used separately, never together.
] 
[Use String rather than importing a module just to misuse a String type alias
Duncan Coutts <duncan at haskell.org>**20070807170526] 
[Add a little documentation.
Thomas Schilling <nominolo at gmail.com>**20070807162023] 
[Fix error message.
Thomas Schilling <nominolo at gmail.com>**20070807162001] 
[Fix translation of deprecated fields.  Add test case.
Thomas Schilling <nominolo at gmail.com>**20070807161837] 
[Warn if no Cabal-version field is specified, but new syntax is used.
Thomas Schilling <nominolo at gmail.com>**20070806235131
 This isn't quite exact.  Ideally, we'd like to have something like
 isEmptyRange (specified-range && >= 1.2) but implementing isEmptyRange
 is non-trivial, so we'll go with this imperfect solution until we need
 that feature elsewhere.
] 
[Re-enable and update unit tests.
Thomas Schilling <nominolo at gmail.com>**20070807000155] 
[Cosmetic cleanup (fix line length)
Thomas Schilling <nominolo at gmail.com>**20070806235644] 
[No longer fail to parse packages without any library or executable
Thomas Schilling <nominolo at gmail.com>**20070806235404
 sections.  Issue a warning instead.  (The previous error message
 "Unexpected end of file" was not very helpful.)
] 
[Allow querying for the wildcard version range.
Thomas Schilling <nominolo at gmail.com>**20070806234707] 
[Split up make target for documentation generation.  Allows to build
Thomas Schilling <nominolo at gmail.com>**20070803200533
 the user's guide separately from the Haddock documentation. 
] 
[Remove more os-specific cppery
Duncan Coutts <duncan at haskell.org>**20070807115707
 The only difference for this one was / vs \\ path separators
] 
[Remove use of cpp in Distribution.System
Duncan Coutts <duncan at haskell.org>**20070807111837
 base it off of the System.Info.os string rather than cpp defs
] 
[Make things build with ghc-6.6.x rather than just ghc HEAD
Duncan Coutts <duncan at haskell.org>**20070807111724
 filepath-1.0 does not export dropDrive
] 
[Ask the compiler what languages it supports, when possible
Ian Lynagh <igloo at earth.li>**20070805171323] 
[Pattern match on an OS datatype rather than using ifdef everywhere
Ian Lynagh <igloo at earth.li>**20070805130347] 
[Add StandaloneDeriving extension
Ian Lynagh <igloo at earth.li>**20070804192416] 
[extensionToGHCFlag is now version dependent, and uses -XFoo flags for >=6.7
Ian Lynagh <igloo at earth.li>**20070804191833] 
[Add TypeFamilies extension
Ian Lynagh <igloo at earth.li>**20070804184959] 
[Don't complain about AllRightsReserved licenses
Duncan Coutts <duncan at haskell.org>**20070804125110
 That can be done in hackage when people try to upload. Fixes bug #127.
] 
[Add setup register --gen-pkg-config flag for distros that want that.
Duncan Coutts <duncan at haskell.org>**20070804115512
 It generates the actual file to be passed to the compiler's package program.
 This is obviously compiler-specific.
] 
[Correct the location of the haddock dir in inplace registrations
Duncan Coutts <duncan at haskell.org>**20070804115428] 
[normalise the input and output file names when pre-processing
Duncan Coutts <duncan at haskell.org>**20070804013029
 eg so we don't call cpp with ././src/blah -o ./dist/blah
 since those ././ can end up in error messages.
] 
[Put the generated haddock-prolog file under dist
Duncan Coutts <duncan at haskell.org>**20070804004848] 
[Try and simplify cleaning by always removing dist
Duncan Coutts <duncan at haskell.org>**20070804004643
 so we don't have to individually track all the files we create
 we still have to delete a few files outside of the build dir sadly
 the configuration is still preserved if you specify --save-configure
] 
[Remove compilerBinaryName, use compilerId instead
Duncan Coutts <duncan at haskell.org>**20070804004524] 
[Move compiler-specific code for configurion into compiler modules
Duncan Coutts <duncan at haskell.org>**20070803213321
 There's slightly more code overally but it's no longer incomprehensible
 because it's not all mixed together for all the different compilers.
] 
[Clean up rather un-sbstract use of Compiler in configure
Duncan Coutts <duncan at haskell.org>**20070803205901] 
[-Wall police
Duncan Coutts <duncan at haskell.org>**20070802194000] 
[Change Compiler's compilerVersion fild to compilerId
Duncan Coutts <duncan at haskell.org>**20070802193400
 Of type PackageIdentifier rather than Version.
] 
[Remove Distribution.Simple.Configure.findProgram as it's no longer used
Duncan Coutts <duncan at haskell.org>**20070802194230] 
[Put the haddock and hscolour version numbers in the global ProgramConfiguration
Duncan Coutts <duncan at haskell.org>**20070802185614
 We do this during the configure step and then later we don't have to run
 haddock & hscolour again to find out their version numbers.
 This also eliminates some annoying module interdependencies.
 Eventually the Program abstraction ought to include the ability for programs
 to discover their own version numbers so it can be done more modularly.
] 
[Alter version parse error message to make it clearer
Duncan Coutts <duncan at haskell.org>**20070802181620] 
[Add version field to Program and add findProgram(AndVersion) utilities
Duncan Coutts <duncan at haskell.org>**20070802172941
 findProgram and findProgramAndVersion construct Program values
 The latter makes it easier to parse output of --version calls.
 The idea is that we should carry the version number along with the program
 if we know it, so we can later decide version-dependent args without having
 to do more IO to find the program version, eg see use_optP_P & haddockVersion.
] 
[Tidy some imports/exports
Duncan Coutts <duncan at haskell.org>**20070802003250] 
[Remove redundant configure flags, missed bits of previous refactoring.
Duncan Coutts <duncan at haskell.org>**20070802003154] 
[Make the Compiler abstraction use the Program abstraction
Duncan Coutts <duncan at haskell.org>**20070801205428
 So out with compilerPath :: FilePath, in with compilerProg :: Program
 Similarly for compilerPkgTool.
 Lots of knock-on changes due to this, including converting many more uses of
 rawSystemExit to rawSystemProgram.
] 
[Simplify rawSystemProgram using programPath
Duncan Coutts <duncan at haskell.org>**20070801200247] 
[Add programPath :: Program -> FilePath
Duncan Coutts <duncan at haskell.org>**20070801200139
 At the moment it's a partial function, but we should change that by having
 a distinction between an abstract program and a configured program.
] 
[Clean up cpphs/ghc -cpp preprocessor code
Duncan Coutts <duncan at haskell.org>**20070801135256
 Now better separated and uses Program better.
 Also no longer needs internal lookupProgram' utils function.
] 
[Clean up calling of ar, make it use Program abstraction
Duncan Coutts <duncan at haskell.org>**20070801021526] 
[Make all the pre-processors use the Program abstraction
Duncan Coutts <duncan at haskell.org>**20070801021049] 
[Improve hangling of the title and prolog for haddock docs
Duncan Coutts <duncan at haskell.org>**20070804021538
 Only include ": " in the title if it has a synopsis to use as subtitle
 Use the description as the prolog, or if that's empty we use the synopsis.
 Do the same for executables, fixing bug #142.
] 
[Less confusing haddock command output when there are no libs in the package
Duncan Coutts <duncan at haskell.org>**20070804013133
 It says:
 > No documentation was generated as this package does not contain a library.
 > Perhaps you want to use the haddock command with the --executables flag.
] 
[Add message saying where haddock docs got put
Duncan Coutts <duncan at haskell.org>**20070804010016
 And make the similar message for sdist respect the verbosity
] 
[Make the writing registration script message less silly
Duncan Coutts <duncan at haskell.org>**20070804002353] 
[Fix haddock markup for finalizePackageDescription
Duncan Coutts <duncan at haskell.org>**20070804001745] 
[Change error message for tabs used as indentation to something more
Thomas Schilling <nominolo at gmail.com>**20070803213331
 helpful.
] 
[Fix import path to HUnit.
Thomas Schilling <nominolo at gmail.com>**20070803200829] 
[Fix printing of 'impl' checks.
Thomas Schilling <nominolo at gmail.com>**20070803200622] 
[Disallow tabs .cabal files with new syntax
Thomas Schilling <nominolo at gmail.com>**20070803181244] 
[Fix tab in Cabal.cabal.
Thomas Schilling <nominolo at gmail.com>**20070803175701] 
[Add impl(...) conditional to configurations.
Thomas Schilling <nominolo at gmail.com>**20070802010527
 You can now use expressions like impl( ghc >= 6.6.1 ) in conditionals
 in .cabal files.
] 
[Add documentation for Cabal Configurations.
Thomas Schilling <nominolo at gmail.com>**20070803125632] 
[Move the SetupWrapper module under Distribution.Simple
Duncan Coutts <duncan at haskell.org>**20070803012304
 It's really a wrapper around the simple build system.
] 
[Cleanup. fix line length
Thomas Schilling <nominolo at gmail.com>**20070801221329] 
[Fix name of flag in error message
Duncan Coutts <duncan at haskell.org>**20070802172141] 
[Add readVersion convenience function to Distribution.Version
Duncan Coutts <duncan at haskell.org>**20070802171703
 So it's merely readVersion :: String -> Maybe Version
 Having to use readP_to_S parseVersion all over the place is annoying.
] 
[extraArgs should override args in command lines
Duncan Coutts <duncan at haskell.org>**20070801023042
 besides, the order was inconsistent within the same function between the
 UserSpecified and FoundOnSystem cases.
] 
[FIX compilation with GHC 6.2.x
Simon Marlow <simonmar at microsoft.com>**20070801095523] 
[Move the haddock code out into it's own module
Duncan Coutts <duncan at haskell.org>**20070731183410
 It removes about 250 loc from Distribution.Simple
] 
[-Wall police
Duncan Coutts <duncan at haskell.org>**20070731173626] 
[Fix order of warnings.
Thomas Schilling <nominolo at gmail.com>**20070730225311] 
[Add line numbers to unknown fields error message.
Thomas Schilling <nominolo at gmail.com>**20070730225256] 
[Display a more helpful error message, when unknown fields are
Thomas Schilling <nominolo at gmail.com>**20070730224026
 noticed. 
] 
[Fix self-compile warnings.
Thomas Schilling <nominolo at gmail.com>**20070730220537] 
[Fix haddock markup
Ian Lynagh <igloo at earth.li>**20070729233545
 I haven't checked that it looks right, but it is now accepted by haddock.
] 
[Pass ghc -package flags when using it as a C compiler in GHCMakefile
Ian Lynagh <igloo at earth.li>**20070729152803
 This means we get the CPP include directories included.
] 
[Add a missing case in updateCfg
Ian Lynagh <igloo at earth.li>**20070729105910] 
[Resolve conflicts
Ian Lynagh <igloo at earth.li>**20070729105854] 
[Fix conflicts.  Fix for changed argument to 'preprocessSources'.
Thomas Schilling <nominolo at gmail.com>**20070728223322] 
[Rename field.
Thomas Schilling <nominolo at gmail.com>**20070728223102] 
[Change HUnit module path to Test.HUnit (the default now).
Thomas Schilling <nominolo at gmail.com>**20070728221453] 
[Add note to 'clean' that it could be simpler, but for compatibility
Thomas Schilling <nominolo at gmail.com>**20070728221342
 reasons isn't (for now). 
] 
[Let sdist command run the preprocessors itself.  This way we don't
Thomas Schilling <nominolo at gmail.com>**20070728221237
 have to put stuff into the source tree.
] 
[Store resolved package description in local build info.  
Thomas Schilling <nominolo at gmail.com>**20070728221102
 
 The clean and sdist commands need to use a flattened representation of
 the original description.  Note the notes for
 flattenPackageDescription for some problems with this approach.
] 
[Export 'flattenPackageDescription'.
Thomas Schilling <nominolo at gmail.com>**20070728215155] 
[Minor documentation fix.
Thomas Schilling <nominolo at gmail.com>**20070728214859] 
[Modify test case.
Thomas Schilling <nominolo at gmail.com>**20070728214825] 
[Add function 'flattenPackageDescription'.
Thomas Schilling <nominolo at gmail.com>**20070728214746] 
[Avoid reporting the same missing dependecy twice.
Thomas Schilling <nominolo at gmail.com>**20070728214645] 
[Add documentation
Thomas Schilling <nominolo at gmail.com>**20070728214541] 
[Add documentation
Thomas Schilling <nominolo at gmail.com>**20070728214444] 
[Add/Fix test cases
Thomas Schilling <nominolo at gmail.com>**20070728214410] 
[Minor. Moved some code.
Thomas Schilling <nominolo at gmail.com>**20070719222541] 
[Add function 'ignoreCondition'.
Thomas Schilling <nominolo at gmail.com>**20070719222444] 
[Re-enable and extend test case.
Thomas Schilling <nominolo at gmail.com>**20070719222341] 
[Filter duplicate dependencies.
Thomas Schilling <nominolo at gmail.com>**20070719222233] 
[Adopt new CondTree data structure.
Thomas Schilling <nominolo at gmail.com>**20070719125305
 
 'finalizePackageDescription' now also takes dependencies of
 executables into account.
] 
[Change CondTree data structure to something more flexible.
Thomas Schilling <nominolo at gmail.com>**20070719124655
 
 This also requires some interface changes.
] 
[Add simpler representation of a .cabal file with conditions.
Thomas Schilling <nominolo at gmail.com>**20070717203942] 
[Preprocessor output never gets written back to the source dir.
Thomas Schilling <nominolo at gmail.com>**20070717174026
 
 'preprocessSources' now gets an additional flag to determine whether
 to process all sources (for building) or only platform independent
 ones (for sdist).
] 
[Add resolved package description to 'LocalBuildInfo'.
Thomas Schilling <nominolo at gmail.com>**20070716204325] 
[Fix removed import by importing a required accessor only.
Thomas Schilling <nominolo at gmail.com>**20070716204238] 
[Add tags target to generate a tags file using 'hasktags'.  (Unix only)
Thomas Schilling <nominolo at gmail.com>**20070716203015] 
[Rename 'PreparedPackageDescription' to 'GenericPackageDescription'
Thomas Schilling <nominolo at gmail.com>**20070716200427] 
[Remove unused dependency.
Thomas Schilling <nominolo at gmail.com>**20070716200215] 
[Move configured_cabal to 'dist' directory.
Thomas Schilling <nominolo at gmail.com>**20070716154146] 
[Bugfix by Ian Lynagh:  Cabal can't have a Cabal-Version header; it breaks bootstrapping
Thomas Schilling <nominolo at gmail.com>**20070716151535] 
[Partial bugfix to allow traditional .cabal files without a library but
Thomas Schilling <nominolo at gmail.com>**20070628112301
 global build dependencies.  The correct solution is to add global
 dependencies to each executable and implement dependency resolution
 for executables.
 
 The current workaround is to add the dependencies to the library, but
 disable building of the library.
] 
[Take advantage of configurations to build Cabal itself and fix bootstrapping problem.
Thomas Schilling <nominolo at gmail.com>**20070628081438] 
[Re-add configurations module to .cabal file.  (Got removed on update.)
Thomas Schilling <nominolo at gmail.com>**20070623204706] 
[Properly fix tests.
Thomas Schilling <nominolo at gmail.com>**20070623203939] 
[Disable (comment out) tests for now.  Break due to changed interface.
Thomas Schilling <nominolo at gmail.com>**20070623203121] 
[Fix typo.
Thomas Schilling <nominolo at gmail.com>**20070623202333] 
[Add proper handling of configurations to configure command.
Thomas Schilling <nominolo at gmail.com>**20070623202017] 
[Fix warnings.
Thomas Schilling <nominolo at gmail.com>**20070623201723] 
[Adjust to new package reading interface.
Thomas Schilling <nominolo at gmail.com>**20070623201546] 
[Downcase flagnames.  Re-add config flags (were removed due to update).
Thomas Schilling <nominolo at gmail.com>**20070623201455] 
[Fix warnings.
Thomas Schilling <nominolo at gmail.com>**20070623201254] 
[Fix warnings, add documentation and changes in response to some
Thomas Schilling <nominolo at gmail.com>**20070623201135
 interface changes.
] 
[Make explicit that reading package descriptions isn't supported here, ATM.
Thomas Schilling <nominolo at gmail.com>**20070623200701] 
[Fixed warning
Thomas Schilling <nominolo at gmail.com>**20070623200522] 
[Fixed warnings, added documentation, and changed os and arch names to
Thomas Schilling <nominolo at gmail.com>**20070623200453
 simple strings.
] 
[Add helpers for reading and writing the file to hold a configured cabal-file.
Thomas Schilling <nominolo at gmail.com>**20070618195710] 
[Add commandline support for specifying defaults for flags.
Thomas Schilling <nominolo at gmail.com>**20070618195449] 
[Compatibility parsing and working configurations.
Thomas Schilling <nominolo at gmail.com>**20070618195329] 
[Pretty printing of conditions and CondTrees.  Non-dependency
Thomas Schilling <nominolo at gmail.com>**20070614125031
 information of CondTrees is now a modifier.  Move CondTree resolution functionality. 
] 
[Prototypical configurations
Thomas Schilling <nominolo at gmail.com>**20070613184332] 
[add line numbers to all field times
Thomas Schilling <nominolo at gmail.com>**20070613173548] 
[add flag as a section
Thomas Schilling <nominolo at gmail.com>**20070613172416] 
[added docs
Thomas Schilling <nominolo at gmail.com>**20070613172309] 
[fixed typo
Thomas Schilling <nominolo at gmail.com>**20070613172230] 
[Abstracted variables out of conditions.  Generalized simplification
Thomas Schilling <nominolo at gmail.com>**20070613172114
 function to accept an arbitrary partial assignment of these
 variables.
] 
[Added Configuration parsing and simplification.
Thomas Schilling <nominolo at gmail.com>**20070529210344] 
[Extended low-level parsing routines to also allow labelled blocks and if-blocks.
Thomas Schilling <nominolo at gmail.com>**20070529205958] 
[Added documentation.
Thomas Schilling <nominolo at gmail.com>**20070528211221] 
[Use the right output directory when building C sources for executables
Duncan Coutts <duncan at haskell.org>**20070726213309] 
[Use our own GetOpt if __GLASGOW_HASKELL__ >= 606 only
Ian Lynagh <igloo at earth.li>**20070724213112
 Used to be if __GLASGOW_HASKELL__ >= 604, but the 6.4 branch had a bug
 which looks likely to be the cause of GHC build failures we're seeing:
 -         procNextOpt (NonOpt x)   RequireOrder      = ([],x:rest,us,[])
 +         procNextOpt (NonOpt x)   RequireOrder      = ([],x:rest,[],[])
] 
[-Wall police
Duncan Coutts <duncan at haskell.org>**20070724172023] 
[Update user guide about haddock --css --hyperlink-source --hscolour-css
Duncan Coutts <duncan at haskell.org>**20070724160742
 The haddock --css flag is new. The old --hscolour=[path] flag got split
 into two flags: --hyperlink-source and --hscolour-css=path
] 
[Remove a couple bits of unused code and imports
Duncan Coutts <duncan at haskell.org>**20070724110732] 
[use nhc-Options rather than deprecated nhc98-Options
Duncan Coutts <duncan at haskell.org>**20070724110703] 
[Hugs build: track change to install-includes
Ross Paterson <ross at soi.city.ac.uk>**20070724101816] 
[Rename --hscolour to --hyperlink-source and add haddock --css flag
Duncan Coutts <duncan at haskell.org>**20070723190026
 So now --hyperlink-source controles wether or not we run hscolour and
 get haddock to link to the sources. The new flag --hscolour-css can
 be used to override the css file that hscolour uses.
 Also, the new flag --css can override the css file that haddock uses.
] 
[Merges from hscolour patch and make it work with haddock-0.8
Duncan Coutts <duncan at haskell.org>**20070723180602
 Some minor changes due to changes since the hscolour patch was written.
 Make it work with haddock-0.8 by using %{MODULE} rather than %{FILE}
 and generate output file names to match (ie not using the original file
 extension, just using the module name for the output file).
] 
[HsColour support
Roberto Zunino <zunrob at users.sf.net>**20070530194747
 Integration of Cabal, HsColour, and Haddock.
 (Also fixes bug #102)
] 
[Remove ContextStack extension
Ian Lynagh <igloo at earth.li>**20070709132341
 Seems to be based on GHC's -fcontext-stack flag, which takes an integer
 argument.
] 
[Remove InlinePhase extension
Ian Lynagh <igloo at earth.li>**20070708172919
 As far as I can tell
 (a) The -finline-phase flag stopped actually being accepted by GHC
     sometime between GHC 4.08.2 and GHC 5.04.3
 (b) It took an Int argument
] 
[Add KindSignatures extension
Ian Lynagh <igloo at earth.li>**20070708120616] 
[Add the MagicHash extension
Ian Lynagh <igloo at earth.li>**20070708111043] 
[TAG 2007-06-29
Ian Lynagh <igloo at earth.li>**20070629112545] 
[get the stub object files right
Simon Marlow <simonmar at microsoft.com>**20070626145413] 
[remove $(LIB) before calling ar
Simon Marlow <simonmar at microsoft.com>**20070626140543] 
[makefile: fix up the way we find _stub.o objects
Simon Marlow <simonmar at microsoft.com>**20070622152042] 
[makefile: replace backslashes with forward slashes for Windows
simonpj at microsoft.com**20070621133101] 
[update output
Ross Paterson <ross at soi.city.ac.uk>**20070620152404] 
[break up the long string literal
Ross Paterson <ross at soi.city.ac.uk>**20070620152103
 
 This makes the output work with implementations (like Hugs) that impose
 a limit on the size of string literals.
] 
[update
Simon Marlow <simonmar at microsoft.com>**20070620091950] 
[include Makefile.local if it exists; allows local customization
Simon Marlow <simonmar at microsoft.com>**20070620091946] 
[clean up .hi-boot and .o-boot
Simon Marlow <simonmar at microsoft.com>**20070620091843] 
[add a "DO NOT EDIT" notice to the top of Cabal-generated Makefiles
Simon Marlow <simonmar at microsoft.com>**20070620091759] 
[Fix warning
Ian Lynagh <igloo at earth.li>**20070615183346] 
[report non-option arguments as errors (fixes #90 and #113)
Ross Paterson <ross at soi.city.ac.uk>**20070607082326
 
 Formerly, non-option arguments to all commands were silently ignored.
 Now setup halts with an error message in this case.
] 
[Fix error message regression
Simon Marlow <simonmar at microsoft.com>**20070606142650
 
 Passing a non-existent program for --with-hc-pkg used to say this:
 
 $ ./Setup configure --with-hc-pkg=foo
 Configuring QuickCheck-2.0...
 /bin/sh: foo: command not found
 Setup: executing external program failed: "foo" --global list >tmp23634
 
 Now it is rather less useful:
 
 $ ./setup configure --with-hc-pkg=foo
 configure: Reading installed packages...
 zsh: 23596 exit 127   ./setup configure --with-hc-pkg=foo
 
 This patch restores the old behaviour, slightly improved:
 
 $ ./Setup --with-hc-pkg=foo configure
 configure: Reading installed packages...
 Setup: executing external program failed (exit 127) : foo --global list
] 
[don't pass unrecognized arguments to ./configure
Ross Paterson <ross at soi.city.ac.uk>**20070605231500
 
 They are now reported as errors.  To pass them to configure, use the
 new --configure-option flag.
 
 Non-option arguments are still ignored (#90 and #113), as with all of
 the other commands.
] 
[Add and use createDirectoryIfMissingVerbose
Ian Lynagh <igloo at earth.li>**20070602002507
 rather than createDirectoryIfMissing
] 
[Overwrite .installed-pkg-config if it exists when registering
Ian Lynagh <igloo at earth.li>**20070530150838] 
[add --cpphs-options
Ross Paterson <ross at soi.city.ac.uk>*-20070115141053] 
[add --cpphs-options
Ross Paterson <ross at soi.city.ac.uk>**20070115141053] 
[implement --configure-option and --ghc-option (#139)
Ross Paterson <ross at soi.city.ac.uk>**20070604114851
 
 Added options used for building in the GHC tree:
 
 	setup configure --configure-option=STR
 	setup build --ghc-option=STR
 	setup makefile --ghc-option=STR
 
 These were formerly scattered across Setup.hs files.
] 
[warning police on SetupWrapper
Ross Paterson <ross at soi.city.ac.uk>**20070603104827] 
[trim imports
Ross Paterson <ross at soi.city.ac.uk>**20070603104802] 
[include preprocessed modules in setup haddock (fixes #138)
Ross Paterson <ross at soi.city.ac.uk>**20070602195508] 
[move dotfiles into dist
Ross Paterson <ross at soi.city.ac.uk>**20070602175348
 
 .setup-config -> dist/setup-config
 .installed-pkg-config -> dist/installed-pkg-config
 .inplace-pkg-config -> dist/inplace-pkg-config
] 
[mark mkGHCMakefile.sh and GHCMakefile.in as source files
Ross Paterson <ross at soi.city.ac.uk>**20070601155538
 so that they'll be included in source distributions of this package.
] 
[cope with ghc-pkg returning multiple values for a field
Ross Paterson <ross at soi.city.ac.uk>**20070601155450] 
[Close the handle of temporary files before removing them
Ian Lynagh <igloo at earth.li>**20070529192852
 The removal fails on Windows if we don't, giving unhelpful errors like
 Setup.exe: .\tmp3660: removeFile: permission denied (Permission denied)
] 
[add nhc98-options: field to .cabal file
Malcolm.Wallace at cs.york.ac.uk**20070528122833] 
[Fix warnings in Paths_* autogenerated module
Ian Lynagh <igloo at earth.li>**20070527220538] 
[Fix quoting when doing gen-script of ' in descriptions
Ian Lynagh <igloo at earth.li>**20070526154747
 It used to turn into '', which just disappears.
 Now it turns into '\''.
] 
[Add Distribution.Simple.GHCMakefile to Exposed-Modules
Ian Lynagh <igloo at earth.li>**20070526153905] 
[old nhc98 Makefiles now obsolete
Malcolm.Wallace at cs.york.ac.uk**20070525133004] 
[Remove package.conf.in and GHC bits of Makefile (used in the old build system)
Ian Lynagh <igloo at earth.li>**20070524142725] 
[avoid overflowing the argument limit when building a split-objs lib
Simon Marlow <simonmar at microsoft.com>**20070524134817] 
[Improvements for 'setup makefile'
Simon Marlow <simonmar at microsoft.com>**20070524132736
  
  - now the makefile can build the library too; so 'setup build' isn't
    required (unless there are post-build steps).  This will be
    necessary for bootstrapping GHC from .hc files, where we'll be
    using Makefiles generated by 'setup makefile' to build the
    libraries.
 
  - the Makefile tempate is in a text file, processed into a .hs file
    by a small script (mkGHCMakefile.sh).  This is run by hand for now,
    and I've included the generated module, so there shouldn't be any
    problems with building Cabal.
 
  - some cleanup and refactoring in Distribution.Simple.GHC
] 
[fix cut&pasto
Simon Marlow <simonmar at microsoft.com>**20070520185605] 
[generalise type of xargs
Simon Marlow <simonmar at microsoft.com>**20070520185556] 
[We now depend on process
Ian Lynagh <igloo at earth.li>**20070523181444] 
[We now depend on pretty, directory and old-time
Ian Lynagh <igloo at earth.li>**20070522133304] 
[Pass rawSystemStdout verbosity, not verbose
Ian Lynagh <igloo at earth.li>**20070523212145] 
[fix compilation with GHC 6.2.x
Simon Marlow <simonmar at microsoft.com>**20070523083703] 
[now needs -package filepath
Malcolm.Wallace at cs.york.ac.uk**20070522085446] 
[Dumping Distribution.Compat.FilePath in favor of System.FilePath
Pepe Iborra <mnislaih at gmail.com>**20070521125919
 
 sorry folks, Compat.FilePath is gone
] 
[Get right the verbosity correspondence for GHC
Pepe Iborra <mnislaih at gmail.com>**20070521124306
   
   GHC has more verbosity levels than Distribution.Verbosity,
   this patch gives a more accurate correspondence
] 
[portability fix
Ross Paterson <ross at soi.city.ac.uk>**20070521113908] 
[custom show'ers for Verbosity
Pepe Iborra <mnislaih at gmail.com>**20070520233520] 
[Export simpleUserHooks
Ian Lynagh <igloo at earth.li>**20070518152026] 
[FIX BUILD with GHC 6.2.x
Simon Marlow <simonmar at microsoft.com>**20070516103919] 
[Small tidyup
Ian Lynagh <igloo at earth.li>**20070515151409] 
[cope with pre-requisite packages with empty haddock fields (like rts)
Ross Paterson <ross at soi.city.ac.uk>**20070515150935] 
[Put some comments in about what the verbosity stuff means
Ian Lynagh <igloo at earth.li>**20070515125013] 
[rejig location of package interfaces for haddock
Ross Paterson <ross at soi.city.ac.uk>**20070515110833
 
 Formerly, setup haddock invoked haddock with a --use-package option
 for each prerequisite package, causing haddock to invoke ghc-pkg to
 get the haddock-interfaces and haddock-html fields for each package.
 The former is accurate, but the latter is not what you want if your
 documentation is to be placed on the web.
 
 Now setup haddock invokes ghc-pkg itself, but if the --html-location
 option is given, its argument is expanded for each package and used
 instead of the haddock-html field.  The results are then assembed as
 --read-interface options for haddock.  For example,
 
 	setup haddock '--html-location=http://hackage.haskell.org/packages/archive/$pkg/latest/doc/html'
 
 generates HTML documentation with hyperlinks pointing at the pages on
 HackageDB.
] 
[Fix warnings
Ian Lynagh <igloo at earth.li>**20070514173011] 
[Fix warnings
Ian Lynagh <igloo at earth.li>**20070514171124] 
[Fix a warning
Ian Lynagh <igloo at earth.li>**20070514170157] 
[Fix warnings
Ian Lynagh <igloo at earth.li>**20070514165951] 
[Compile with -Wall
Ian Lynagh <igloo at earth.li>**20070514161917] 
[Make a proper verbosity type, rather than using Int values
Ian Lynagh <igloo at earth.li>**20070514165514
 Hopefully this will make it easier to get better verbosity consistency.
 
 We could, by changing only Distribution.Verbosity, use
 "type Verbosity = Int" for now to give users of the library a chance to
 catch up, but the upcoming Cabal release seems like a good opportunity
 to cram in as much of the interface-changing stuff that we want to do
 as we can. I think the added benefit of a slow switch would be very low
 indeed.
] 
[separate build and output directory for Hugs build
Ross Paterson <ross at soi.city.ac.uk>**20070513001502
 
 Hugs requires a separate directory for the output files from the directory
 containing the preprocessed files.  The --scratchdir option now sets the
 former (and thus has an effect only for Hugs).
 
 This repairs the Hugs build.
] 
[non-GHC version of rawSystemStdout
Ross Paterson <ross at soi.city.ac.uk>**20070513001017] 
[remove copy of cabal-install library
Ross Paterson <ross at soi.city.ac.uk>**20070501160347] 
[Use Control.Exception even for nhc98 now.
Malcolm.Wallace at cs.york.ac.uk**20070504144146] 
[remove cabal-install and cabal-setup from Makefile
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070503220644
 These are no longer in the tree, they have their own repos now.
] 
[Fix more verbosity settings of messages
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070503213124] 
[Fix import of IO.try
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070503205024
 Hopefully System.IO.Error exists for nhc98 too.
] 
[For nhc98, restore 'systemGetStdout' under the name 'rawSystemStdout' :-)
Malcolm.Wallace at cs.york.ac.uk**20070503145457
 This should now be equivalent in functionality to what was previously removed.
] 
[Hack around non-portable System.Process stuff for nhc98.
Malcolm.Wallace at cs.york.ac.uk**20070503142544
 This is enough to permit Cabal to compile again, but it certainly won't run.
] 
[Fix a couple verbosity settings
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070502211900
 Showing what files are copied should only be shown at verbosity
 level 2 and above. The default verbosity level is 1.
 Similarly, creating the hidden package registration file should
 not be shown at the default verbosity level.
] 
[fix installIncludeFiles again.
Bertram Felgenhauer <int-e at gmx.de>**20070502182917
 the include file directory must be created for ghc, otherwise package registration will fail. sigh.
] 
[nhc98 does not have Control.Exception
Malcolm.Wallace at cs.york.ac.uk**20070502122017] 
[fix Haddock syntax error
Simon Marlow <simonmar at microsoft.com>**20070502093700] 
[Add test case for platform dependent and independent generated sources
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070501142716
 The c2hs .hs files should go in dist/build while the happy .hs source
 should remain in the src dir and end up in the sdist tarball.
] 
[fix installIncludeFiles thinko
Bertram Felgenhauer <int-e at gmx.de>**20070501131608
 due to the newly added guard, the "Can't happen" is no longer true.
] 
[Do not delete platform independent pre-processed sources during sdist
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070501142419
 Since only platform independent pre-processed sources are now left in the
 src dirs we don't have to delete any pre-processed sources and can just
 inlcude them all into the src tarball.
 Ideally we'd track this slightly better in future, it's not nice to be keeping
 any generates sources in the src dirs, they should be considered read-only.
] 
[Leave platform independent pre-processed sources in the src dir
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070501142323
 Only put platform dependent ones into dist/build
] 
[Record if pre-processors are platform independent
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070501142147
 PreProcessor is now a record with a couple fields.
 Quite a few knock-on changes due to changing this data type.
] 
[call c2hs using the more detailed info
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070422102617
 we use --output-dir=dist/base
 and --output=<file relative to the search dir it was found in>.hs
 This actually depends on a patch in c2hs to make it treat --output-dir
 in the way we want. That patch will be forthcomming soonish.
 But the point is:
 c2hs --output-dir=dist/base --output=Foo/Bar.hs src/Foo/Bar.chs
 will generate dist/base/Foo/Bar.hs and also dist/base/Foo/Bar.h
 but inside the .hs file it'll reference Foo/Bar.h so when we compile the
 .hs file we have to -Idist/base
 Clear as mud?
] 
[Generalise PreProcessors to take more detailed args
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070422100558
 Most pre-processors just need the full source file and target file names.
 More complicated ones where the generated files have to embed links to each
 other need more information. For example c2hs generates .hs file that
 reference generated .h files. These links should be relative to the dist/build
 dir and not to the top of the source tree, since we do not want to add -I. to
 the includes search path. We only want to use -Idist/build, hence the embeded
 links must be relative to that. Therefor c2hs needs to know the base output
 directory as well as the name of the file relative to that.
 So we add a new type PreProcessorFull that has this extra info and a function
 simplePP :: :: PreProcessor -> PreProcessorFull
 for the common case of most existing pre-processors that do not need this
 extra info.
 This patch doesn't actually change the c2hs stuff, that comes next.
] 
[Put pre-processed source into the dist/build dir rather than src dirs
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070422095631
 This is generally just a nicer thing to do, we should probably aim to
 not write any files into the source tree at all.
 The main change is in the preprocessModule function. It now takes an extra
 arg which is the destination directory. For now I'm passing the buildDir,
 but we could consider putting pre-processed files into a separate fir
 from where the .o and .hi files end up.
 To work out the correct destination file we need to know not only the source
 file but which of the search dirs it was found in, since the relative file
 name will be the name of the source file relative to the search dir it was
 found in, not the name relative to the top of the source tree. This is so that
 we will be able to find the pre-processed .hs file just by adding dist/build
 to the sources search path when we compile (eg with -i for ghc).
 This almost certainly breaks the sdist thing where pre-processed files get
 included into the tarball. So that'll need looking at.
] 
[update documentation for install-headers: field
Bertram Felgenhauer <int-e at gmx.de>**20070420131524] 
[install headers for all compilers
Bertram Felgenhauer <int-e at gmx.de>**20070420123527
 This patch moves the installation of header files from Distribution.Simple.GHC
 to Distribution.Simple.Install. This is required for the header files to be
 usable for preprocessing Haskell code in other packages.
] 
[don't automatically include install-include: headers into compilations via C
Bertram Felgenhauer <int-e at gmx.de>**20070420123418
 This way it's possible to install header files that are meant for preprocessing
 Haskell code, or header files that are meant to be indirectly included by
 others.
] 
[Don't overwrite existing makefiles
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070430203552
 Patch contributed by Bryan O'Sullivan
] 
[Fix openTempFile so it works on windows with ghc at least
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070430185744
 It's still a hack. The right solution is to proerly implement openTempFile
 in base for all Haskell impls, not just GHC.
] 
[Use rawSystem not system for capturing output of commands
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070430184046
 For example we were using a wrapper around 'system' to find the haddock
 version. This invokes the system command interpreter and passes the
 command to run as an argument. If the command has spaces in it and is not
 properly escaped then everything goes wrong. This happens for example
 on windows when haddock and other programs are kept under "Program Files".
 So the right thing to do is never to use system, but always rawSystem since
 then there are no escaping issues.
 
 This patch replaces a couple function systemCaptureStdout and systemGetStdout
 with rawSystemStdout which now lives in Distribution.Simple.Utils.
 
 This also uses some rather nasty code to get the output of a command.
 It really really should not be this hard to do portably. To work around
 the fact that we cannot use runInteractiveProcess we instead have to create
 a temporary file. This also turns out to be a hack because the 'standard'
 openTempFile is not implemented except by GHC, so we now have a hacky version
 living in Distribution.Compat.TempFile just waiting for the standard 
 openTempFile to be made properly portable, or for us to get some
 System.Process function that does what we want.
] 
[Fix the verbosity level for printing executed commands
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070430155054
 Since 1 is the default verbosity level we should only print commands
 at level 2 and above.
] 
[initialBuildSteps should not actually build.
Bryan O'Sullivan <bos at serpentine.com>**20070424183841] 
[pretend that Cabal can build with nhc98
Malcolm.Wallace at cs.york.ac.uk**20070424104244] 
[minor tweaks to nhc98 branches of case distinctions
Malcolm.Wallace at cs.york.ac.uk**20070212171419] 
[minor clarifications in doc of package descriptions
Ross Paterson <ross at soi.city.ac.uk>**20070423093806] 
[Fix for older GHCs, which exported a System.IO.try
Ian Lynagh <igloo at earth.li>**20070419002443] 
[work around missing Control.Exception for nhc98
Malcolm.Wallace at cs.york.ac.uk**20070418230821] 
[Remove unnecessary import
Ian Lynagh <igloo at earth.li>**20070418114407] 
[Fix imports
Ian Lynagh <igloo at earth.li>**20070418110139] 
[Change variable name to match type change
Ian Lynagh <igloo at earth.li>**20070418104811] 
[Fix Cabal's Setup.lhs after Maybe UserHooks / UserHooks change
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070418034619] 
[Behave the same on Windows and non-Windows
Ian Lynagh <igloo at earth.li>**20070417230311] 
[Stop having hooks return an ExitCode that we then ignore
Ian Lynagh <igloo at earth.li>**20070417225657] 
[Small tidyup
Ian Lynagh <igloo at earth.li>**20070417225031] 
[Stop pretending we might not have any UserHooks
Ian Lynagh <igloo at earth.li>**20070417224220] 
[Be better about exiting if a command we run fails
Ian Lynagh <igloo at earth.li>**20070417222257] 
[Suggest that missing deps need to be downloaded and installed from hackage
Ian Lynagh <igloo at earth.li>**20070417210158] 
[Make contents of SrcDist more useful to outside users.
Bryan O'Sullivan <bos at serpentine.com>**20070415060916
 
 This change simply splits sdist into three functions.
 
 The normal sdist function remains unchanged from the caller's
 perspective, but it now consists of two phases, each an exported function.
 The source tree is prepared by prepareTree, and the archive is created
 by createArchive.
 
 This lets the cabal-rpm tool prepare a source tree and insert a few
 extra files into it before generating a tarball.
 
] 
[setup makefile: handle hs-source-dirs
Simon Marlow <simonmar at microsoft.com>**20070416140205
 but only if there's a single entry for now.
] 
[setup makefile: use -p option to mkdir when making object directories
Simon Marlow <simonmar at microsoft.com>**20070416134720
 I had a feeble attempt to avoid needing this originally, using $(sort ...)
 to create parents before children, but sometimes the parents aren't in
 the list, so it doesn't work.  mkdir's -p option is POSIX, and I found
 it on all the platforms I checked (Linux, Solaris, Darwin, FreeBSD).
] 
[a couple of fixes to 'setup makefile'
Simon Marlow <simonmar at microsoft.com>**20070416133307
 Put the -package-name flag at the beginning of GHC_OPTS, allowing it
 to be overriden later (as we do in the base package, for example).
 Also, add -split-objs if necessary.
] 
[remove illegal literal tabs in strings (again)
Malcolm.Wallace at cs.york.ac.uk**20070416101220] 
[add missing support for .hs-boot/.lhs-boot with 'setup makefile'
Simon Marlow <simonmar at microsoft.com>**20070413152244] 
[Pass all the Cc/Ld flags to hsc2hs
Ian Lynagh <igloo at earth.li>**20070413131318] 
[REINSTATE: Fix C/Haskell type mismatches
Malcolm.Wallace at cs.york.ac.uk**20070412130607
 This patch was previously applied and then rolled back.
 This new version imports System.Posix.Types.CPid correctly for nhc98.
] 
[Fix -Wall warnings
Ian Lynagh <igloo at earth.li>**20070411004954] 
[-Wall fixes
Ian Lynagh <igloo at earth.li>**20070411003509] 
[Remove duplicate import
Ian Lynagh <igloo at earth.li>**20070410170930] 
[remove illegal tab chars in string literals
Malcolm.Wallace at cs.york.ac.uk**20070410085626] 
[Use Distribution.Compat.FilePath.pathSeparator in Distribution.SetupWrapper, instead of having a local copy.
bjorn at bringert.net**20070409165203] 
[Fix C/Haskell type mismatches
Ian Lynagh <igloo at earth.li>*-20070404003510] 
[Rejig the adjacent checking in the unlitter
Ian Lynagh <igloo at earth.li>**20070407173415
 We were rejecting
     # 1 "foo"
     > ...
 in the HUnit package, claiming that it had a comment next to a program line.
 Now we treat anything cpp inserts as being blank.
] 
[parse (but don't pass on) options for ./configure
Ian Lynagh <igloo at earth.li>**20070406153622] 
[Remove cabal-{builder,install,setup,upload} (now in separate repos)
Ian Lynagh <igloo at earth.li>**20070405194729] 
[Add 'setup makefile' command
Simon Marlow <simonmar at microsoft.com>**20070309155022
 'setup makefile' generates a Makefile that performs the steps
 necessary to compile the Haskell sources to object code.  This only
 works for libraries, and only with GHC right now.
 
 Instead of simply 'setup build', you can do this:
 
   $ ./setup makefile
   $ make
   $ ./setup build
 
 where './setup makefile' does the preprocessing and generates a
 Makefile tailored to the current package.  'make' will build all the
 Haskell code to object files, and 'setup build' will build any C code
 and the library archives.
 
 The reason for all this is that you can say 'make -j' and get a
 parallel build, or you can say
 
   make dist/build/Foo.o EXTRA_HC_OPTS=-keep-s-file
 
 to compile a single file with extra options.
] 
[make Setup suitable for building the libraries with GHC
Ian Lynagh <igloo at earth.li>**20061112214536] 
[Expose Distribution.Compat.ReadP
Ian Lynagh <igloo at earth.li>**20061112214447] 
[Fix C/Haskell type mismatches
Ian Lynagh <igloo at earth.li>**20070404003510] 
[Use rawSystemPath for calling tar rather than system
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070327110606
 Means we get -v verboe output and better error messages if the command
 is not found.
] 
[Check the return value of tar
Bryan O'Sullivan <bos at serpentine.com>**20070326234148] 
[Fixed and improved Haddock comments
sven.panne at aedion.de**20070322164427] 
[If we export ParseResult, we should export PError and PWarning, too
sven.panne at aedion.de**20070322164340] 
[remove Makefile.inc (only affects nhc98)
Malcolm.Wallace at cs.york.ac.uk**20070320120844] 
[Fixes compiling an executable for profiling with template haskell.
Judah Jacobson <judah.jacobson at gmail.com>**20070314012802] 
[rejig handling of continuation lines (fixes Cabal #118)
Ross Paterson <ross at soi.city.ac.uk>**20070311154610
 
 Also avoids quadratic behaviour on long fields.
] 
[add Distribution.SetupWrapper to exposed-modules
Simon Marlow <simonmar at microsoft.com>**20070309122146] 
[Tweaks to make Cabal play nicer with haddock
Ian Lynagh <igloo at earth.li>**20070308155718
 
 The path for the html docs now includes the package name at the end,
 which works nicer for multiple packages sharing a contents/index.
 
 Use --ghc-pkg when available (in haddock darcs only currently) to tell
 haddock which ghc-pkg to use.
 
 Use --allow-missing-html when available (in haddock darcs only
 currently) to tell haddock not to worry if it can't find the HTML for
 packages we depend on. This is necessary when haddocking a group of
 packages before moving them all into place.
] 
[Cope with ghc-pkg telling us packages are broken
Ian Lynagh <igloo at earth.li>**20070307193131] 
[Tell GHC to use .hs mode when we want it to cpp something for us
Ian Lynagh <igloo at earth.li>**20070307143612] 
[Add parentheses so expressions are parsed correctly
Ian Lynagh <igloo at earth.li>**20070307131941] 
[minor refactoring
Ross Paterson <ross at soi.city.ac.uk>**20070301002731] 
[fix \begin{code typo
Ross Paterson <ross at soi.city.ac.uk>**20070301002557] 
[document the --with-compiler / --with-hc inconsistency
Ross Paterson <ross at soi.city.ac.uk>**20070225115601] 
[Clarify documentation on --with-compiler and --with-hc-pkg
simonpj at microsoft.com**20070221110452] 
[minor markup tweaks
Ross Paterson <ross at soi.city.ac.uk>**20070218104622] 
[This usePackages stuff is haddock-specific so name it as such
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20070213201434] 
[{en,dis}able-use-packages, -optP-P only if haddock<0.8
Conal Elliott <conal at conal.net>**20070204061106] 
[cabal-upload: Added command-line options for username, password, checking instead of uploading. Added ability to get login from file, and to get password from the terminal. Added still unused verbosity options. Bumped version number to 0.2.
bjorn at bringert.net**20070212232920] 
[exclude Setup.lhs
Ross Paterson <ross at soi.city.ac.uk>**20070212193608
 
 This was generating a useless Main entry in the lib doc index.
 (good for STABLE)
] 
[Add recent Cabal modules to nhc98 build system.
Malcolm.Wallace at cs.york.ac.uk**20070212171106] 
[Compatibility with Haskell'98.
Malcolm.Wallace at cs.york.ac.uk**20070212170804
 Import Distribution.Compat.Exception instead of Control.Exception.
 Fix illegal indentation of cascaded do-blocks.
] 
[add --enable-optimization/--disable-optimization config options (on by default)
Ross Paterson <ross at soi.city.ac.uk>**20070212004513] 
[cabal-upload: nicer output.
bjorn at bringert.net**20070206154619] 
[Send Accept header.
bjorn at bringert.net**20070206153521] 
[Allow uploading multiple packages.
bjorn at bringert.net**20070206153406] 
[Changed HTTP dependency to >= 1.0. 
bjorn at bringert.net**20070206153054] 
[cabal-upload: Removed build-simple since hackage doesn't seem to accept it for non-lib packages.
bjorn at bringert.net**20070206133616] 
[Added URL for cabal-upload wiki page.
bjorn at bringert.net**20070206132142] 
[Added usage message to cabal-upload.
bjorn at bringert.net**20070206131408] 
[Added a small hacky first version of cabal-upload.
bjorn at bringert.net**20070206112237] 
[cabal-setup doesn't need -cpp
Ross Paterson <ross at soi.city.ac.uk>**20070115154724] 
[Refactorings only
Simon Marlow <simonmar at microsoft.com>**20070114203741
 Here are a batch of refactorings to clean up parsing and parts of the
 simple build system.  This patch originated in a patch sent to
 cabal-devel at haskell.org with an intial implementation of
 configurations.  Since then we decided to go a different route with
 configurations, so I have separated the refactoring from the
 configurations patch.
 
 At this point, 2 tests fail for me, but I get the same 2 failures
 without this patch.
] 
[pass arguments through when performing the setup actions ourselves
Ross Paterson <ross at soi.city.ac.uk>**20070113133211] 
[separate option for the compiler for Setup.hs
Ross Paterson <ross at soi.city.ac.uk>**20070113133000
 
 This need not be the same compiler as used to build the package
] 
[Ignoring user packages when installing locally doesn't make sense.
Lemmih <lemmih at gmail.com>**20070112150318] 
[cabal-install now caches downloaded packages in the directory for the package, and with .tar.gz extension.
bjorn at bringert.net**20070112143527] 
[cabal-install.cabal: Added build-type field. Change hs-source-dir to hs-source-dirs (hs-source-dir has been deprecated for some time).
bjorn at bringert.net**20070112131959] 
[cabal-install --user now keeps package cache and package list in ~/.cabal-install
bjorn at bringert.net**20070112131301] 
[fix ghc-options (not a listField)
bjorn at bringert.net**20070112124938] 
[add a Build-Type field, and use it in setupWrapper
Ross Paterson <ross at soi.city.ac.uk>**20070111233018
 
 As discussed on the libraries list (Nov 2006), add a field Build-Type
 which can be used to declare that this package uses one of the boilerplate
 setup scripts.  This allows setupWrapper (used by cabal-setup and
 cabal-install) to bypass the setup script in this case and perform
 the setup actions itself.
] 
[remove a use of null+head
Ross Paterson <ross at soi.city.ac.uk>**20070111182430] 
[remove two fromJust's
Ross Paterson <ross at soi.city.ac.uk>**20070111182401] 
[pass CABAL_VERSION to Hugs
Ross Paterson <ross at soi.city.ac.uk>**20070111182216] 
[cabal-install now puts the package list in /var/lib/cabal-install and the tarballs in /var/cache/cabal-install by default. Added command-line options for changing those.
bjorn at bringert.net**20070111190452] 
[Track verbosity argument changes
Ian Lynagh <igloo at earth.li>**20070111180601] 
[Testsuite quietening
Ian Lynagh <igloo at earth.li>**20070111175329] 
[cabal-install: Output usage info for the right command when pasrsing the package name arguments fails.
bjorn at bringert.net**20070111164924] 
[SetupWrapper now passes verbosity to other functions, as required by Igloo's patch.
bjorn at bringert.net**20070111161651] 
[Make cabal-install use setupWrapper (the library version of cabal-setup).
bjorn at bringert.net**20070111160535] 
[Moved the cabal-setup code to Distribution.SetupWrapper, so that cabal-install can use it. CabalSetup.hs now just calls the setupWrapper function.
bjorn at bringert.net**20070111130506] 
[Quieten the testsuite more
Ian Lynagh <igloo at earth.li>**20070111155957] 
[Pass verbosity info down to warn
Ian Lynagh <igloo at earth.li>**20070111154526] 
[Derive Show on various datatypes
Ian Lynagh <igloo at earth.li>**20070111140220] 
[Give feedback in runTests.sh
Ian Lynagh <igloo at earth.li>**20070111132654] 
[Be less verbose at verbosity level 1
Ian Lynagh <igloo at earth.li>**20070111131228] 
[Fix warning
Ian Lynagh <igloo at earth.li>**20070111130928] 
[No need for -fno-warn-unused-matches any more
Ian Lynagh <igloo at earth.li>**20070111130824] 
[Always pass Hooks around, not Maybe Hooks
Ian Lynagh <igloo at earth.li>**20070111124234] 
[Make Makefile use the right ghc/ghc-pkg
Ian Lynagh <igloo at earth.li>**20070111122833] 
[Add -Wall to GHCFLAGS
Ian Lynagh <igloo at earth.li>**20070111102742] 
[Updated cabal-install test scripts to use the main Cabal repo.
bjorn at bringert.net**20070111111727] 
[Added cabal-install test scripts.
bjorn at bringert.net**20070110184835] 
[Added cabal-install Makefile.
bjorn at bringert.net**20070110184754] 
[Added HTTP package code used by cabal-install.
bjorn at bringert.net**20070110184545] 
[Imported all the cabal-install sources.
bjorn at bringert.net**20070110183142] 
[Added cabal-install dep on regex-compat.
bjorn at bringert.net**20070110180020] 
[Removed old CabalInstall.hs (it has moved to cabal-install/src in one of the pataches I pulled in).
bjorn at bringert.net**20070110174435] 
[Pulling in cabal-install: changed default Hackage DB URL.
bjorn at bringert.net**20070110173825] 
[Pulling cabal-with-install into Cabal: cabal-install.cabal changes.
bjorn at bringert.net**20070110172811] 
[Pulling changes from cabal-with-install: Multiple repositories.
bjorn at bringert.net**20070110164852
 Original patch:
 Sat Sep  2 00:13:40 CEST 2006  Paolo Martini <paolo at nemail.it>
   * Multiple repositories.
] 
[Pulling changes from cabal-with-install: Stripping off the dependencies, only HTTP left
bjorn at bringert.net**20070110164556
 Original patch:
 Sun Aug 20 19:01:03 CEST 2006  Paolo Martini <paolo at nemail.it>
   * Stripping off the dependencies, only HTTP left
] 
[Resolve Makefile conflict from importing Cabal-with-install patches.
bjorn at bringert.net**20070110163852] 
[a program to test download & install a bunch of cabal packages
ijones at syntaxpolice.org**20061114063409] 
[added --inplace trick to cabal build so that cabal-install can build on machines without cabal.
ijones at syntaxpolice.org**20060922034620] 
[First attempt to make a new repository (url in the configuration)
Paolo Martini <paolo at nemail.it>**20060820180342] 
[Tarball index format support
Paolo Martini <paolo at nemail.it>**20060816223509] 
[Quieten a test
Ian Lynagh <igloo at earth.li>**20070110175223] 
[Pass 0 verbosity on to GHC when building
Ian Lynagh <igloo at earth.li>**20070110174050] 
[More verbosity tweaking
Ian Lynagh <igloo at earth.li>**20070110172956] 
[Rejig verbosity levels a bit; 1 is now the default (was 0)
Ian Lynagh <igloo at earth.li>**20070110165149] 
[Make system tweaks to avoid cabal thinking it isn't bootstrapped when running the testsuite
Ian Lynagh <igloo at earth.li>**20070110162940] 
[Typo
Ian Lynagh <igloo at earth.li>**20070110154617] 
[Refer to the right variables
Ian Lynagh <igloo at earth.li>**20070110151326] 
[Give unrecognised flags more clearly
Ian Lynagh <igloo at earth.li>**20070110144650] 
[Beautify
Ian Lynagh <igloo at earth.li>**20070110143711] 
[Retab
Ian Lynagh <igloo at earth.li>**20070110143103] 
[Remove some chatter from the test scripts
Ian Lynagh <igloo at earth.li>**20070110142756] 
[Eliminate more warnings
Ian Lynagh <igloo at earth.li>**20070110142114] 
[More -Wall clean fixes
Ian Lynagh <igloo at earth.li>**20070110135838] 
[Improve cleaning
Ian Lynagh <igloo at earth.li>**20070110134230] 
[-Wall clean fixes
Ian Lynagh <igloo at earth.li>**20070110125523
 
 This patch is sponsored by Hac 07.
 Have you hacked a lambda today?
] 
[Fix non-fatal problem with 'setup haddock' for an exe package
Simon Marlow <simonmar at microsoft.com>**20070109133751
 For some unknown reason, we were passing --use-package=P to haddock,
 where P is the name of the current executable package.  This can never
 work, since P is not a library and will not be installed.  Fortunately
 Haddock ignores the error and continues anyway.
 
] 
[Set the Cabal version when building via the fptools build system
sven.panne at aedion.de**20070106152814
 
 Without this patch, Cabal is effectively "version-less" and all .cabal
 files with a version requirement are unusable. Therefore I think that
 this patch (or at least something equivalent) should be pushed to the
 6.6.1 branch, too.
] 
[added --save-configure flag to clean. got some complaints that there was no way to avoid reconfiguring after a clean.  now if you use --save-configure, you should be able to.
ijones at syntaxpolice.org**20061219152204] 
[tiny mod to License comments
ijones at syntaxpolice.org**20061219060021] 
[improving help output
ijones at syntaxpolice.org**20061219055849
 As suggested by Claus Reinke in this ticket:
 http://hackage.haskell.org/trac/hackage/ticket/105
] 
[fix ./Setup unregister --help, which was giving the help for register
Simon Marlow <simonmar at microsoft.com>**20061215165000] 
[Fix the links in the user guide to the API docs
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>*-20061129131633] 
[Fix the links in the user guide to the API docs
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061129131633] 
[haddock comments for SrcDist.hs
ijones at syntaxpolice.org**20061127041303] 
[some haddock comments for LocalBuildInfo.hs
ijones at syntaxpolice.org**20061127040916] 
[a little comment for JHC.hs
ijones at syntaxpolice.org**20061127040026] 
[some comments for Install.hs
ijones at syntaxpolice.org**20061127035919] 
[some comments for Hugs.hs
ijones at syntaxpolice.org**20061127035310] 
[haddock comments for GHC and GHCPackageConig
ijones at syntaxpolice.org**20061127034617] 
[some comments for Configure.hs
ijones at syntaxpolice.org**20061127033157] 
[some comments for Build.hs
ijones at syntaxpolice.org**20061127032409] 
[minor comments and cleanup for Setup.hs
ijones at syntaxpolice.org**20061127031744] 
[some haddock explanation of preprocessors
ijones at syntaxpolice.org**20061127031055] 
[some comments for Package.hs
ijones at syntaxpolice.org**20061127025108] 
[haddockizing some comments from Make.hs
ijones at syntaxpolice.org**20061127024142] 
[adding comments to Program.hs
ijones at syntaxpolice.org**20061127022353] 
[comments for the Program module
ijones at syntaxpolice.org**20061127002749] 
[don't return an error code just because there's no library to register
ijones at syntaxpolice.org**20061124144831] 
[Purely cosmetic; have '--<FOO>-args' use ARGS on their RHS rather than PATH in usage output
sof at galois.com**20061121195844] 
[parse executable field as a token (as documented), rather than free text
Ross Paterson <ross at soi.city.ac.uk>**20061120093400] 
[trim trailing spaces (including CRs) from all input lines
Ross Paterson <ross at soi.city.ac.uk>**20061120092526] 
[help nhc98 find the import of programLocation
Malcolm.Wallace at cs.york.ac.uk**20061117144001] 
[sdist: make it work on Windows platforms by simplifying 'tar' invocation. Hopefully not at the cost of other plats (i.e., as-yet untested there..)"
sof at galois.com**20061117014832] 
[build: consult and use any user-provided settings for 'ld' and 'ar'
sof at galois.com**20061117014622] 
[defaultUserHooks.sDistHook: pass in optional LBI to SrcDist.sdist
sof at galois.com**20061117014448] 
[defaultProgramConfiguration: add 'ld' and 'tar' entries
sof at galois.com**20061117014318] 
[revise Paths module for the Hugs target
Ross Paterson <ross at soi.city.ac.uk>**20061108223349
 
 When targetting Hugs, the Paths module now uses prefix-independent
 paths relative to the location of the Main module of the program,
 on all platforms.
 
 For the Hugs target, this replaces the code using GetModuleFileNameA(),
 which never worked.  Behaviour under GHC should be unchanged.
] 
[Hugs: fix location of installed package info
Ross Paterson <ross at soi.city.ac.uk>**20061021144613] 
[Fix escaping of ' chars in register.sh script.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061016215459] 
[Tidy up command comments
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061013211158] 
[Fix getDataDir etc. when bindir=$prefix
Simon Marlow <simonmar at microsoft.com>**20061013100941] 
[Update text on the front page: packages can now overlap in GHC 6.6
Simon Marlow <simonmar at microsoft.com>**20061012114601
 
] 
[New unlit code "ported" from cpphs-1.2
Lennart Kolmodin <kolmodin at dtek.chalmers.se>**20061009192609] 
[Share one more place where the cabal version is defined.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061010140027] 
[Fix spelling error in error message.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061010140013] 
[Centeralise the places that know that Cabal version number
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061010135918] 
[Remove spurious debug message.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061010125643] 
[Bump to next unstable development version
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061010125602] 
[Make cabal know it's own version number correctly
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061010130939
 This is an unpleasent way of doing it.
 Will have to fix once and for all in the next version.
] 
[TAG 1.1.6
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061009123801] 
[Bum version to 1.1.6 release
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061009123733] 
[Add note about unix dep for ghc-6.2
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061009123632] 
[Update README, changelog and releaseNotes
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061009123558] 
[TAG 1.1.5.9.4
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061007141722] 
[Bump version to 1.1.5.9.4
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061007141412] 
[Only use -package-name with the package's version number for ghc-6.4
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061007123309
 This change was added for ghc-6.6 but broke packages for ghc-6.2.2.
] 
[Make the configure step respect the HC makefile var
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061007113643] 
[Have the default make target be build rather than test
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061007113556
 This is more normal.
] 
[Read the buildinfo for the haddock step.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061005212138
 In particular this means we pick up any cc-options that are
 needed for preprocessing the source before haddock reads it.
 This fixes the haddock build step for many of the packages in
 the ghc-extralibs collection.
] 
[Use pragma OPTIONS rather than OPTIONS_GHC for compatability with ghc 6.2.x
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20061005211937] 
[TAG 1.1.5.9.3
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060911223941] 
[Bump version for 3rd 1.1.6 release candidate
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060911223908] 
[Make Distribution.Compat.FilePath public and Distribution.Compat.ReadP private
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060911222733
 Ideally all the Distribution.Compat.* modules would be private,
 however there is currently no sensible alternative to the FilePath module
 and hiding it at this stage breaks packages.
] 
[Use slightly simpler way of getting GHC version.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060823105956
 ghc has supported --numeric-version for ages.
] 
[Be cleverer about guessing hc-pkg name and location.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060823105412
 So it now works if you say:
 ./setup configure --with-compiler=ghc-6.5
 ie specifying a path-relative name rather than an absolute path.
 We then look for hc-pkg in the same dir as where we found the compiler.
 If the compiler appears to have a version suffix then we additionally
 and preferentially look for hc-pkg with that same version suffix.
 (I'm not sure that bit works if you've got a .exe suffix, perhaps a
 windows person could try it / take a look)
] 
[CabalSetup: reuse './setup' if it's newer than the setup script.
Lemmih <lemmih at gmail.com>**20060926231910] 
[Fix the combination of --enable-library-profiling and --enable-split-objs
Lemmih <lemmih at gmail.com>**20060926231658] 
[clarification of the way --inplace works
ijones at syntaxpolice.org**20060922042102] 
[cleanups to user's guide
Ross Paterson <ross at soi.city.ac.uk>**20060910144428
 
  * markup fixes
  * spelling
  * id's for some elements to avoid warnings
  * mention the use of Description field by setup haddock
  * clean up --hoogle description
] 
[Check exit codes!
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060908173615
 Cabal was not noticing haddock failing. That's bad.
] 
[Use {-# OPTIONS_GHC -cpp #-} so that runghc Setup.lhs works.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060908153717] 
[TAG 1.1.5.9.2
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060906234045] 
Patch bundle hash:
c1e1073b196e5d904420bb7fb0f4bd6c3fa650bc


More information about the cabal-devel mailing list