Thu Jan 17 23:36:10 CET 2008 Lennart Kolmodin <[EMAIL PROTECTED]>
* Implement QA for PackageDescription
Addresses #191 (QA) and #180 (QA for missing license).
This patch only adds a new exposed module, it's not yet used anywhere.
Fri Jan 18 00:04:23 CET 2008 Lennart Kolmodin <[EMAIL PROTECTED]>
* Fix haddock module doc for QA
Fri Jan 18 00:04:39 CET 2008 Lennart Kolmodin <[EMAIL PROTECTED]>
* Rename QA function for PackageDescription
Fri Jan 18 20:40:41 CET 2008 Lennart Kolmodin <[EMAIL PROTECTED]>
* Don't fail QA if no license file is set
Sun Jan 20 22:55:49 CET 2008 Lennart Kolmodin <[EMAIL PROTECTED]>
* Separate into two QA categories, and readjust levels
Much code written in a session with Duncan Coutts
Sun Jan 20 22:58:23 CET 2008 Lennart Kolmodin <[EMAIL PROTECTED]>
* Run QA when running sdist
Code written in a session with Duncan Coutts
New patches:
[Implement QA for PackageDescription
Lennart Kolmodin <[EMAIL PROTECTED]>**20080117223610
Addresses #191 (QA) and #180 (QA for missing license).
This patch only adds a new exposed module, it's not yet used anywhere.
] {
adddir ./Distribution/PackageDescription
hunk ./Cabal.cabal 51
+ Distribution.PackageDescription.QA,
addfile ./Distribution/PackageDescription/QA.hs
hunk ./Distribution/PackageDescription/QA.hs 1
+{-# OPTIONS -cpp #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module : Distribution.PackageDescription.QA
+-- Copyright : Isaac Jones 2003-2008
+--
+-- Maintainer : Isaac Jones <[EMAIL PROTECTED]>,
+-- Lennart Kolmodin <[EMAIL PROTECTED]>
+-- Stability : alpha
+-- Portability : portable
+--
+-- Quality Assurance for package descriptions.
+
+{- All rights reserved.
+
+Redistribution and use in source and binary forms, with or without
+modification, are permitted provided that the following conditions are
+met:
+
+ * Redistributions of source code must retain the above copyright
+ notice, this list of conditions and the following disclaimer.
+
+ * Redistributions in binary form must reproduce the above
+ copyright notice, this list of conditions and the following
+ disclaimer in the documentation and/or other materials provided
+ with the distribution.
+
+ * Neither the name of Isaac Jones nor the names of other
+ contributors may be used to endorse or promote products derived
+ from this software without specific prior written permission.
+
+THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
+A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
+OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
+SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
+LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
+DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
+THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
+(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
+OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}
+
+module Distribution.PackageDescription.QA (
+ -- * Quality Assurance
+ qualityAssurePackage
+ ) where
+
+import Control.Monad(when,unless)
+import Data.List(intersperse)
+import System.Directory(doesFileExist)
+
+import Distribution.Compiler(CompilerFlavor(..))
+import Distribution.PackageDescription
+
+-- ------------------------------------------------------------
+-- * Quality Assurance
+-- ------------------------------------------------------------
+
+-- |Quality Assurance for package descriptions.
+qualityAssurePackage :: PackageDescription -> IO [String]
+qualityAssurePackage pkg_descr = fmap fst . runQA $ do
+
+ flip mapM_ ghc_options $ \ flags -> do
+ let has_Wall = "-Wall" `elem` flags
+ has_Werr = "-Werror" `elem` flags
+ when (has_Wall && has_Werr) $
+ qa $ "Using both -Wall and -Werror makes the package easy to "
+ ++ "break with future GHC versions."
+
+ ghcWarn "-fasm" $
+ "flag -fasm is unnecessary and breaks on all "
+ ++ "arches except for x86, x86-64 and ppc."
+
+ ghcWarn "-O" $
+ "Cabal automatically add the -O flag and setting it yourself "
+ ++ "will disable the use of the --disable-optimization flag."
+
+ ghcWarn "-O2" $
+ "-O2 is rarely needed as it often prolong the compile time "
+ ++ "with usually with little benefit."
+
+ let ffi_msg = "Instead of using -ffi or -fffi, use extensions: ForeignFunctionInterface"
+
+ ghcWarn "-ffi" ffi_msg
+ ghcWarn "-fffi" ffi_msg
+
+ checkLicenseExists pkg_descr
+
+ -- TODO: keep an eye on #190 and implement when/if it's closed.
+ -- warn for ghc-options: -fvia-C when ForeignFunctionInterface is set
+ -- http://hackage.haskell.org/trac/hackage/ticket/190
+
+ where
+ ghc_options = [ strs | bi <- allBuildInfo pkg_descr
+ , (GHC, strs) <- options bi ]
+ all_ghc_options = concat ghc_options
+
+ ghcWarn :: String -> String -> QA ()
+ ghcWarn flag msg =
+ warnWhenFlag all_ghc_options flag ("ghc-options: " ++ msg)
+
+checkLicenseExists :: PackageDescription -> QA ()
+checkLicenseExists pkg = do
+ exists <- io $ doesFileExist file
+ unless exists $
+ qa $ "Cabal file refers to license file \"" ++ file
+ ++ "\" which does not exist."
+ where
+ file = licenseFile pkg
+
+warnWhenFlag :: [String] -> String -> String -> QA ()
+warnWhenFlag flags flag msg =
+ when (flag `elem` flags) (qa msg)
+
+-- the WriterT monad over IO
+data QA a = QA { runQA :: IO ([String], a) }
+
+instance Monad QA where
+ a >>= mb = QA $ do
+ (warnings, x) <- runQA a
+ (warnings', x') <- runQA (mb x)
+ return (warnings ++ warnings', x')
+ return x = QA $ return ([], x)
+
+qa :: String -> QA ()
+qa msg = QA $ return ([withLines pretty msg], ())
+ where
+ -- like (unlines . f . lines) except no trailing \n
+ withLines f = concat . intersperse "\n" . f . lines
+ pretty [] = []
+ pretty (x:xs) = ("QA: " ++ x) : map (" "++) xs
+
+io :: IO a -> QA a
+io action = QA $ do
+ x <- action
+ return ([], x)
hunk ./Makefile 76
+ -rm -f Distribution/PackageDescription/*.o Distribution/PackageDescription/*.hi
}
[Fix haddock module doc for QA
Lennart Kolmodin <[EMAIL PROTECTED]>**20080117230423] {
hunk ./Distribution/PackageDescription/QA.hs 5
--- Copyright : Isaac Jones 2003-2008
+-- Copyright : Lennart Kolmodin 2008
hunk ./Distribution/PackageDescription/QA.hs 7
--- Maintainer : Isaac Jones <[EMAIL PROTECTED]>,
--- Lennart Kolmodin <[EMAIL PROTECTED]>
+-- Maintainer : Lennart Kolmodin <[EMAIL PROTECTED]>
}
[Rename QA function for PackageDescription
Lennart Kolmodin <[EMAIL PROTECTED]>**20080117230439] {
hunk ./Distribution/PackageDescription/QA.hs 45
- qualityAssurePackage
+ qaCheckPackage
hunk ./Distribution/PackageDescription/QA.hs 60
-qualityAssurePackage :: PackageDescription -> IO [String]
-qualityAssurePackage pkg_descr = fmap fst . runQA $ do
+qaCheckPackage :: PackageDescription -> IO [String]
+qaCheckPackage pkg_descr = fmap fst . runQA $ do
}
[Don't fail QA if no license file is set
Lennart Kolmodin <[EMAIL PROTECTED]>**20080118194041] hunk ./Distribution/PackageDescription/QA.hs 103
-checkLicenseExists pkg = do
- exists <- io $ doesFileExist file
- unless exists $
- qa $ "Cabal file refers to license file \"" ++ file
- ++ "\" which does not exist."
+checkLicenseExists pkg =
+ unless (null file) $ do
+ exists <- io $ doesFileExist file
+ unless exists $
+ qa $ "Cabal file refers to license file \"" ++ file
+ ++ "\" which does not exist."
[Separate into two QA categories, and readjust levels
Lennart Kolmodin <[EMAIL PROTECTED]>**20080120215549
Much code written in a session with Duncan Coutts
] {
hunk ./Distribution/PackageDescription/QA.hs 12
+--
+-- This module provides functionality to check for common mistakes.
hunk ./Distribution/PackageDescription/QA.hs 47
- qaCheckPackage
+ qaCheckPackage,
+ QANotice(..)
hunk ./Distribution/PackageDescription/QA.hs 52
-import Data.List(intersperse)
hunk ./Distribution/PackageDescription/QA.hs 61
+-- TODO: give hints about old extentions. see Simple.GHC, reverse mapping
+-- TODO: and allmost ghc -X flags should be extensions
+-- TODO: Once we implement striping (ticket #88) we should also reject
+-- ghc-options: -optl-Wl,-s.
+-- TODO: check that either license or license-file is set
+
+data QANotice
+ = QAWarning { qaMessage :: String }
+ | QAFailure { qaMessage :: String }
+
+instance Show QANotice where
+ show notice = qaMessage notice
+
hunk ./Distribution/PackageDescription/QA.hs 75
-qaCheckPackage :: PackageDescription -> IO [String]
+qaCheckPackage :: PackageDescription -> IO [QANotice]
hunk ./Distribution/PackageDescription/QA.hs 77
+ ghcSpecific pkg_descr
+ cabalFormat pkg_descr
+
+ checkLicenseExists pkg_descr
hunk ./Distribution/PackageDescription/QA.hs 82
- flip mapM_ ghc_options $ \ flags -> do
- let has_Wall = "-Wall" `elem` flags
- has_Werr = "-Werror" `elem` flags
- when (has_Wall && has_Werr) $
- qa $ "Using both -Wall and -Werror makes the package easy to "
- ++ "break with future GHC versions."
+cabalFormat :: PackageDescription -> QA ()
+cabalFormat pkg_descr = do
+ when (null (category pkg_descr)) $
+ warn "No category field."
+ when (null (description pkg_descr)) $
+ warn "No description field."
+ when (null (maintainer pkg_descr)) $
+ warn "No maintainer field."
+ when (null (synopsis pkg_descr)) $
+ warn "No synopsis field."
+ when (length (synopsis pkg_descr) >= 80) $
+ warn "Over-long synopsis field"
hunk ./Distribution/PackageDescription/QA.hs 95
- ghcWarn "-fasm" $
+
+ghcSpecific :: PackageDescription -> QA ()
+ghcSpecific pkg_descr = do
+ let has_WerrorWall = flip any ghc_options $ \opts ->
+ "-Werror" `elem` opts
+ && ("-Wall" `elem` opts || "-W" `elem` opts)
+ has_Werror = any (\opts -> "-Werror" `elem` opts) ghc_options
+ when has_WerrorWall $
+ critical $ "ghc-options: -Wall -Werror makes the package "
+ ++ "very easy to break with future GHC versions."
+ when (not has_WerrorWall && has_Werror) $
+ warn $ "ghc-options: -Werror makes the package easy to "
+ ++ "break with future GHC versions."
+
+ ghcFail "-fasm" $
hunk ./Distribution/PackageDescription/QA.hs 113
- ghcWarn "-O" $
+ ghcFail "-O" $
hunk ./Distribution/PackageDescription/QA.hs 121
- let ffi_msg = "Instead of using -ffi or -fffi, use extensions: ForeignFunctionInterface"
-
- ghcWarn "-ffi" ffi_msg
- ghcWarn "-fffi" ffi_msg
-
- checkLicenseExists pkg_descr
+ -- most important at this stage to get the framework right
+ when (any (`elem` all_ghc_options) ["-ffi", "-fffi"]) $
+ critical $ "Instead of using -ffi or -fffi, use extensions: "
+ ++"ForeignFunctionInterface"
hunk ./Distribution/PackageDescription/QA.hs 135
+
hunk ./Distribution/PackageDescription/QA.hs 138
- warnWhenFlag all_ghc_options flag ("ghc-options: " ++ msg)
+ when (flag `elem` all_ghc_options) $
+ warn ("ghc-options: " ++ msg)
+
+ ghcFail :: String -> String -> QA ()
+ ghcFail flag msg =
+ when (flag `elem` all_ghc_options) $
+ critical ("ghc-options: " ++ msg)
+
hunk ./Distribution/PackageDescription/QA.hs 148
-checkLicenseExists pkg =
+checkLicenseExists PackageDescription { licenseFile = file } =
hunk ./Distribution/PackageDescription/QA.hs 152
- qa $ "Cabal file refers to license file \"" ++ file
- ++ "\" which does not exist."
- where
- file = licenseFile pkg
+ critical $ "license-file field refers to file \"" ++ file
+ ++ "\" which does not exist."
hunk ./Distribution/PackageDescription/QA.hs 155
-warnWhenFlag :: [String] -> String -> String -> QA ()
-warnWhenFlag flags flag msg =
- when (flag `elem` flags) (qa msg)
hunk ./Distribution/PackageDescription/QA.hs 157
-data QA a = QA { runQA :: IO ([String], a) }
+data QA a = QA { runQA :: IO ([QANotice], a) }
hunk ./Distribution/PackageDescription/QA.hs 166
-qa :: String -> QA ()
-qa msg = QA $ return ([withLines pretty msg], ())
- where
- -- like (unlines . f . lines) except no trailing \n
- withLines f = concat . intersperse "\n" . f . lines
- pretty [] = []
- pretty (x:xs) = ("QA: " ++ x) : map (" "++) xs
+qa :: QANotice -> QA ()
+qa notice = QA $ return ([notice], ())
+
+warn :: String -> QA ()
+warn = qa . QAWarning
+
+critical :: String -> QA ()
+critical = qa . QAFailure
}
[Run QA when running sdist
Lennart Kolmodin <[EMAIL PROTECTED]>**20080120215823
Code written in a session with Duncan Coutts
] {
hunk ./Distribution/Simple/SrcDist.hs 63
+import Distribution.PackageDescription.QA
hunk ./Distribution/Simple/SrcDist.hs 78
-import Control.Monad(when)
+import Control.Monad(when, unless)
hunk ./Distribution/Simple/SrcDist.hs 114
+
+ -- do some QA
+ qas <- qaCheckPackage pkg_descr
+ let qfail = [ s | QAFailure s <- qas ]
+ qwarn = [ s | QAWarning s <- qas ]
+ unless (null qfail) $ do
+ notice verbosity "QA errors:"
+ notice verbosity $ unlines qfail
+ unless (null qwarn) $ do
+ notice verbosity $ "QA warnings:"
+ notice verbosity $ unlines qwarn
+ unless (null qfail) $
+ notice verbosity "Notice that the public hackage server would reject this package due to QA issues."
+
}
Context:
[Remove some functions that were deprecated in the last stable series
Duncan Coutts <[EMAIL PROTECTED]>**20080120130012
So they should be safe to remove now.
]
[Inform users of max verbosity (fixes ticket 176)
[EMAIL PROTECTED]
[Ticket 176: Fix verbosity error to include the valid -v values
[EMAIL PROTECTED]
Fixed:
http://hackage.haskell.org/trac/hackage/ticket/176
]
[Ticket 201: report IO errors during clean
[EMAIL PROTECTED]
[Fix warnings in Cabal
Ian Lynagh <[EMAIL PROTECTED]>**20080118191230]
[Comment out an unused binding
Ian Lynagh <[EMAIL PROTECTED]>**20080116172204]
[Inform users of max verbosity (fixes ticket 176)
[EMAIL PROTECTED]
[Warn if a build-type is not specified. We want all packages to use this now.
Duncan Coutts <[EMAIL PROTECTED]>**20080111023917]
[We default configUserInstall to False so we should not set configPackageDB
Duncan Coutts <[EMAIL PROTECTED]>**20080111023733
because we use the value of configUserInstall to set the default value for
configPackageDB, and any value the user sets will override that.
]
[Bump minor version number due to more minor api and behaviour changes
Duncan Coutts <[EMAIL PROTECTED]>**20080110201117]
[Make --user --global change the default prefix
Duncan Coutts <[EMAIL PROTECTED]>**20080110193830
Previously --user and --global didn't mean what it looks like they mean,
instead of doing a per-user or a global installation they just meant to
register in the per-user or global package databases (and to allow
dependencies to be satisfied from the per-user or global db)
With this patch --user / --global means to do a per-user or global install
so in addition to the package db differences it also sets the default
installation prefix. This prefix can of course still be overridden using the
--prefix= flag. The global prefix is as before, the default per-user prefix
is $HOME/.cabal on Unix and on Windows it's something like:
C:/Documents And Settings/$user/Application Data/cabal
(using getAppUserDataDirectory "cabal"). This is the per-user prefix that
cabal-install currently uses. We can change it if people think it's not good.
]
[Un-deprecate configCompilerAux
Duncan Coutts <[EMAIL PROTECTED]>**20080110175148
but make it do something sensible with the ProgramConfiguration
]
[Export the Flag constructors
Duncan Coutts <[EMAIL PROTECTED]>**20080110175123]
[Allow symbol characters (e.g '+') in the components of a build-tool name
David Waern <[EMAIL PROTECTED]>**20080108211218]
[Set dynlibdir to $libdir per default.
Clemens Fruhwirth <[EMAIL PROTECTED]>**20071228183604]
[Use os(windows) not os(win32) in user guide configurations example
Duncan Coutts <[EMAIL PROTECTED]>**20071228125735
Spotted by Spencer Janssen
]
[Use getTemporaryDirectory from Distribution.Compat.Direcotry
Duncan Coutts <[EMAIL PROTECTED]>**20071228125530
for compatability with ghc-6.2.2
]
[Fix haddock parse error ($prefix -> \$prefix)
Clemens Fruhwirth <[EMAIL PROTECTED]>**20071227124051]
[Rejig --list-options handling so it takes priority
Duncan Coutts <[EMAIL PROTECTED]>**20071218191636
--list-options no takes priority over errors in other flags and over --help
this is so that it can be used consistently for command completion without
returning garbage (ie error messages on ill formed partial command lines
or producing --help output). Also make --list-options list all the common
options appart from itself, so that's just --help at the moment.
]
[Export flagToList for cabal-install to use
Duncan Coutts <[EMAIL PROTECTED]>**20071217185359]
[Support command completion in the Make module
Duncan Coutts <[EMAIL PROTECTED]>**20071217185328]
[Add correct^H^H^H^H British English spelling of optimisation
Duncan Coutts <[EMAIL PROTECTED]>**20071217133533
For the --enable/disable-optimi(z|s)ation flag, allow the British English
spelling of the flags as an alias. The current one is still the one
displayed, and it does not list bith in the --help text, though the command
completion would list both.
Perhaps the default should be on the basis of the current locale :-).
]
[Add --list-options flag, should be useful for shell command line completion
Duncan Coutts <[EMAIL PROTECTED]>**20071217132048
It applies at the top level in which case it lists the global flags and
the sub-commands. It applies for each sub-command in which case it lists
the sub-command's available flags.
]
[Make all command line flags and flag collection types monoids
Duncan Coutts <[EMAIL PROTECTED]>**20071215193650
And specify command flags in a way that allows converting from or two strings.
So not only can we parse command lines into the various flag types, we can
convert back. This is crucial in cabal-install so that we can call Setup.hs
scripts with all the various args, and override certain flags in a typed way
rather than just representing them all as strings.
]
[Export Command constructor so cabal-install can make derived commands
Duncan Coutts <[EMAIL PROTECTED]>**20071208192401
Also move commandHelp out of the structure into a helper function. Change
the type of commandOptions so it doesn't include the CommonFlag. Instead,
add those in whenever necessary. This makes deriving commands easier.
Also fix docs.
]
[Replace lots of configBlahDir fields with just one InstallDirs
Duncan Coutts <[EMAIL PROTECTED]>**20071208182620
So instead of 10 fields like this:
configPrefix :: Maybe FilePath,
...
we have just one compound one:
configInstallDirs :: InstallDirs (Maybe FilePath)
Now that LocalBuildInfo and cabal-install's config use InstallDirs it makes
converting a lot easier since we can use fmap and combineInstallDirs.
This should also be easier to maintain as it has significantly reduced the
number of places in the code you have to change when you add/change a dir.
]
[Merge InstallDirTemplates into InstallDirs
Duncan Coutts <[EMAIL PROTECTED]>**20071208182334
This simplifies things and makes it a bit more versatile since
we can use things like InstallDirs (Maybe PathTemplate).
]
[Bump version number as we've made api changes
Duncan Coutts <[EMAIL PROTECTED]>**20071215194028]
[Make fromPathTemplate not drop vars
Duncan Coutts <[EMAIL PROTECTED]>**20071215193943
It's useful to be able to convert String <-> PathTeplate without loosing info.
]
[Don't supress warnings, fix uncovered warnings
Duncan Coutts <[EMAIL PROTECTED]>**20071208191939]
[Move CopyDest from Setup to InstallDirs module
Duncan Coutts <[EMAIL PROTECTED]>**20071208170913
It's a better place to put it and it allows Setup to use InstallDirs later
]
[Add more to the user guide intro trying to explain the scope and use model
Duncan Coutts <[EMAIL PROTECTED]>**20071208161402]
[Fix haddock markup
Duncan Coutts <[EMAIL PROTECTED]>**20071207162314]
[Rename interfacedir to haddockdir
Duncan Coutts <[EMAIL PROTECTED]>**20071207142824
Since it really only refers to haddock interfaces, so interface is too
general a term. Cannot push to 1.2 branch as it changes the api.
]
[Add mandir support to InstallDirs
Duncan Coutts <[EMAIL PROTECTED]>**20071207141839
It's not used by Cabal at all but some packages want to install man pages
and this should make it easier for them to figure out where to install them.
In particular c2hs and lhs2tex have man pages.
]
[Fix hscolour code so it only outputs the css once per-lib or exe
Duncan Coutts <[EMAIL PROTECTED]>**20071207130309
Rather than for every module in the lib. Tidy the code up a little too.
]
[First go at supporting ghc-6.9's ghc-pkg list --simple-output
Duncan Coutts <[EMAIL PROTECTED]>**20071207123107
We used to have to parse the human readable output from ghc-pkg list because
previously it was not possible to specify which package dbs to query.
Now the behaviour is that you specify exactly which dbs you want and you
only get those packages listed. For example ghc-pkg list --global lists only
packages from the global db. So we now use:
ghc-pkg list --simple-output --global
ghc-pkg list --simple-output --global --user
]
[Note what form of string we get from invoking hmake --version
Duncan Coutts <[EMAIL PROTECTED]>**20071207122829]
[Add -framework arguments when linking executables.
[EMAIL PROTECTED]
[Support --hyperlink-source for Haddock >= 2.0
David Waern <[EMAIL PROTECTED]>**20071209180555]
[Use a default HsColour CSS if available
Duncan Coutts <[EMAIL PROTECTED]>**20071206145937
Supported in HsColour 1.9 and later
]
[export ccLdOptionsBuildInfo helper function
Duncan Coutts <[EMAIL PROTECTED]>**20071205194146
Useful in Setup.hs scripts for things like HSQL that need to
find CC and LD flags by calling foo-config style programs.
The same function is used internally for pkg-config support.
]
[make rawSystemStdout put its temp files in the temp dir rather than cwd
Duncan Coutts <[EMAIL PROTECTED]>**20071202220620
Should fixe reported wierdness with finding program version numbers
]
[The NHC module now uses cpp
Duncan Coutts <[EMAIL PROTECTED]>**20071129124745]
[Rename defaultMain__ to defaultMainHelper
Duncan Coutts <[EMAIL PROTECTED]>**20071121203604
It was a silly name.
]
[Bump development version number due to api change
Duncan Coutts <[EMAIL PROTECTED]>**20071120164121
Since we've changed the exports of the Setup module significantly.
However since this is a dev series I don't think it makes sense to
bump the major version number as in the PVP, or we'd end up doing
it all the time in a development series.
]
[Remove unused code in Setup module
Duncan Coutts <[EMAIL PROTECTED]>**20071120163922
This changes the API so cannot be pushed to the 1.2 branch.
]
[Use the new Command stuff for Distribution.Simple
Duncan Coutts <[EMAIL PROTECTED]>**20071120161816]
[Use the new Command stuff for Distribution.Make
Duncan Coutts <[EMAIL PROTECTED]>**20071120161605]
[Stop using deprecated setup code in SetupWrapper
Duncan Coutts <[EMAIL PROTECTED]>**20071120161435]
[Add Command module to exposed-modules
Duncan Coutts <[EMAIL PROTECTED]>**20071116145234]
[Add new Command abstraction for handling command line args
Duncan Coutts <[EMAIL PROTECTED]>**20071116141225
Add instances of it for all existing Cabal commands.
This should makes command line handling more regular and hopefully make it
easier to override or make derived commands in cabal-install.
So far we're only adding code, not modifying existing stuff except renaming
some existing internal functions so they do not clash with the new code.
]
[Add emptyPFEFlags and emptySDistFlags for consistency
Duncan Coutts <[EMAIL PROTECTED]>**20071116135625]
[Simplify parameters to defaultMain__
Duncan Coutts <[EMAIL PROTECTED]>**20071116132323
Don't use maybe, just have the callers pass the defaults instead.
Eliminate the Maybe PackageDescription parameter and instead just have
the called override the readDesc in the UserHooks.
This simplifies defaultMainWorker too as it can always just use readDesc.
]
[Make scratchdir into a proper configure flag
Duncan Coutts <[EMAIL PROTECTED]>**20071116131604
rather than using the flag extension mechanism.
It was the old flag using it and I'm about to replace that whole system.
]
[Refactor: move UserHooks into it's own module
Duncan Coutts <[EMAIL PROTECTED]>**20071114150659]
[Tidy up args in the pfe, clean, haddock and hscolour default hooks
Duncan Coutts <[EMAIL PROTECTED]>**20071114150131
Don't pass unnecessary args and inline trivial definitions
]
[Partial implementation of installing for nhc98
Duncan Coutts <[EMAIL PROTECTED]>**20071127174132
Doesn't install into the right place by default yet.
]
[Library archive creation for nhc98
Duncan Coutts <[EMAIL PROTECTED]>**20071127174017
So far only for vanilla not profiling libs.
]
[Escape some special characters
Ian Lynagh <[EMAIL PROTECTED]>**20071126163253]
[Fix a broken link
Ian Lynagh <[EMAIL PROTECTED]>**20071126163137]
[Escape some special characters in the haddock docs
Ian Lynagh <[EMAIL PROTECTED]>**20071126155145]
[Fix what looks like a doc braino
Ian Lynagh <[EMAIL PROTECTED]>**20071126154824]
[Put nhc98 .hi files in the target dir rather than the src dir
Duncan Coutts <[EMAIL PROTECTED]>**20071127003800
So they end up next to the .o files under dist/ just like for ghc.
]
[Workaround import bug in nhc98
Duncan Coutts <[EMAIL PROTECTED]>**20071123210009
Cabal can now build using itself and nhc98
]
[Add support for building libs and exes with nhc98 via hmake
Duncan Coutts <[EMAIL PROTECTED]>**20071123205750
Doesn't do installation yet or check for existence of dependent packages.
]
[FIX BUILD with GHC 6.2: getTemporaryDirectory wasn't available
Simon Marlow <[EMAIL PROTECTED]>**20071123093121]
[Do proper pre-processing for Haddock 2
David Waern <[EMAIL PROTECTED]>**20071109162557
Besides pre-processing, this patch adds include paths and output paths
to the ghc flags passed to Hadddock.
]
[Import changelog changes from the 1.2 branch
Duncan Coutts <[EMAIL PROTECTED]>**20071116145738]
[Export PreProcessor constructor and mkSimplePreProcessor
Duncan Coutts <[EMAIL PROTECTED]>**20071116145327
Otherwise it is impossible to declare new pre-processors in Setup.hs files
]
[Fix finding ghc's ld.exe on windows.
Duncan Coutts <[EMAIL PROTECTED]>**20071120101110
It looks like it had worked but the ld -x test broke that too. Grr.
]
[Fix configure --interfacedir=
Duncan Coutts <[EMAIL PROTECTED]>**20071114191550
bug #178
]
[Fix haddock interface file location used when registering inplace packages
Ian Lynagh <[EMAIL PROTECTED]>**20071110171424
This fixes inter-package doc links when building GHC.
]
[Add extensions that ghc-6.6 supports
Duncan Coutts <[EMAIL PROTECTED]>**20071109142250]
[The extension is NoMonoPatBinds not MonoPatBinds
Duncan Coutts <[EMAIL PROTECTED]>**20071109142217]
[Add language extensions introduced in GHC 6.8
Duncan Coutts <[EMAIL PROTECTED]>**20071108185612]
[Make the ld -x test use the temp dir rather than dist dir
Duncan Coutts <[EMAIL PROTECTED]>**20071108141349
Should fix cabal-install.
]
[fix compilation with GHC 6.2.x
Simon Marlow <[EMAIL PROTECTED]>**20071105113004]
[Install the haddock interface file to the right place
Ian Lynagh <[EMAIL PROTECTED]>**20071030170254]
[Add an interfacedir configure flag, for where to put haddock insterface files
Ian Lynagh <[EMAIL PROTECTED]>**20071029174908]
[put the binary-dist copy in the right place
Simon Marlow <[EMAIL PROTECTED]>**20071026132515]
[fix $(TOP)
Simon Marlow <[EMAIL PROTECTED]>**20071026101915]
[fix XML (at least, makes it work here)
Simon Marlow <[EMAIL PROTECTED]>**20071026101907]
[no longer need to pass --allow-missing-html to haddock
Ross Paterson <[EMAIL PROTECTED]>**20071026084124
This option only affects Haddock if it is invoked with --use-package,
and Cabal no longer uses that option, as it now gets the arguments for
--read-interface from ghc-pkg directly (cf patch "rejig location of
package interfaces for haddock").
]
[no longer need to pass --ghc-pkg to haddock
Ross Paterson <[EMAIL PROTECTED]>**20071026073126
Haddock only runs ghc-pkg if invoked with --use-package, and Cabal no
longer uses that option, as it now gets the arguments for --read-interface
from ghc-pkg directly (cf patch "rejig location of package interfaces
for haddock").
]
[fix help text (--PROG-arg is now --PROG-option)
Ross Paterson <[EMAIL PROTECTED]>**20071026001045]
[Fix a bug in the Unlit pre-processor
David Waern <[EMAIL PROTECTED]>**20071024181908
With this patch, unlit can handle line pragmas with filenames that contain
spaces.
]
[Adjust verbosity of a step in configure
Duncan Coutts <[EMAIL PROTECTED]>**20071024160758]
[Compile a .c rather than a .hs file to make a .o file in ld -x configure test
Duncan Coutts <[EMAIL PROTECTED]>**20071024150505
Since when bootstrapping ghc we're not in any position to compile .hs files
that easily.
]
[Create the dist/ dir early in the configuration process
Duncan Coutts <[EMAIL PROTECTED]>**20071024133554]
[Create temp files in dist, since it is now guaranteed to exist
Duncan Coutts <[EMAIL PROTECTED]>**20071024102850]
[Regenerate GHC/Makefile.hs from GHC/Makefile.in
Duncan Coutts <[EMAIL PROTECTED]>**20071023183804]
[Only use ld -x on systems where ld supports that.
Duncan Coutts <[EMAIL PROTECTED]>**20071023183738
Hopefully this fixes it for both ordinary builds and via ghc makefiles.
]
[pass cpp-options to cpphs
Ross Paterson <[EMAIL PROTECTED]>**20071023184210]
[Refuse to run any commands if the .cabal has been modified
Simon Marlow <[EMAIL PROTECTED]>**20071023093111
See GHC bug #1372
This is a consistency check, intended to prevent this class of build
failures:
* Package P is updated, its version number is bumped, the
new version is compiled and installed.
* Package Q depends on P. Q is modified to use the new P, and Q's
.cabal file is updated with changes to the build-depends field to
depend on the new version of P.
* The user has an old build of Q. They pull the changes to Q and
'setup build' without cleaning or re-configuring. Build errors
ensue, because the code of Q depends on changes to P's API, and
we're still building against the old P.
Note that you can't get segfaults this way, only build errors.
This also relies on some new consistency checking in GHC 6.8 to work
properly. If the user re-configures their Q build and then issues
'setup build' without cleaning, GHC must now realise that the package
flags have changed, and re-compile all the affected Q modules. GHC
6.6 would not do this, but 6.8 does.
]
[Add support for Haddock 2.0
David Waern <[EMAIL PROTECTED]>**20071021231415]
[Be explicit about the base version dependency
Duncan Coutts <[EMAIL PROTECTED]>**20071023122417
don't just leave it up to the default search order
]
[typo in comment
Ross Paterson <[EMAIL PROTECTED]>**20071022091235]
[Correct the spelling of mingw32 in os alias list
Duncan Coutts <[EMAIL PROTECTED]>**20071018195641
Doh!
]
[refinement of fix for #1785: don't use xargs' -s option at all
Simon Marlow <[EMAIL PROTECTED]>**20071019124522]
[FIX GHC bug #1785: use 2048 as the maximum command-line size
Simon Marlow <[EMAIL PROTECTED]>**20071018140500
Apparently Solaris sets a limit of 2048 here
]
[don't fail if xxx_hsc_make.c is gone
Ross Paterson <[EMAIL PROTECTED]>**20071018164245
The non-GHC hsc2hs deletes it even if the compilation fails.
]
[Use cpp-options rather than abusing ghc-options
Duncan Coutts <[EMAIL PROTECTED]>**20071017164914]
[Add a "cpp-options:" field and use it for pre-processing .hs .hsc .chs files
Duncan Coutts <[EMAIL PROTECTED]>**20071017164747
This is for pre-processing Haskell modules, not for C code. We already have
cc-options for that purpose. Up 'til now people have been abusing ghc-options
for this purpose. Even Cabal itself was guilty of doing that.
]
[Figure out if hsc2hs is using gcc or ghc as it's C compiler
Duncan Coutts <[EMAIL PROTECTED]>**20071017143108
and pass the appropriate flags on the basis of knowing that.
This is a hack.
What we should do longer term is make hsc2hs always use gcc as it's C compiler
and have Cabal figure out the right flags to pass it, rather than using ghc
to pass on the appropriate flags to gcc.
]
[Change the handling of cpp & ghc flags for hsc2hs
Duncan Coutts <[EMAIL PROTECTED]>**20071016231652
The hsc2hs that comes with ghc uses ghc as the C compiler. This means we must
escape the real cc flags. It also means we can ask ghc to add extra include
dirs that we might need to find includes of dependent packages. This is a bit
of a hack. In the longer term it'd be better for Cabal to collect the include
dirs and cc options of dependent packages and to pass them explicitly itself.
]
[Improve error messages for failed sanity checks.
Thomas Schilling <[EMAIL PROTECTED]>**20070925144955]
[Translate flat files into sectionized files, by duplicating global
Thomas Schilling <[EMAIL PROTECTED]>**20070925144921
dependecies into each non-empty section. The previous solution dumped
them into the library section, even if it would have been empty
otherwise.
]
[Move ghcVerbosity function into GHC module to share code
Duncan Coutts <[EMAIL PROTECTED]>**20071014165730]
[Note current development version number in release notes
Duncan Coutts <[EMAIL PROTECTED]>**20071012121835]
[Update the TODO list, mostly removing things.
Duncan Coutts <[EMAIL PROTECTED]>**20071012121702
Most of these are duplicated by Trac bugs.
We should try and get rid of this TODO file completely and just use Trac.
]
[Add logging functions notice, info, debug functions and use them consistently
Duncan Coutts <[EMAIL PROTECTED]>**20071012113237
We previously had this kind of code all over the place:
> when (verbosity >= verbose)
> (putStrLn "some message")
We now replace that with:
> info verbosity "some message"
Much nicer.
]
[When parsing ghc-pkg output, only look at the first package.conf file for GlobalPackageDB and SpecificPackageDB, and all package.conf files for UserPackageDB.
[EMAIL PROTECTED]
Before, we would consider user packages when fulfilling dependencies
for global installs. ghc-pkg will refuse to install packages globally if they
use user packages. Thus, without this patch, global installs can fail when you have user packages installed.
]
[Pass -c (silent create) to ar when verbosity < normal.
[EMAIL PROTECTED]
[Change --verbosity= option of SetupWrapper (cabal-setup) to --verbose=, since that is what the rest of Cabal uses.
[EMAIL PROTECTED]
[Pass -w -v0 to ghc when compiling Setup.{lhs,hs} in SetupWrapper when verbosity == silent.
[EMAIL PROTECTED]
[Update documentation on configurations
Duncan Coutts <[EMAIL PROTECTED]>**20071012015338
Describe the new syntax and make variuous changes to the
description of the meaning.
]
[Use -O2 for compiling .c files when we configure --enable-optimization
Duncan Coutts <[EMAIL PROTECTED]>**20071011223607
Seems a reasonable default behaviour.
]
[parameterise InstalledPackageInfo over the type of module names
Simon Marlow <[EMAIL PROTECTED]>**20071003114947
This is useful in GHC, we can instantiate InstalledPackageInfo to
ModuleName and avoid lots of String<->FastString conversions.
]
[Remove commented-out code.
[EMAIL PROTECTED]
Push to 1.2.
]
[Rename parseDescription to parsePackageDescription.
[EMAIL PROTECTED]
This should be pushed to cabal-1.2 to make cabal-install work with 1.2.
]
[Bump version number to 1.3
[EMAIL PROTECTED]
[Expose parseDescription.
[EMAIL PROTECTED]
[Fix GenericPrackageDescription pretty printing to make it parsable. It still does not include all information.
[EMAIL PROTECTED]
[Haddock comment for the available dependencies argument to finalizePackageDescription.
[EMAIL PROTECTED]
[Add extra-libs to shared library linking
Clemens Fruhwirth <[EMAIL PROTECTED]>**20070927123923]
[Actually -stubdir only works well in ghc-6.8 due to -I search dir mess
Duncan Coutts <[EMAIL PROTECTED]>**20070926131843
In ghc-6.6 the Foo/Bar.hc files only #include "Bar_stub.h" rather than
#include "Foo/Bar_stub.h". This means when we set the stubdir so that the
_stub.h files don't sit next to the .hs file then the include search path
is not right to find the _stub.h file. In ghc-6.8 this is fixed so that
it adds the -stubdir path to the include search path when calling gcc.
]
[The -stubdir flag is supported in ghc-6.6 not just 6.6.1
Duncan Coutts <[EMAIL PROTECTED]>**20070926114223]
[Add -package-name to GHC invocation when linking DSOs
Clemens Fruhwirth <[EMAIL PROTECTED]>**20070926090025]
[Be more fuzzy with os, arch and impl matching in conditions. Fixes bug #158.
Duncan Coutts <[EMAIL PROTECTED]>**20070925132608
Do all the comparisons case insensitively and add some OS aliases so that
if os(windows) works if the System.Info.os is actually "mingw32".
]
[Don't generate links when dependent docs not installed. Fixes bug #157.
Duncan Coutts <[EMAIL PROTECTED]>**20070924142520
Generates a warning rather than failing as before.
]
[Fix warnings
Ian Lynagh <[EMAIL PROTECTED]>**20070923122921]
[Fix pre-processing for executables
Duncan Coutts <[EMAIL PROTECTED]>**20070922105414
The pre-processed files should go into the exe's build dir, not the
lib's build dir. Also pre-process main modules, fixing bug #14.
]
[Add a boring file
Ian Lynagh <[EMAIL PROTECTED]>**20070913203550]
[Remove some now-unecessary cleaning that causes problems for haskell-src
Ian Lynagh <[EMAIL PROTECTED]>**20070920203257
The code that removes .hs files in the source tree generated from .y files
had a comment:
XXX: This is actually no longer necessary, but we keep it, so that
clean works correctly on packages built with an older version of Cabal
This was causing problems for source distributions that include such
generated files (including haskell-src in extralibs).
]
[Move expensive conviguration actions inside branch where they're used
Duncan Coutts <[EMAIL PROTECTED]>**20070917085834
We only need to configure the compiler and resolve any "Cabal-Version:"
dependency when we're actually going to compile the Setup.hs program.
We can otherwise save time by not calling ghc and ghc-pkg unnecessarily.
(I only noticed this because I've got >150 registered packages which
causes ghc and ghc-pkg to be very slow to start.)
]
[Note in .cabal file that we're using a custom build-type
Duncan Coutts <[EMAIL PROTECTED]>**20070917033959]
[Pass on all the cabal-setup options to cabal, not just unrecognised ones
Duncan Coutts <[EMAIL PROTECTED]>**20070917025121
So for example -v and -w get passed on rather than swallowed by cabal-setup
itself.
]
[Put setup program and setup .o/.hi files into dist/setup
Duncan Coutts <[EMAIL PROTECTED]>**20070917024907
That way they get cleaned automatically and do not clutter the top dir.
]
[Correct the verbosity range in the "--help" text
Duncan Coutts <[EMAIL PROTECTED]>**20070917024416
The correct range in 0--3, not 0--2 or 0--5
]
[look in odir for source and .hs files, not buildDir lbi
Duncan Coutts <[EMAIL PROTECTED]>**20070917145030
odir = buildDir lbi for the lib case, which is why it worked most of the time
in testing but in the exe case it's a different dir.
]
[Put _stub.{c|h} files under dist/ so they'll get cleaned. Fixes bug #154.
Duncan Coutts <[EMAIL PROTECTED]>**20070917123042
Only used with ghc-6.6 and later which supports the -stubdir flag.
With earlier ghc versions the files still end up in the src dirs and so do not
get cleaned.
]
[Fix haddockDir
Ian Lynagh <[EMAIL PROTECTED]>**20070912133051]
[Add htmlDirTemplate to inplaceDirs
Ian Lynagh <[EMAIL PROTECTED]>**20070912125749]
[Add a --htmldir flag
Ian Lynagh <[EMAIL PROTECTED]>**20070912122145]
[Don't forcibly append "pkgName (package pkg_descr)" to htmldir
Ian Lynagh <[EMAIL PROTECTED]>**20070911192814]
[TAG 2007-09-06
Ian Lynagh <[EMAIL PROTECTED]>**20070906212150]
[use OPTIONS instead of OPTIONS_GHC for now, the latter doesn't work with GHC 6.2.x
Simon Marlow <[EMAIL PROTECTED]>**20070912105243]
[Don't create empty data dirs. Fixes bug #153.
Duncan Coutts <[EMAIL PROTECTED]>**20070912113803
Patch contributed by Sven Panne.
]
[Use confgurations to help build Cabal for ghc-6.2.x
Duncan Coutts <[EMAIL PROTECTED]>**20070912112934
Replacing a long-standing comment telling people how to do it manually.
]
[warning police
Simon Marlow <[EMAIL PROTECTED]>**20070907140731]
[Update D.S.GHC/Makefile.hs
Clemens Fruhwirth <[EMAIL PROTECTED]>**20070906213507]
[Add shared library building to GHC module (also via Makefile)
Clemens Fruhwirth <[EMAIL PROTECTED]>**20070906213132]
[fix type clash: Data.Version -> Distribution.Version
[EMAIL PROTECTED]
[fix broken #ifdefs for nhc98
[EMAIL PROTECTED]
[spell nhc98-options correctly
[EMAIL PROTECTED]
[Fix various mispellings of nhc98.
[EMAIL PROTECTED]
[nhc-options should be spelled nhc98-options
[EMAIL PROTECTED]
[TAG 1.2.0
Duncan Coutts <[EMAIL PROTECTED]>**20070906121830]
Patch bundle hash:
3ec15ceb8c120b182136c8ccf27a591ab836d9c8
_______________________________________________
cabal-devel mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cabal-devel