Wed Mar 19 18:50:52 CET 2008  Pepe Iborra <[EMAIL PROTECTED]>
  * #223 part2: Support all the configure options in the config file
  
  This patch takes advantage of the new OptionField structure in 
Distribution.Simple.Command
  to provide support for all the configure command line options in the 
.cabal/config file.
  This has a global effect on all the packages managed by cabal-install.
  
  The ticket also mentions support for per-package sections in the config file. 
This patch
  does not take care of that.
  
New patches:

[#223 part2: Support all the configure options in the config file
Pepe Iborra <[EMAIL PROTECTED]>**20080319175052
 
 This patch takes advantage of the new OptionField structure in Distribution.Simple.Command
 to provide support for all the configure command line options in the .cabal/config file.
 This has a global effect on all the packages managed by cabal-install.
 
 The ticket also mentions support for per-package sections in the config file. This patch
 does not take care of that.
 
] {
hunk ./Hackage/Config.hs 24
-import Data.Char (isAlphaNum, toLower)
+import Data.Char (isAlphaNum)
hunk ./Hackage/Config.hs 32
-import Distribution.Compat.ReadP (ReadP, char, munch1, readS_to_P)
+import Distribution.Compat.ReadP (ReadP, char, munch1)
hunk ./Hackage/Config.hs 41
-import Distribution.Simple.Setup (Flag(..), toFlag, fromFlag, fromFlagOrDefault)
+import Distribution.Simple.Command (ShowOrParseArgs(..), viewAsFieldDescr)
+import Distribution.Simple.Program (defaultProgramConfiguration)
+import Distribution.Simple.Setup ( Flag(..), toFlag, fromFlag, fromFlagOrDefault
+                                 , ConfigFlags, defaultConfigFlags, configureOptions)
+import qualified Distribution.Simple.Setup as ConfigFlags
hunk ./Hackage/Config.hs 68
-    configCompiler          :: Flag CompilerFlavor,
-    configCompilerPath      :: Flag FilePath,
-    configHcPkgPath         :: Flag FilePath,
-    configUserInstallDirs   :: InstallDirs (Flag PathTemplate),
-    configGlobalInstallDirs :: InstallDirs (Flag PathTemplate),
hunk ./Hackage/Config.hs 70
-    configVerbose           :: Flag Verbosity,
-    configUserInstall       :: Flag Bool,        -- ^--user-install flag
hunk ./Hackage/Config.hs 71
-    configUploadPassword    :: Flag Password
+    configUploadPassword    :: Flag Password,
+    configUserInstallDirs   :: InstallDirs (Flag PathTemplate),
+    configGlobalInstallDirs :: InstallDirs (Flag PathTemplate),
+    configFlags             :: ConfigFlags
hunk ./Hackage/Config.hs 78
+configUserInstall     :: SavedConfig -> Flag Bool
+configUserInstall     =  ConfigFlags.configUserInstall . configFlags
+
hunk ./Hackage/Config.hs 89
-savedConfigToConfigFlags userInstallFlag config = mempty {
-    Cabal.configHcFlavor    = configCompiler config,
-    Cabal.configHcPath      = configCompilerPath config,
-    Cabal.configHcPkg       = configHcPkgPath config,
+savedConfigToConfigFlags userInstallFlag config = (configFlags config) {
hunk ./Hackage/Config.hs 93
-                                else configGlobalInstallDirs config,
-    Cabal.configVerbose     = configVerbose config
+                                else configGlobalInstallDirs config
hunk ./Hackage/Config.hs 132
-         { configCompiler          = toFlag defaultCompiler
-         , configCompilerPath      = mempty
-         , configHcPkgPath         = mempty
+         { configFlags = (defaultConfigFlags defaultProgramConfiguration){
+                           ConfigFlags.configHcFlavor    = toFlag defaultCompiler
+                         , ConfigFlags.configVerbose     = toFlag normal
+                         , ConfigFlags.configUserInstall = toFlag True
+                         , ConfigFlags.configInstallDirs = error
+                             "ConfigFlags.installDirs: avoid this field. Use UserInstallDirs \
+                              \ or GlobalInstallDirs instead"
+                         }
hunk ./Hackage/Config.hs 144
-         , configVerbose           = toFlag normal
-         , configUserInstall       = toFlag True
hunk ./Hackage/Config.hs 187
-configFieldDescrs = 
-    configWriteFieldDescrs
+configFieldDescrs =
+    map ( configFlagsField . viewAsFieldDescr) (configureOptions ShowArgs)
+    ++ configCabalInstallFieldDescrs
hunk ./Hackage/Config.hs 193
--- | The subset of the config file fields that we write out
--- if the config file is missing.
-configWriteFieldDescrs :: [FieldDescr SavedConfig]
-configWriteFieldDescrs =
-    [ simpleField "compiler"
-                (text . show . fromFlagOrDefault GHC) (fmap toFlag parseCompilerFlavor)
-                configCompiler (\c cfg -> cfg { configCompiler = c })
-    , listField "repos"
+configCabalInstallFieldDescrs :: [FieldDescr SavedConfig]
+configCabalInstallFieldDescrs =
+    [ listField "repos"
hunk ./Hackage/Config.hs 202
-    , boolField "user-install" (fromFlag . configUserInstall) (\u cfg -> cfg { configUserInstall = toFlag u })
hunk ./Hackage/Config.hs 213
+                              
+-- | The subset of the config file fields that we write out
+-- if the config file is missing.
+configWriteFieldDescrs :: [FieldDescr SavedConfig]
+configWriteFieldDescrs = configCabalInstallFieldDescrs
+                         ++ [f | f <- configFieldDescrs, fieldName f `elem` ["compiler", "user-install"]]
hunk ./Hackage/Config.hs 231
+configFlagsField :: FieldDescr ConfigFlags -> FieldDescr SavedConfig
+configFlagsField = liftField configFlags (\ff cfg -> cfg{configFlags=ff})
+
hunk ./Hackage/Config.hs 259
-parseCompilerFlavor :: ReadP r CompilerFlavor
-parseCompilerFlavor = 
-    do s <- munch1 isAlphaNum
-       return $ case map toLower s of
-                  "ghc"    -> GHC
-                  "nhc"    -> NHC
-                  "hugs"   -> Hugs
-                  "hbc"    -> HBC
-                  "helium" -> Helium
-                  "jhc"    -> JHC
-                  _        -> OtherCompiler s
-
hunk ./Hackage/Setup.hs 44
-import Distribution.Simple.Setup (Flag(..), toFlag, flagToList)
-import Distribution.Verbosity (Verbosity, normal, flagToVerbosity, showForCabal)
-
+import Distribution.Simple.Setup (Flag(..), toFlag, flagToList, trueArg, optionVerbose)
+import Distribution.Verbosity (Verbosity, normal)
hunk ./Hackage/Setup.hs 220
-optionDryRun :: Option InstallFlags
+optionDryRun :: OptionField InstallFlags
hunk ./Hackage/Setup.hs 227
-optionOnly :: Option InstallFlags
+optionOnly :: OptionField InstallFlags
hunk ./Hackage/Setup.hs 234
-optionRootCmd :: Option InstallFlags
+optionRootCmd :: OptionField InstallFlags
hunk ./Hackage/Setup.hs 239
-    (reqArg "COMMAND" toFlag flagToList)
+    (reqArg' "COMMAND" toFlag flagToList)
hunk ./Hackage/Setup.hs 291
-        (reqArg "USERNAME" toFlag flagToList)
+        (reqArg' "USERNAME" toFlag flagToList)
hunk ./Hackage/Setup.hs 296
-        (reqArg "PASSWORD" toFlag flagToList)
+        (reqArg' "PASSWORD" toFlag flagToList)
hunk ./Hackage/Setup.hs 319
-liftOptionsFst :: [Option a] -> [Option (a,b)]
+liftOptionsFst :: [OptionField a] -> [OptionField (a,b)]
hunk ./Hackage/Setup.hs 322
-liftOptionsSnd :: [Option b] -> [Option (a,b)]
+liftOptionsSnd :: [OptionField b] -> [OptionField (a,b)]
hunk ./Hackage/Setup.hs 325
-trueArg {-, falseArg-} :: (b -> Flag Bool) -> (Flag Bool -> b -> b) -> ArgDescr b
-trueArg  = noArg (Flag True) (\f -> case f of Flag True  -> True; _ -> False)
---falseArg = noArg (Flag False) (\f -> case f of Flag False -> True; _ -> False)
-
-optionVerbose :: (flags -> Flag Verbosity)
-              -> (Flag Verbosity -> flags -> flags)
-              -> Option flags
-optionVerbose get set =
-  option "v" ["verbose"]
-    "Control verbosity (n is 0--3, default verbosity level is 1)"
-    get set
-    (optArg "n" (toFlag . flagToVerbosity)
-                (fmap (Just . showForCabal) . flagToList))
-
}

Context:

[Record and report the exceptions that cause build failure
Duncan Coutts <[EMAIL PROTECTED]>**20080319170753
 When installing a bunch of package we have to catch exceptions since
 we carry on building other packages that did not depend on the
 failing package. We were recording what phase the failure was in but
 not the actual exception. We now record that too and print it along
 with the more general explanation of what package failed and in
 which phase. It's not perfect, eg when a package fails to compile we
 end up printing that the exception was "ExitFailure 1" which is not
 very useful.
] 
[Simplify the tar code a bit more
Duncan Coutts <[EMAIL PROTECTED]>**20080319015243
 We always know the base path for construction or extraction so don't
 bother using Maybe FilePath. Also use GZip qualified.
] 
[Use relative paths when makeing tar.gz rather than changing current dir
Duncan Coutts <[EMAIL PROTECTED]>**20080319013936
 The current directory is a global variable, we should not mutate it.
 So instead, pass a base and relative path when generating tar entries.
 Also change sanitizePath to be pure and use FilePath.Poisx.
] 
[Minor changes to the tar packing code
Duncan Coutts <[EMAIL PROTECTED]>**20080319000919
 Use lazy bytestring when packing tar entry headers rather than strict and
 then making a single chunk lazy bytestring later. The lazy bytestring pack
 will only generate a single chunk for a String that short (<4k).
 Use openBinaryFile rather than openFile + hSetBinaryMode.
 Add a haddock module header with copyright note.
] 
[Refactor the SrcDist code in a similar way as in the Cabal lib
Duncan Coutts <[EMAIL PROTECTED]>**20080319000633] 
[fix imports, because Dependency has moved in Cabal
Andrea Vezzosi <[EMAIL PROTECTED]>**20080318174423] 
[FIX #40, now cabal sdist creates the archive using Hackage.Tar
Andrea Vezzosi <[EMAIL PROTECTED]>**20080318173047
 we don't call setup sdist anymore but we use functions from Distribution.Simple.SrcDist
] 
[Parse filepaths in the config file the same way as in .cabal files
Duncan Coutts <[EMAIL PROTECTED]>**20080312135335
 That is, allow quoted and unquoted paths.
] 
[Implement CLI flag --root-cmd for 'cabal install' as in #202
Andrea Vezzosi <[EMAIL PROTECTED]>**20080306160816
 It also adds the internal flag --only so we can avoid building a setup when build-type == Simple.
] 
[List.hs: fix synopsis paragraph wrapping
Brent Yorgey <[EMAIL PROTECTED]>**20080307192159] 
[Adapt to using the bundled ReadP
Duncan Coutts <[EMAIL PROTECTED]>**20080310233609
 +1 for using the same version of the ReadP lib everywhere,
 previously we would only have noticed this type error with nhc98.
] 
[Make the 'upload' command more self explanatory
Duncan Coutts <[EMAIL PROTECTED]>**20080310233346
 It tells you what to do if you don't supply any args, rather than doing
 nothing and it check for simple mistakes and gives helpful error messages.
] 
[Use new buildOS and buildArch
Duncan Coutts <[EMAIL PROTECTED]>**20080306114834] 
[Hackage/List.hs: reflow paragraphs when displaying synopsis/description.
Brent Yorgey <[EMAIL PROTECTED]>**20080305193407] 
[Attempt to make things work using hugs, assume everything is installed
Duncan Coutts <[EMAIL PROTECTED]>**20080305152641] 
[Instead of Setup.lhs use .hs like everyone else does
Duncan Coutts <[EMAIL PROTECTED]>**20080303232408] 
[Hackage/List.hs: port showPackageInfo to pretty-printing combinators, improve display of packages with multi-line synopses
Brent Yorgey <[EMAIL PROTECTED]>**20080304211707] 
[Fix defect when unpacking tar files containing links
Lennart Kolmodin <[EMAIL PROTECTED]>**20080304194255
 There were two issues;
   * Unpacking links that point to files not yet unpacked
   * Used the link target as absolute path, but it's relative
 This patch addresses both issues, which is ticket #246.
 There may still be errors if a link refer to another link which has not
 been unpacked yet.
] 
[Update for recent Cabal lib api and behaviour changes
Duncan Coutts <[EMAIL PROTECTED]>**20080303213931
 Depend on latest Cabal lib version and bump our own version due to recent
 feature additions and removal of the 'info' command.
] 
[CLI completion: Add completion of packages
Lennart Kolmodin <[EMAIL PROTECTED]>**20080303183231
 Add completion of packages to the commands install, list, upgrade and fetch.
 Only complete packages if the user is not trying to complete a flag.
 Complete with package-versions if the package name ends with a dash,
 otherwise just complete with the package names.
] 
[Fix fromFlag bug and use default flags for list command
Duncan Coutts <[EMAIL PROTECTED]>**20080303164154] 
[Fix savedConfigToConfigFlags so the command line overrides the config
Duncan Coutts <[EMAIL PROTECTED]>**20080303140007
 "cabal configure --global" was incorrectly passing the user prefix to setup.
] 
[In 'list', also include packages that are only installed and not available
Duncan Coutts <[EMAIL PROTECTED]>**20080303010346
 Previously we took the available packages and did an inner join with the
 installed packages so we missed out packages like base which are installed
 by not available. Now we get the selected installed and available package
 sets and do a full outer join using a sort and merge operation.
 Also use a proper data type to hold the info we print about each package.
] 
[Remove shortopt -I for --installed
Lennart Kolmodin <[EMAIL PROTECTED]>**20080302195639] 
[Implement 'cabal list --simple-output'
Lennart Kolmodin <[EMAIL PROTECTED]>**20080302195437
 Provides a output format that is easier to pass on to unix tools and other
 scripting tools. Also works together with --installed.
] 
[Implement --installed to 'cabal list'
Lennart Kolmodin <[EMAIL PROTECTED]>**20080301222704
 Adding --installed to 'cabal list' will make it print only packages that are
 installed.
] 
[Improve 'cabal list'
Lennart Kolmodin <[EMAIL PROTECTED]>**20080301202117
 Make the output of 'cabal list' prettier. 
 $ cabal list xmonad
  * xmonad
       Latest version available: 0.6
       Latest installed version: 0.6
       Homepage: http://xmonad.org
       Category: System
       Synopsis: A tiling window manager
       License:  BSD3
  * xmonad-contrib ...[snip]
 Very much like the gentoo tools eix and esearch.
 This targets part of ticket #235. It still does not show packages that are
 installed but not available.
] 
[Remove 'info' command, make --dry-run cover that feature
Duncan Coutts <[EMAIL PROTECTED]>**20080229140300
 In -v mode info produced a detailed tree explaining the dependency
 resolution. That feature has been moved into 'install --dry-run -v'.
] 
[Add --dry-run to upgrade, replacing existing info message
Duncan Coutts <[EMAIL PROTECTED]>**20080229110710
 Also adjust the default for --dry-run to be false rather than empty.
] 
[Implement --dry-run for 'cabal install'
Lennart Kolmodin <[EMAIL PROTECTED]>**20080228195034] 
[Revert to ordinary read/writeFile for the config file
Duncan Coutts <[EMAIL PROTECTED]>**20080228105914] 
[Take nub by package id when making a dep graph
Duncan Coutts <[EMAIL PROTECTED]>**20080227021706
 and give more detailed error messages for internal error conditions.
 Fixes a problem where installing a set of packages where several depended
 on the same package would give us a ResolvedDependency list containing
 multiple copies of that package. The DepGraph was expecting unique packages.
 Resolving package deps and generating install plans needs more thought
 and better specified invariants.
] 
[Read package descriptions from the index as UTF8
Duncan Coutts <[EMAIL PROTECTED]>**20080225133357] 
[Convert to using readTextFile as appropriate
Duncan Coutts <[EMAIL PROTECTED]>**20080224180038
 Added readBinaryFile for on use (uploading .tar.gz files)
 Remove readURI as it was not being used.
] 
[Depend on latest Cabal lib
Duncan Coutts <[EMAIL PROTECTED]>**20080223184326] 
[Print output as UTF8
Duncan Coutts <[EMAIL PROTECTED]>**20080223184130] 
[Handle unpacking failures slightly more gracefully
Duncan Coutts <[EMAIL PROTECTED]>**20080222002748
 And note problem #246 about unpacking tar files with links
] 
[Update for Package and various utils having moved modules
Duncan Coutts <[EMAIL PROTECTED]>**20080222235759
 Several of the general util functions in Hackage.Utils are now in the main
 Cabal lib in Distribution.Simple.Utils so we use those.
 The Package class moved into Distribution.Package.
 Use the packageId class function in more places.
] 
[Use exitFailure rather than exitWith (ExitFailure 1)
Duncan Coutts <[EMAIL PROTECTED]>**20080222000323
 and instead of exitWith ExitSuccess just return through main rather than
 throwing an exception
] 
[Make the qa check return an exit code reporting the status
Lennart Kolmodin <[EMAIL PROTECTED]>**20080221213201] 
[When a package seems ok, say so
Lennart Kolmodin <[EMAIL PROTECTED]>**20080221213126] 
[Fix typo
Lennart Kolmodin <[EMAIL PROTECTED]>**20080221213041] 
[Naive implementation of 'cabal check'
Lennart Kolmodin <[EMAIL PROTECTED]>**20080221204820
 A naive implementation of 'cabal check'.
 It will list the errors and warnings as implemented by Cabal, yielding them
 in groups of severity. Currently ignores verbosity levels, no additional
 arguments are understood. This addresses ticket #211.
] 
[Make the install code collect some detail on the reasons for package failure
Duncan Coutts <[EMAIL PROTECTED]>**20080221204922
 Then print out at the end why packages failed. This is a step closer to
 producing detailed build reports.
] 
[Make ResolvedPackage an instance of Package and PackageFixedDeps
Duncan Coutts <[EMAIL PROTECTED]>**20080221204756
 And use that to simplify the code slightly. Also add an assertion into
 removeFailed, that the first returned result is the failed package itself,
 since we'll rely on this in the install code.
] 
[Replace RepoIndex type with PackageIndex PkgInfo
Duncan Coutts <[EMAIL PROTECTED]>**20080220212848
 and adapt to the minor finalisePackageDescription change
] 
[Use a dependency graph rather than a list when installing packages
Duncan Coutts <[EMAIL PROTECTED]>**20080220110637
 This allows us to figure out what to do when installing a single package
 fails. Instead of just carrying on as if nothing had happened and then
 failing several other packages which depended on the one that failed
 initially we can cut those dependent packages out as soon as the first one
 fails and if there is anything left that did not depend on the failed
 package then we can try and carry on.
] 
[Update to Cabal lib api changes
Duncan Coutts <[EMAIL PROTECTED]>**20080215131142
 The InstalledPackageIndex replaces our Hackage.LocalIndex module
] 
[Use setupMessage for consistency in downloading message
Duncan Coutts <[EMAIL PROTECTED]>**20080213193346] 
[-Wall clean
Duncan Coutts <[EMAIL PROTECTED]>**20080213193325] 
[Bump version and required Cabal version
Duncan Coutts <[EMAIL PROTECTED]>**20080211012151
 Due to recent Cabal api changes
] 
[Fixed imports to correspond to the latest arrangement of Distribution.PackageDescription.
[EMAIL PROTECTED] 
[Rename ResolvedPackage to ResolvedDependency
Duncan Coutts <[EMAIL PROTECTED]>**20080120144754] 
[Make the configure command take the defaults from the config file
Duncan Coutts <[EMAIL PROTECTED]>**20080119170358
 Just like the install command has always done. This makes them consistent.
 So by default that means cabal configure uses --user --prefix=$HOME/.cabal
] 
[Note in the README than the unix package is not a dependency
Duncan Coutts <[EMAIL PROTECTED]>**20080119170254] 
[Fix a warning.
Duncan Coutts <[EMAIL PROTECTED]>**20080119170155
 All the other warnings are instances of ghc bug #1148.
] 
[Fix "cabal list" with no package specified
Duncan Coutts <[EMAIL PROTECTED]>**20080119155219] 
[Treat package names given on the command line case insenitively
Duncan Coutts <[EMAIL PROTECTED]>**20080118230004
 Implements feature request #167.
] 
[Add IndexUtils with functions to disambiguate packaage names
Duncan Coutts <[EMAIL PROTECTED]>**20080118225545
 To allow us to implement case-insensitivity in package names given on the
 command line. We lookup in the package index for packages with the same name
 case-insensitively. If there is no exact match exact case-sensitively and
 there are more than one packages matching case-insensitively then it aborts
 with a message listing the matches. This should not often happen since within
 any single HackageDB server, we can check that packages names are unique
 case-insensitively but it's possible to get ambiguities if cabal-install has
 been configured to use multiple repos.
] 
[Remove unused listInstalledPackages, replaced by LocalIndex.read
Duncan Coutts <[EMAIL PROTECTED]>**20080118221309] 
[Change Dependency module to use the LocalIndex ADT
Duncan Coutts <[EMAIL PROTECTED]>**20080118220703
 The whole Dependency module is pure now, no IO since it takes the indexes
 as arguments, rather than the many more args required to do the IO to load
 up the indexes. Much nicer. Also update all callers.
] 
[Update copyright and docs for RepoIndex
Duncan Coutts <[EMAIL PROTECTED]>**20080118220013
 Added my copyright as I've almost completely rewritten the module.
] 
[Add Hackage.LocalIndex module as an index of installed packages
Duncan Coutts <[EMAIL PROTECTED]>**20080118215953
 Very much like the RepoIndex module but only holds package ids at the moment
  rather that full InstalledPackageInfo records that we'd really prefer.
] 
[Rename Hackage.Index -> Hackage.RepoIndex
Duncan Coutts <[EMAIL PROTECTED]>**20080118215132
 In preperation to add Hackage.LocalIndex module
] 
[Trivial change to utils
Duncan Coutts <[EMAIL PROTECTED]>**20080118214236] 
[Disable a particularly slow invariant check
Duncan Coutts <[EMAIL PROTECTED]>**20080117200539] 
[Move package substring searching into the Index module and use it in List
Duncan Coutts <[EMAIL PROTECTED]>**20080117200439
 Not much faster but rather cleaner.
] 
[Make a proper RepoIndex ADT
Duncan Coutts <[EMAIL PROTECTED]>**20080117175854
 This represents the collection of packages from a remote repo.
 It encodes the policies on how we find packages when we have multiple repos.
 The policy is encoded in the repo merge operation and in the various kinds of
 lookup functions.
] 
[Add Utils module, tidy imports
Duncan Coutts <[EMAIL PROTECTED]>**20080117175709] 
[Split ParseUtils module out of Utils module
Duncan Coutts <[EMAIL PROTECTED]>**20080117173017] 
[Have command line args override saved config not the other way around
Duncan Coutts <[EMAIL PROTECTED]>**20080115200258
 Fixes setting the --prefix from the command line which was previously being
 ignored in favour of the default prefix from the config file.
] 
[Set the useragent string to be "cabal-install/$version"
Duncan Coutts <[EMAIL PROTECTED]>**20080115160347
 eg, currently it is "cabal-install/0.4.2"
] 
[Don't verbosely display the http conversation chatter by default
Duncan Coutts <[EMAIL PROTECTED]>**20080115160233
 Though do display it at deafening verbosity level.
] 
[Use proxy port number rather than ignoring it
Duncan Coutts <[EMAIL PROTECTED]>**20080115151033] 
[Refactor proxy handling yet again
Duncan Coutts <[EMAIL PROTECTED]>**20080115150933
 This time to better handle parsing and warning about invalid proxy uris
] 
[Remove unused var
Duncan Coutts <[EMAIL PROTECTED]>**20080115150838] 
[Use commandDefaultFlags = mempty rather than commandAddActionWithEmptyFlags
Duncan Coutts <[EMAIL PROTECTED]>**20080115150725
 Simpler and simplifies the Command api in the Cabal lib
] 
[Fix compilation on windows
Duncan Coutts <[EMAIL PROTECTED]>**20080114143456
 Silly #ifdefs making things harder to test.
] 
[After refactoring the http proxy code we don't need the unix package
Duncan Coutts <[EMAIL PROTECTED]>**20080114142301
 Which was just being used for an exception-free version of getEnv but we
 have to cope with exceptions anyway for the Win32 registry.
] 
[Set the user install flag when restoring saved config
Duncan Coutts <[EMAIL PROTECTED]>**20080114141313] 
[Allow finding the proxy to fail without failing overall
Duncan Coutts <[EMAIL PROTECTED]>**20080113201627
 On windows, if looking up the info in the registry failed then we failed
 overall. Now we just don't use the proxy. Also refactored a bit.
] 
[Fix getting verbosity flags
Duncan Coutts <[EMAIL PROTECTED]>**20080111025634] 
[Depend on latest development version of Cabal lib
Duncan Coutts <[EMAIL PROTECTED]>**20080110203711] 
[Remove redundant code an re-enable accidentally disabled code
Duncan Coutts <[EMAIL PROTECTED]>**20080110180137] 
[Significantly refactor configuration handling
Duncan Coutts <[EMAIL PROTECTED]>**20080110175634
 ConfigFlags is not used in any of the modules that do the real work, instead
 we just pass in the necessary information. Renamed ConfigFlags to SavedConfig
 and moved it's definition into the Config module. Also change what information
 is kept in the Repo type so that it knows the local path too. A PkgInfo now
 also knows which Repo it is from.
] 
[Added support for users behind proxy servers, reading system settings from the env var on unix or registry on windows
<[EMAIL PROTECTED]>**20071221201500] 
[Added upgrade command
[EMAIL PROTECTED]
 cabal upgrade installs the latest version of any currently installed
 package.
 
] 
[improved error handling for multiple installs
[EMAIL PROTECTED]
 When installing multiple packages, don't quit just after the first
 error, but rather collect the list of packages that failed to install
 continue installing whatever packages we can, and provide an error
 message at the end.
 
] 
[Initial attempt at command line completion
Lennart Kolmodin <[EMAIL PROTECTED]>**20071219215747] 
[Added dependency on random. Needed by Hackage.Upload.
[EMAIL PROTECTED] 
[Improve 'cabal info pkg' message when there is nothing to install
Duncan Coutts <[EMAIL PROTECTED]>**20071218004724
   "All requested packages already installed. Nothing to do."
 rather than:
   "These packages would be installed:\n"
 followed by ... nothing.
] 
[Make logging and verboisty a bit more consistent
Duncan Coutts <[EMAIL PROTECTED]>**20071218004604
 Use the Distribution.Simple.Utils functions and eliminate use of printf
] 
[Don't append '.' to filename in message. Make config file end in a new line.
Duncan Coutts <[EMAIL PROTECTED]>**20071217234934] 
[Get the saved hackage username and password from the config file
Duncan Coutts <[EMAIL PROTECTED]>**20071217234649
 rather than from the old ~/.cabal-upload/auth file.
 Now uses ~/.cabal/config with:
 hackage-username:
 hackage-password:
] 
[Add Bjorn Bringert to authors and copyright list
Duncan Coutts <[EMAIL PROTECTED]>**20071217224227
 Since much recent cabal-install work is his and he wrote cabal-upload which
 was just integrated.
] 
[Remove unnecessary use of a type alias
Duncan Coutts <[EMAIL PROTECTED]>**20071217223913] 
[Initial integration of upload feature
Duncan Coutts <[EMAIL PROTECTED]>**20071217223748
 It still uses it's own config file, but now uses the same command line stuff
] 
[Fix usage message, swap program and sub-command names
Duncan Coutts <[EMAIL PROTECTED]>**20071217223620] 
[Remove redundant parameters
Duncan Coutts <[EMAIL PROTECTED]>**20071217211141] 
[Add the cabal-setup commands: configure, build etc
Duncan Coutts <[EMAIL PROTECTED]>**20071217210621
 So we now have the complete set of commands in one tool.
 This uses the new Command infrastructure to do two way conversion between
 flags as strings and as a structured parsed form.
] 
[Add Upload module direct copy of cabal-upload
Duncan Coutts <[EMAIL PROTECTED]>**20071217205813] 
[Add a verbosity flag to the info list update and fetch commands
Duncan Coutts <[EMAIL PROTECTED]>**20071217190035] 
[Add command listing support
Duncan Coutts <[EMAIL PROTECTED]>**20071217185912
 first step to shell command line completion
] 
[installCommand only ever needs to use defaultProgramConfiguration
Duncan Coutts <[EMAIL PROTECTED]>**20071217185811
 So don't bother making it a parameter
] 
[Add in more global help text like that of Setup.hs
Duncan Coutts <[EMAIL PROTECTED]>**20071217185605] 
[Replace command line handling
Duncan Coutts <[EMAIL PROTECTED]>**20071215194603
 Use the new cabal command line handling infrastructure. Use proper flag types
 rather than strings. 
 Drop support for per-package command line flags as it was generally agreed to
 be confusing.
] 
[Read/write binary files using ByteString without .Char8 modules
Duncan Coutts <[EMAIL PROTECTED]>**20071022222115
 ByteString.Char8 treats files as text files, which are really different
 on windows. We were getting CRLF translation in Windows which was messing
 everything up, like saving & reading the index file.
 So now only use BS.Char8 where necessary.
] 
[Remove old non-existant copyright file from extra-source-files
Duncan Coutts <[EMAIL PROTECTED]>**20071021174954
 We only have one LICENCE file
] 
[TAG 0.4.0
Duncan Coutts <[EMAIL PROTECTED]>**20071021143856] 
Patch bundle hash:
99ac46fe2ac21d8c0aa4759cb8c490f47797a5a9
_______________________________________________
cabal-devel mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cabal-devel

Reply via email to