1 patch for repository http://darcs.haskell.org/packages/Cabal:

Tue Oct 26 00:26:24 BST 2010  Ian Lynagh <ig...@earth.li>
  * Split known-extensions off into their own type, and remove knownExtensions
  The knownExtensions list had already got out of sync with the datatype.
  Now we use an Enum instance to get the list of constructors.
  Also, having the actual extensions in a separate type than UnknownExtension
  and EnableExtension makes it easier to add extension disabling support
  later.
New patches:

[Split known-extensions off into their own type, and remove knownExtensions
Ian Lynagh <ig...@earth.li>**20101025232624
 The knownExtensions list had already got out of sync with the datatype.
 Now we use an Enum instance to get the list of constructors.
 Also, having the actual extensions in a separate type than UnknownExtension
 and EnableExtension makes it easier to add extension disabling support
 later.
] {
hunk ./Distribution/PackageDescription/Check.hs 104
 
 import qualified Language.Haskell.Extension as Extension (deprecatedExtensions)
 import Language.Haskell.Extension
-         ( Language(UnknownLanguage), knownLanguages, Extension(..) )
+         ( Language(UnknownLanguage), knownLanguages, Extension(..), KnownExtension(..) )
 import System.FilePath
          ( (</>), takeExtension, isRelative, isAbsolute
          , splitDirectories,  splitPath )
hunk ./Distribution/PackageDescription/Check.hs 426
     deprecatedExtensions = nub $ catMaybes
       [ find ((==ext) . fst) Extension.deprecatedExtensions
       | bi <- allBuildInfo pkg
-      , ext <- allExtensions bi ]
+      , EnableExtension ext <- allExtensions bi ]
     languagesUsedAsExtensions =
       [ name | bi <- allBuildInfo pkg
              , UnknownExtension name <- allExtensions bi
hunk ./Distribution/PackageDescription/Check.hs 1028
                      , PublicDomain, AllRightsReserved, OtherLicense ]
 
     mentionedExtensions = [ ext | bi <- allBuildInfo pkg
-                                , ext <- allExtensions bi ]
+                                , EnableExtension ext <- allExtensions bi ]
     mentionedExtensionsThatNeedCabal12 =
       nub (filter (`elem` compatExtensionsExtra) mentionedExtensions)
 
hunk ./Distribution/Simple/GHC.hs 117
 import Distribution.Verbosity
 import Distribution.Text
          ( display, simpleParse )
-import Language.Haskell.Extension (Language(..), Extension(..))
+import Language.Haskell.Extension (Language(..), Extension(..), KnownExtension(..))
 
 import Control.Monad            ( unless, when )
 import Data.Char                ( isSpace )
hunk ./Distribution/Simple/GHC.hs 311
           ++ [ (ext, "-X" ++ display ext)
              | Just ext <- map readExtension (lines exts) ]
 
-  | otherwise = return oldLanguageExtensions
+  | otherwise = return [ (EnableExtension ke, flag)
+                       | (ke, flag) <- oldLanguageExtensions ]
 
   where
     Just ghcVersion = programVersion ghcProg
hunk ./Distribution/Simple/GHC.hs 321
     -- NamedFieldPuns. We now encourage packages to use NamedFieldPuns so for
     -- compatability we fake support for it in ghc-6.8 by making it an alias
     -- for the old RecordPuns extension.
-    extensionHacks = [ (NamedFieldPuns, "-XRecordPuns")
+    extensionHacks = [ (EnableExtension NamedFieldPuns, "-XRecordPuns")
                      | ghcVersion >= Version [6,8]  []
                     && ghcVersion <  Version [6,10] [] ]
 
hunk ./Distribution/Simple/GHC.hs 326
 -- | For GHC 6.6.x and earlier, the mapping from supported extensions to flags
-oldLanguageExtensions :: [(Extension, Flag)]
+oldLanguageExtensions :: [(KnownExtension, Flag)]
 oldLanguageExtensions =
     [(OverlappingInstances       , "-fallow-overlapping-instances")
     ,(TypeSynonymInstances       , "-fglasgow-exts")
hunk ./Distribution/Simple/GHC.hs 509
              comp (withProfLib lbi) (libBuildInfo lib)
 
   let libTargetDir = pref
-      forceVanillaLib = TemplateHaskell `elem` allExtensions libBi
+      forceVanillaLib = EnableExtension TemplateHaskell `elem` allExtensions libBi
       -- TH always needs vanilla libs, even when building for profiling
 
   createDirectoryIfMissingVerbose verbosity True libTargetDir
hunk ./Distribution/Simple/GHC.hs 707
   -- with profiling. This is because the code that TH needs to
   -- run at compile time needs to be the vanilla ABI so it can
   -- be loaded up and run by the compiler.
-  when (withProfExe lbi && TemplateHaskell `elem` allExtensions exeBi)
+  when (withProfExe lbi && EnableExtension TemplateHaskell `elem` allExtensions exeBi)
      (runGhcProg (binArgs False False))
 
   runGhcProg (binArgs True (withProfExe lbi))
hunk ./Distribution/Simple/Haddock.hs 259
                      removeFile targetFile
 
                  return hsFile
-            needsCpp = CPP `elem` allExtensions bi
+            needsCpp = EnableExtension CPP `elem` allExtensions bi
             defines | isVersion2 = []
                     | otherwise  = ["-D__HADDOCK__"]
 
hunk ./Distribution/Simple/Hugs.hs 98
          , rawSystemStdInOut
          , die, info, notice )
 import Language.Haskell.Extension
-         ( Language(Haskell98), Extension(..) )
+         ( Language(Haskell98), Extension(..), KnownExtension(..) )
 import System.FilePath          ( (</>), takeExtension, (<.>),
                                   searchPathSeparator, normalise, takeDirectory )
 import Distribution.System
hunk ./Distribution/Simple/Hugs.hs 139
   let comp = Compiler {
         compilerId             = CompilerId Hugs version,
         compilerLanguages      = hugsLanguages,
-        compilerExtensions     = hugsLanguageExtensions
+        compilerExtensions  =  [ (EnableExtension ke, flag)
+                               | (ke, flag) <- hugsLanguageExtensions ]
       }
   return (comp, conf'')
 
hunk ./Distribution/Simple/Hugs.hs 178
 hugsLanguages = [(Haskell98, "")] --default is 98 mode
 
 -- | The flags for the supported extensions
-hugsLanguageExtensions :: [(Extension, Flag)]
+hugsLanguageExtensions :: [(KnownExtension, Flag)]
 hugsLanguageExtensions =
     [(OverlappingInstances       , "+o")
     ,(IncoherentInstances        , "+oO")
hunk ./Distribution/Simple/Hugs.hs 341
     srcMainFile <- findFile (hsSourceDirs bi) mainPath
     let exeDir = destDir </> exeName exe
     let destMainFile = exeDir </> hugsMainFilename exe
-    copyModule verbosity (CPP `elem` allExtensions bi) bi lbi srcMainFile destMainFile
+    copyModule verbosity (EnableExtension CPP `elem` allExtensions bi) bi lbi srcMainFile destMainFile
     let destPathsFile = exeDir </> paths_modulename
     copyFileVerbose verbosity (autogenModulesDir lbi </> paths_modulename)
                               destPathsFile
hunk ./Distribution/Simple/Hugs.hs 363
 --TODO: should not be using mLibSrcDirs at all
 compileBuildInfo verbosity destDir mLibSrcDirs mods bi lbi = do
     -- Pass 1: copy or cpp files from build directory to scratch directory
-    let useCpp = CPP `elem` allExtensions bi
+    let useCpp = EnableExtension CPP `elem` allExtensions bi
     let srcDir = buildDir lbi
         srcDirs = nub $ srcDir : hsSourceDirs bi ++ mLibSrcDirs
     info verbosity $ "Source directories: " ++ show srcDirs
hunk ./Distribution/Simple/Hugs.hs 391
     createDirectoryIfMissingVerbose verbosity True (takeDirectory destFile)
     (exts, opts, _) <- getOptionsFromSource srcFile
     let ghcOpts = [ op | (GHC, ops) <- opts, op <- ops ]
-    if cppAll || CPP `elem` exts || "-cpp" `elem` ghcOpts then do
+    if cppAll || EnableExtension CPP `elem` exts || "-cpp" `elem` ghcOpts then do
         runSimplePreProcessor (ppCpp bi lbi) srcFile destFile verbosity
         return ()
       else
hunk ./Distribution/Simple/JHC.hs 67
          ( CompilerFlavor(..), CompilerId(..), Compiler(..)
          , PackageDBStack, Flag, languageToFlags, extensionsToFlags )
 import Language.Haskell.Extension
-         ( Language(Haskell98), Extension(..))
+         ( Language(Haskell98), Extension(..), KnownExtension(..))
 import Distribution.Simple.Program
          ( ConfiguredProgram(..), jhcProgram, ProgramConfiguration
          , userMaybeSpecifyPath, requireProgramVersion, lookupProgram
hunk ./Distribution/Simple/JHC.hs 108
       comp = Compiler {
         compilerId             = CompilerId JHC version,
         compilerLanguages      = jhcLanguages,
-        compilerExtensions     = jhcLanguageExtensions
+        compilerExtensions     = [ (EnableExtension ke, flag)
+                                 | (ke, flag) <- jhcLanguageExtensions ]
       }
   return (comp, conf')
 
hunk ./Distribution/Simple/JHC.hs 117
 jhcLanguages = [(Haskell98, "")]
 
 -- | The flags for the supported extensions
-jhcLanguageExtensions :: [(Extension, Flag)]
+jhcLanguageExtensions :: [(KnownExtension, Flag)]
 jhcLanguageExtensions =
     [(TypeSynonymInstances       , "")
     ,(ForeignFunctionInterface   , "")
hunk ./Distribution/Simple/LHC.hs 113
 import Distribution.Text
          ( display, simpleParse )
 import Language.Haskell.Extension
-         ( Language(Haskell98), Extension(..) )
+         ( Language(Haskell98), Extension(..), KnownExtension(..) )
 
 import Control.Monad            ( unless, when )
 import Data.List
hunk ./Distribution/Simple/LHC.hs 339
              (compiler lbi) (withProfLib lbi) (libBuildInfo lib)
 
   let libTargetDir = pref
-      forceVanillaLib = TemplateHaskell `elem` allExtensions libBi
+      forceVanillaLib = EnableExtension TemplateHaskell `elem` allExtensions libBi
       -- TH always needs vanilla libs, even when building for profiling
 
   createDirectoryIfMissingVerbose verbosity True libTargetDir
hunk ./Distribution/Simple/LHC.hs 547
   -- with profiling. This is because the code that TH needs to
   -- run at compile time needs to be the vanilla ABI so it can
   -- be loaded up and run by the compiler.
-  when (withProfExe lbi && TemplateHaskell `elem` allExtensions exeBi)
+  when (withProfExe lbi && EnableExtension TemplateHaskell `elem` allExtensions exeBi)
      (runGhcProg $ lhcWrap (binArgs False False))
 
   runGhcProg (binArgs True (withProfExe lbi))
hunk ./Distribution/Simple/NHC.hs 77
 import qualified Distribution.Simple.PackageIndex as PackageIndex
 import Distribution.Simple.PackageIndex (PackageIndex)
 import Language.Haskell.Extension
-         ( Language(Haskell98), Extension(..) )
+         ( Language(Haskell98), Extension(..), KnownExtension(..) )
 import Distribution.Simple.Program
          ( ProgramConfiguration, userMaybeSpecifyPath, programPath
          , requireProgram, requireProgramVersion, lookupProgram
hunk ./Distribution/Simple/NHC.hs 135
   let comp = Compiler {
         compilerId         = CompilerId NHC nhcVersion,
         compilerLanguages  = nhcLanguages,
-        compilerExtensions = nhcLanguageExtensions
+        compilerExtensions     = [ (EnableExtension ke, flag)
+                                 | (ke, flag) <- nhcLanguageExtensions ]
       }
   return (comp, conf'''')
 
hunk ./Distribution/Simple/NHC.hs 144
 nhcLanguages = [(Haskell98, "-98")]
 
 -- | The flags for the supported extensions
-nhcLanguageExtensions :: [(Extension, Flag)]
+nhcLanguageExtensions :: [(KnownExtension, Flag)]
 nhcLanguageExtensions =
     -- NHC doesn't enforce the monomorphism restriction at all.
     -- TODO: pattern guards in 1.20
hunk ./Distribution/Simple/UHC.hs 88
   let comp = Compiler {
                compilerId          =  CompilerId UHC uhcVersion,
                compilerLanguages   =  uhcLanguages,
-               compilerExtensions  =  uhcLanguageExtensions
+               compilerExtensions  =  [ (EnableExtension ke, flag)
+                                      | (ke, flag) <- uhcLanguageExtensions ]
              }
   return (comp, conf')
 
hunk ./Distribution/Simple/UHC.hs 97
 uhcLanguages = [(Haskell98, "")]
 
 -- | The flags for the supported extensions.
-uhcLanguageExtensions :: [(Extension, C.Flag)]
+uhcLanguageExtensions :: [(KnownExtension, C.Flag)]
 uhcLanguageExtensions =
     [(CPP, "--cpp"),
      (PolymorphicComponents, ""),
hunk ./Language/Haskell/Extension.hs 46
         knownLanguages,
 
         Extension(..),
-        knownExtensions,
+        KnownExtension(..),
         deprecatedExtensions
   ) where
 
hunk ./Language/Haskell/Extension.hs 102
 -- * Extension
 -- ------------------------------------------------------------
 
--- Note: if you add a new 'Extension':
+-- Note: if you add a new 'KnownExtension':
 --
 -- * also add it to the Distribution.Simple.X.languageExtensions lists
 --   (where X is each compiler: GHC, JHC, Hugs, NHC)
hunk ./Language/Haskell/Extension.hs 107
 --
--- * also to the 'knownExtensions' list below.
-
 -- | This represents language extensions beyond a base 'Language' definition
 -- (such as 'Haskell98') that are supported by some implementations, usually
 -- in some special mode.
hunk ./Language/Haskell/Extension.hs 116
 -- documented in section 7.2.1 of the GHC User's Guide.
 
 data Extension =
- 
+  -- | A known extension
+    EnableExtension KnownExtension
+
+  -- | An unknown extension, identified by the name of its @LANGUAGE@
+  -- pragma.
+  | UnknownExtension String
+
+  deriving (Show, Read, Eq)
+
+data KnownExtension =
+
   -- | [GHC &#xa7; 7.6.3.4] Allow overlapping class instances,
   -- provided there is a unique most specific instance for each use.
     OverlappingInstances
hunk ./Language/Haskell/Extension.hs 389
   -- paper \"Regular Expression Patterns\" by Niklas Broberg, Andreas Farre
   -- and Josef Svenningsson, from ICFP '04.
   | RegularPatterns
-
-  -- | An unknown extension, identified by the name of its @LANGUAGE@
-  -- pragma.
-  | UnknownExtension String
-  deriving (Show, Read, Eq)
+  deriving (Show, Read, Eq, Enum)
 
 -- | Extensions that have been deprecated, possibly paired with another
 -- extension that replaces it.
hunk ./Language/Haskell/Extension.hs 394
 --
-deprecatedExtensions :: [(Extension, Maybe Extension)]
+deprecatedExtensions :: [(KnownExtension, Maybe KnownExtension)]
 deprecatedExtensions =
   [ (RecordPuns, Just NamedFieldPuns)
   , (PatternSignatures, Just ScopedTypeVariables)
hunk ./Language/Haskell/Extension.hs 406
 -- name to the old one for older compilers. Otherwise we are in danger
 -- of the scenario in ticket #689.
 
-knownExtensions :: [Extension]
-knownExtensions =
-  [ OverlappingInstances
-  , UndecidableInstances
-  , IncoherentInstances
-  , RecursiveDo
-  , ParallelListComp
-  , MultiParamTypeClasses
-  , NoMonomorphismRestriction
-  , FunctionalDependencies
-  , Rank2Types
-  , RankNTypes
-  , PolymorphicComponents
-  , ExistentialQuantification
-  , ScopedTypeVariables
-  , ImplicitParams
-  , FlexibleContexts
-  , FlexibleInstances
-  , EmptyDataDecls
-  , CPP
-
-  , KindSignatures
-  , BangPatterns
-  , TypeSynonymInstances
-  , TemplateHaskell
-  , ForeignFunctionInterface
-  , Arrows
-  , Generics
-  , NoImplicitPrelude
-  , NamedFieldPuns
-  , PatternGuards
-  , GeneralizedNewtypeDeriving
-
-  , ExtensibleRecords
-  , RestrictedTypeSynonyms
-  , HereDocuments
-  , MagicHash
-  , TypeFamilies
-  , StandaloneDeriving
-
-  , UnicodeSyntax
-  , PatternSignatures
-  , UnliftedFFITypes
-  , LiberalTypeSynonyms
-  , TypeOperators
---PArr -- not ready yet, and will probably be renamed to ParallelArrays
-  , RecordWildCards
-  , RecordPuns
-  , DisambiguateRecordFields
-  , OverloadedStrings
-  , GADTs
-  , NoMonoPatBinds
-  , RelaxedPolyRec
-  , ExtendedDefaultRules
-  , UnboxedTuples
-  , DeriveDataTypeable
-  , ConstrainedClassMethods
-  , PackageImports
-  , ImpredicativeTypes
-  , NewQualifiedOperators
-  , PostfixOperators
-  , QuasiQuotes
-  , TransformListComp
-  , ViewPatterns
-  , XmlSyntax
-  , RegularPatterns
-  ]
-
 instance Text Extension where
   disp (UnknownExtension other) = Disp.text other
hunk ./Language/Haskell/Extension.hs 408
-  disp other                    = Disp.text (show other)
+  disp (EnableExtension ke)     = Disp.text (show ke)
 
   parse = do
     extension <- Parse.munch1 Char.isAlphaNum
hunk ./Language/Haskell/Extension.hs 414
     return (classifyExtension extension)
 
--- | 'read' for 'Extension's is really really slow so for the Text instance
+instance Text KnownExtension where
+  disp ke = Disp.text (show ke)
+
+  parse = do
+    extension <- Parse.munch1 Char.isAlphaNum
+    case classifyExtension extension of
+        EnableExtension ke ->
+            return ke
+        UnknownExtension _ ->
+            fail ("Can't parse " ++ show extension ++ " as KnownExtension")
+
+-- | 'read' for 'KnownExtension's is really really slow so for the Text
+-- instance
 -- what we do is make a simple table indexed off the first letter in the
 -- extension name. The extension names actually cover the range @'A'-'Z'@
 -- pretty densely and the biggest bucket is 7 so it's not too bad. We just do
hunk ./Language/Haskell/Extension.hs 437
 --
 classifyExtension :: String -> Extension
 classifyExtension string@(c:_)
-  | inRange (bounds extensionTable) c
-  = case lookup string (extensionTable ! c) of
-      Just extension    -> extension
+  | inRange (bounds knownExtensionTable) c
+  = case lookup string (knownExtensionTable ! c) of
+      Just extension    -> EnableExtension extension
       Nothing           -> UnknownExtension string
 classifyExtension string = UnknownExtension string
 
hunk ./Language/Haskell/Extension.hs 443
-extensionTable :: Array Char [(String, Extension)]
-extensionTable =
+knownExtensionTable :: Array Char [(String, KnownExtension)]
+knownExtensionTable =
   accumArray (flip (:)) [] ('A', 'Z')
     [ (head str, (str, extension))
hunk ./Language/Haskell/Extension.hs 447
-    | extension <- knownExtensions
+    | extension <- [toEnum 0 ..]
     , let str = show extension ]
hunk ./Language/Haskell/Extension.hs 450
+
}

Context:

[Make the .cabal file fully 1.10-compliant
Ian Lynagh <ig...@earth.li>**20101020133037
 Ignore-this: 66409062c8d4b698f69aa58a83b85ef1
 Add Default-Language field, and change Extensions to Default-Extensions.
] 
[Require "cabal-version: >= 1.10" as we use the new testsuite syntax
Ian Lynagh <ig...@earth.li>**20101020131829
 Ignore-this: 6aecdd77f78234f0359af0509f1ba636
] 
[Fix warnings: Remove duplicate imports
Ian Lynagh <ig...@earth.li>**20101020125710
 Ignore-this: dea9d889078c729459e1ab92a8e54c08
] 
[Update the pretty printer to the current testsuite interface
Duncan Coutts <dun...@haskell.org>**20101020120506
 Ignore-this: 480a349e93be8228f81f93632cabe2c7
] 
[Improve error messages about programs not being found
Duncan Coutts <dun...@haskell.org>**20101019074436
 Ignore-this: 9b4daf9a09179482049146669af59f76
 Make it clear it is a program we are talking about, not a library.
] 
[Merge conflicts
Ian Lynagh <ig...@earth.li>**20101020112200
 Ignore-this: d96cab403511f914d9d8df1a29ca58ee
] 
[Add a note about the remaining issue with runhugs scripts
Duncan Coutts <dun...@haskell.org>**20101018232248
 Ignore-this: 3e83a3238d08cdb3ad9e353d43fbf7fa
] 
[Add package QA checks for the new language and extensions fields
Duncan Coutts <dun...@haskell.org>**20101018180343
 Ignore-this: a063fd21e86e4e19b8152258c5a0711f
] 
[Check at configure time that languages are supported by the compiler
Duncan Coutts <dun...@haskell.org>**20101018180300
 Ignore-this: e3988c2eff46129b1f2732cd9647c935
] 
[Add compiler support for using the new languages and extensions fields
Duncan Coutts <dun...@haskell.org>**20101018180151
 Ignore-this: ec1b61767d492dcd2dfa6a07ace3b982
] 
[Add hugs support for the languages and extensions fields
Duncan Coutts <dun...@haskell.org>**20101018175647
 Ignore-this: 9b39c392119aebbbad22a64dcf992f88
 Incidentally, should fixe ticket #43.
] 
[Add parsing for the new language and extensions fields
Duncan Coutts <dun...@haskell.org>**20101018091918
 Ignore-this: c59c8ef96c83f35e293c8f495b89fda6
] 
[Add new language and extensions fields (internal data structures)
Duncan Coutts <dun...@haskell.org>**20101018090620
 Ignore-this: f49dd9278b0053bc441a37beeb2f6145
 New fields default-language and other-languages for specifying the
 base languages for the package, e.g. Haskell98, Haskell2010
 New fields default-extensions and other-extensions for the language
 extensions. Separate from the old extensions field.
 The separation lets us express the difference between declaring to
 the outside world that a package uses certain languages or extensions
 and whether certain languages or extensions should be applied to
 all modules in the package component.
] 
[Extend the Compiler interface to list the supported languages
Duncan Coutts <dun...@haskell.org>**20101018082608
 Ignore-this: 8b1ab7cc14f35dd6604c2a85173ad48
] 
[Add a Language type, starting with Haskell98 and Haskell2010
Duncan Coutts <dun...@haskell.org>**20101018082208
 Ignore-this: de80df5317b5d44900e30c947a86364b
] 
[Merge and tweaks following pretty printer changes
Duncan Coutts <dun...@haskell.org>**20101018195344
 Ignore-this: 513a2b0ce02fed98f5beba0dd893eb16
] 
[pretty printer fixes (FreeText starting with ., version tags, version range parens, option order).
j...@arcor.de**20101011094517
 Ignore-this: 400ac5be014f1529632bd16ffd878a92
] 
[reentered accidentally lost exports
j...@arcor.de**20100929105852
 Ignore-this: 2ad4ecfac6feba4c2a59a131c05c8a40
] 
[new cabal pretty printer.
j...@arcor.de**20100929103653
 Ignore-this: 43f954ec31373e327f2c29fcbf3f0865
] 
[Fix old doc links
Duncan Coutts <dun...@haskell.org>**20100727012425
 Ignore-this: 9e9d0f2045adebe7bb38b5d1a7d2d71a
] 
[Add note about ticket #689 about deprecated extensions
Duncan Coutts <dun...@haskell.org>**20100622151328
 Ignore-this: 56cf0027a4c10f4c07045e2ccdbb819c
] 
[Head version needs cabal-version: >=1.8 due to test stanza
Duncan Coutts <dun...@haskell.org>**20101017155521
 Ignore-this: 6652a529071ccb2eb1cdeda3451aac30
] 
[Remove unused cpp version definition
Duncan Coutts <dun...@haskell.org>**20101017155218
 Ignore-this: 8dc3425bd811d60d28c2eaf365ec1e66
] 
[Change the way we handle the version number during bootstrapping
Duncan Coutts <dun...@haskell.org>**20101016191252
 Ignore-this: e21559acc28b7bd811dc4fe147e645b2
 Means we only need to have the version in one place now. Yay.
] 
[Restore compatability with ghc-6.8 and 6.6 but drop support for ghc-6.4
Duncan Coutts <dun...@haskell.org>**20101016182714
 Ignore-this: 6aef933e4bfb4a9c47021d17370805ea
] 
[Add the Cabal unit tests as a test-suite stanza
Duncan Coutts <dun...@haskell.org>**20101016165656
 Ignore-this: b9abbfe867754b8bf5b02919c1f25509
 Still some other tests that need hooking up to this mechanism
] 
[Update the unit tests of the testsuite feature
Duncan Coutts <dun...@haskell.org>**20101016165615
 Ignore-this: bc08d2a8609943f40e901c42916072c2
] 
[Rename test --human-log to just --log
Duncan Coutts <dun...@haskell.org>**20101016153441
 Ignore-this: a2ccb95759a67ae2888a2db2d2ba678d
 Still have --machine-log as a separate flag
] 
[Remove the test --append-human-log and --replay features
Duncan Coutts <dun...@haskell.org>**20101016153235
 Ignore-this: 23d9c6431f929cd4078c54e03928cef2
] 
[Add instance Text TestShowDetails parsing and use it for --show-details flag
Duncan Coutts <dun...@haskell.org>**20101016153015
 Ignore-this: 1018e874b8acbf51bd7081df1210285
 Rather than Read/Show
] 
[Fix a cabal-version check so it accepts the field missing entirely
Duncan Coutts <dun...@haskell.org>**20101016151929
 Ignore-this: e30f6fe6e7f54cc5c791a3b6761e93de
] 
[Add testsuites to the allBuildInfo function, used mainly in checks
Duncan Coutts <dun...@haskell.org>**20101013172229
 Ignore-this: be876b609bf1266f3928f25e94f87703
] 
[Update the message for a package check
Duncan Coutts <dun...@haskell.org>**20101013172206
 Ignore-this: 875cc7c6a763321f2e3251195c9dfb1e
] 
[Add a few TODOs about package checks
Duncan Coutts <dun...@haskell.org>**20101013172128
 Ignore-this: 837bda043d740f0b92549f3379d43909
] 
[Check test-suite sections even when they have been disabled at configure time
Duncan Coutts <dun...@haskell.org>**20101013171851
 Ignore-this: 938113ec297b2e5c511a72c5ac8a86d
] 
[Default to Haskell98 for GHC 7.x
Duncan Coutts <dun...@haskell.org>**20101013022258
 Ignore-this: c34b946f55e5ec054cc842914f58b5a5
 GHC 7 defaults to Haskell2010, we stick with 98 for the moment.
 We will later introduce a new language field to control this.
] 
[Change the syntax and behaviour of the cabal-version field
Duncan Coutts <dun...@haskell.org>**20101013014933
 Ignore-this: c4cb33360d623ff312b5c3f2d78f730c
 For historical reasons the cabal-version is specified with a version range,
 to indicate the range of versions of tools that the package will work with.
 We now think it makes more sense to specify the version of the Cabal spec
 that the package follows. Old Cabal versions will not be able to parse simple
 versions in this field. So we initially make the parser allow plain versions
 but then we add a check to warn about using it prior to Cabal-1.12 at which
 point it will be allowed.
 Added a check about using version ranges that are not of the form '>= x.y'.
 Also change behaviour to ignore upper bounds in the given version range.
] 
[Add final newline
Simon Marlow <marlo...@gmail.com>**20101013125337
 Ignore-this: 99e055c7186219369902a63c63c3fd76
 Something in the Windows build was complaining about the lack of a
 final newline.
] 
[Fix duplicate import warnings
Ian Lynagh <ig...@earth.li>**20101012131227
 Ignore-this: a9b51a864f95206f4d972f1e7506be55
] 
[Remove the ghc Makefile stuff for the old docbook xml
Duncan Coutts <dun...@haskell.org>**20101010210026
 Ignore-this: 6c714ba98b60e15e44577b64d2de3e1c
 Not woth keeping it, none of it can sensibly be reused. The GHC
 devs will need to add something new for the markdown user guide.
] 
[Update Makefile for new markdown user guide
Duncan Coutts <dun...@haskell.org>**20101010205938
 Ignore-this: dcb5bd072c619516e23329f170458d72
] 
[Add a FIXME about parsing cabal files
Duncan Coutts <dun...@haskell.org>**20101010203421
 Ignore-this: 12804d54e81b5ea5878e52628717bc1d
] 
[Refactor the missing VCS info QA check
Duncan Coutts <dun...@haskell.org>**20101010192346
 Ignore-this: fa6a50a9bd43cf9069e7cd16e23a2b4e
 Starting with Marc Weber's code and just moving
 it about and making it fit in a bit nicer.
] 
[Remove redundant import
Duncan Coutts <dun...@haskell.org>**20101010190724
 Ignore-this: a978a6a257a31a57d07d57471f04af49
] 
[Rename LocalBuildInfo extraArgs to extraConfigArgs to avoid name clashes
Duncan Coutts <dun...@haskell.org>**20101010190036
 Ignore-this: 817061002399a51cbf31da2ba002737b
] 
[Add a bunch of TODOs about the test feature
Duncan Coutts <dun...@haskell.org>**20101010173245
 Ignore-this: f2acc005fef4996a2c5260356eaf219f
] 
[Change how the test suite interfaces are represented, parsed and used
Duncan Coutts <dun...@haskell.org>**20101010162526
 Ignore-this: 8773e7756fc23bc04c9e5b2b14031512
 Also, stick to version 0.9 of the "detailed" test interface, since it's
 not quite finalised yet. Misc other minor code cleanups.
] 
[Added test suites to Cabal User Guide
Thomas Tuegel <ttue...@gmail.com>**20100811141332
 Ignore-this: 3975acc803fdba809ca1c8abeef21677
 Ticket #215 (Overhaul support for packages' tests).
] 
[Removed "$stdio" from acceptable template variables
Thomas Tuegel <ttue...@gmail.com>**20100810201828
 Ignore-this: c50e05e9a73c726567eff0a364f29750
 Ticket #215 (Overhaul support for packages' tests).  In the usage message, the
 template variable "$stdio" was incorrectly listed as being available in the
 "--human-log" and "--machine-log" flags.  The variable has been removed.
] 
[Added --test-option(s) flags
Thomas Tuegel <ttue...@gmail.com>**20100809161341
 Ignore-this: cea82267bbc0b16d5f21bfc086285905
 Ticket #215 (Overhaul support for packages' tests).  This patch adds the
 --test-option(s) flags for passing command-line options to test executables.
] 
[Respect verbosity flag when outputting test log
Thomas Tuegel <ttue...@gmail.com>**20100809151517
 Ignore-this: 73668e49eeea216c27b5233c7e3fe2cb
 Ticket #215 (Overhaul support for packages' tests).  This patch corrects the
 printing of the human-readable test log to the terminal so the setting of the
 verbosity flag is respected.
] 
[Added --replay option to cabal test
Thomas Tuegel <ttue...@gmail.com>**20100803164932
 Ignore-this: c97d70e21d3847aa4d889304a7e94451
 Ticket #215 (Overhaul support for packages' tests).  This patch adds support for
 using machine logs from previous runs to replay tests with the same options.
 When using --replay, Cabal will replay all test suites listed in the machine log
 specified; test suite names specified on the command line are ignored.
] 
[Renamed "library" test suite type to "detailed"
Thomas Tuegel <ttue...@gmail.com>**20100803141125
 Ignore-this: 457c1a155020303962ae55b2bcd8415c
 Ticket #215 (Overhaul support for packages' tests).
] 
[Fixed human test log output for failing tests
Thomas Tuegel <ttue...@gmail.com>**20100803030246
 Ignore-this: f9d3ef127cdb849762af79f31a0c80c9
 Ticket #215 (Overhaul support for packages' tests).  This patch corrects the bug
 in the human test log output to terminal where the line wrapping code in Cabal
 caused terminal control codes output by the test framework to be placed
 incorrectly.  Line wrapping is no longer performed.
] 
[Displaying human-readable test log when requested
Thomas Tuegel <ttue...@gmail.com>**20100730151818
 Ignore-this: 98f0adb8e47a52a59ccb3581982157ed
 Ticket #215 (Overhaul support for packages' tests).  This patch causes Cabal to
 display the contents of the human-readable log file on the terminal when run 
 with --show-details=always or when run with --show-details=failures and a 
 failure is detected.  The structure of the test logging code has been changed 
 for clarity to debug a problem where test executables that write to their stderr 
 channel disrupt terminal output.
] 
[Added debugging output to test summary
Thomas Tuegel <ttue...@gmail.com>**20100730134008
 Ignore-this: 826d20639f17ae0650d1c9b8a56b43a7
 Ticket #215 (Overhaul support for packages' tests).
] 
[Using correct name of log file in human-readable log
Thomas Tuegel <ttue...@gmail.com>**20100730041720
 Ignore-this: 3c6df44f5d6414ce1fe2b58c50590726
 Ticket #215 (Overhaul support for packages' tests).  Previously, human-readable
 logs listed the name of the temporary file where test suite output is
 initially logged.
] 
[Renamed option '--test-filter' to '--show-details'
Thomas Tuegel <ttue...@gmail.com>**20100730023026
 Ignore-this: 8b78eed5ccf9cb7ed6a55b86d886e5cc
 Ticket #215 (Overhaul support for packages' tests).
] 
[Displaying location of test suite log on terminal
Thomas Tuegel <ttue...@gmail.com>**20100729141159
 Ignore-this: e98a67180c6ff1511b86e442f9acf3c1
 Ticket #215 (Overhaul support for packages' tests).  It was decided that
 indicating the location of the human-readable test suite log made Cabal's test
 runner easier to use.
] 
[Passing names of test suites to run to test stage
Thomas Tuegel <ttue...@gmail.com>**20100726150811
 Ignore-this: bf556a0a06fe26b132f1eb5caec21805
 Ticket #215 (Overhaul support for packages' tests).
] 
[Fixed deprecation warning in Distribution.TestSuite
Thomas Tuegel <ttue...@gmail.com>**20100726141448
 Ignore-this: 64cd6a5a936efd6b0ee0f50564440a9d
 Ticket #215 (Overhaul support for packages' tests).  Warning resulted from use
 of Control.OldException.
] 
[Fixed help message for machine-log path template
Thomas Tuegel <ttue...@gmail.com>**20100724164652
 Ignore-this: 52205830166a307eedce807e908f7a0a
 Ticket #215 (Overhaul support for packages' tests).  The message previously
 indicated that $test-suite is acceptable in the machine log path template,
 which is not true.
] 
[Catching exceptions when lifting pure tests to IO
Thomas Tuegel <ttue...@gmail.com>**20100724134336
 Ignore-this: 89a2265a94ee0082935d236dd64c12d4
 Ticket #215 (Overhaul support for packages' tests).
] 
[Using common function to name path environment variables in PathsModule and Test
Thomas Tuegel <ttue...@gmail.com>**20100722145840
 Ignore-this: 5cea1a3e77acb84a162de3d1c85a3fe6
 Ticket #215 (Overhaul support for packages' tests).  The names of environment
 variables used to set package paths at runtime were previously hard-coded into
 the function that generates the paths module.  A function generating the
 variable names is now exported from Distribution.Simple.Build.PathsModule and
 used to set the datadir in Distribution.Simple.Test to prevent breakage if the
 naming scheme changes.
] 
[Added documentation for machine-readable test log types
Thomas Tuegel <ttue...@gmail.com>**20100722140017
 Ignore-this: 60f934e11b1c3ee4df9f48677528af47
 Ticket #215 (Overhaul support for packages' tests).
] 
[Improved documentation for Distribution.TestSuite
Thomas Tuegel <ttue...@gmail.com>**20100722124239
 Ignore-this: f7b1261270c4815b0691ce33c664908c
 Ticket #215 (Overhaul support for packages' tests).
] 
[Fixed documentation errors in Distribution.Simple.Test
Thomas Tuegel <ttue...@gmail.com>**20100721221844
 Ignore-this: b111e727b4a556b17c2a1eb4dfd6971b
 Ticket #215 (Overhaul support for packages' tests).
] 
[Renamed Distribution.TestSuite.optionLookup to lookupOption
Thomas Tuegel <ttue...@gmail.com>**20100721170724
 Ignore-this: 3a5e79fd0a14d974e664a74af5cb83d1
 Ticket #215 (Overhaul support for packages' tests.)
] 
[Added console-style test summary information to human-readable logs
Thomas Tuegel <ttue...@gmail.com>**20100721163516
 Ignore-this: 494c2220285ef4bda036ecdfd7242adf
 Ticket #215 (Overhaul support for packages' tests).
] 
[Added flag allowing human-readable test logs to be appended instead of overwritten
Thomas Tuegel <ttue...@gmail.com>**20100721160421
 Ignore-this: f157a4830f82a4a978c1cfb1931a0258
 Ticket #215 (Overhaul support for packages' tests).
] 
[Added clarifying comments to Distribution.Simple.Test
Thomas Tuegel <ttue...@gmail.com>**20100721160417
 Ignore-this: 100000890351a75557a6dfa0f71c419f
 Ticket #215 (Overhaul support for packages' tests).
] 
[Using a separate PathTemplateEnv for machine test logs
Thomas Tuegel <ttue...@gmail.com>**20100720204724
 Ignore-this: 4920c6e88b8d3d3d788ba42d6b5268af
 Ticket #215 (Overhaul support for packages' tests).  Previously, the use of a
 dummy test suite name would lead to unintuitive expansions of the PathTemplate
 governing the location of the machine-readable package test log.
] 
[Exporting machine log types from Distribution.Simple.Test
Thomas Tuegel <ttue...@gmail.com>**20100720204558
 Ignore-this: 6920621dbabf471cef7d688904b9b1b8
 Ticket #215 (Overhaul support for packages' tests).  These types were exported
 to enable parsing of test logs by external utilities.
] 
[Added 'check' and 'optionLookup' to Distribution.TestSuite
Thomas Tuegel <ttue...@gmail.com>**20100720134707
 Ignore-this: 21ef44dc0087ff8333b1722309f8fbdd
 Ticket #215 (Overhaul support for packages' tests).  These functions were added
 for the benefit of test runner authors.
] 
[Saving Options from test runs for reproducability
Thomas Tuegel <ttue...@gmail.com>**20100715180003
 Ignore-this: 858c387d83e93e193f7c66df3901f6e3
 Ticket #215 (Overhaul support for packages' tests).  Saving the Options used
 required changes to the TestSuite interface, with the Option values now being
 specified as Strings and not Dynamics.  This was necessary because the lack of
 a Read instance for Dynamic.
] 
[Improvements to test suite logging
Thomas Tuegel <ttue...@gmail.com>**20100715020549
 Ignore-this: b47f4358302b283e93ccaff81db123f2
 Ticket #215 (Overhaul support for packages' tests).  This patch includes proper
 support for both machine- and human-readable logs.
] 
[Removed duplicate code for test suite interface version checks
Thomas Tuegel <ttue...@gmail.com>**20100713144835
 Ignore-this: e06c264351013480a66c013ca398db4b
 Ticket #215 (Overhaul support for packages' tests).  Duplicate code for checking
 the test suite interface version was replaced with a single function
 'testVersion1 :: Version -> Bool' exported from Distribution.PackageDescription.
] 
[Added QA checks for test suite name conflicts
Thomas Tuegel <ttue...@gmail.com>**20100712154401
 Ignore-this: df13e2f16cf4e879f5d5f6538c6e7db8
 Ticket #215 (Overhaul suppport for packages' tests).
] 
[New test suite log format
Thomas Tuegel <ttue...@gmail.com>**20100708132650
 Ignore-this: 96a300e6acedd0de63757713fbb1d832
 Ticket #215 (Overhaul support for package's tests).  This patch adds a new test
 log file format based on the TestSuiteLog data structure.  The interface between
 Cabal and the library test suite runner has consequently changed.
] 
[Inheriting existing environment for test suite executables
Thomas Tuegel <ttue...@gmail.com>**20100707222244
 Ignore-this: 6f08245c83817a85c7da5a05f810abd6
 Ticket #215 (Overhaul support for packages' tests).  Previously, the test
 runner replaced the environment for test suite executables with one containing
 only the datadir path for package data files.  For test suites invoking other
 programs, it is necessary to preserve the system paths, so the datadir path
 variable is appended to the inherited environment.
] 
[Improvements to library test suite runner, including documentation
Thomas Tuegel <ttue...@gmail.com>**20100624181304
 Ignore-this: 45baa7905de5423e91707f52e590bbad
 Ticket #215 (Overhaul support for packages' tests).
] 
[Renamed 'result' and 'getResult' to 'run' and 'runM'
Thomas Tuegel <ttue...@gmail.com>**20100623184640
 Ignore-this: 7bb6dd598eaa135fcbf73e82ab0d2ce2
 Ticket #215 (Overhaul support for packages' tests).
] 
[Setting datadir environment variables when running tests
Thomas Tuegel <ttue...@gmail.com>**20100623183201
 Ignore-this: 7a9e26c684417871609847f6e4d4883e
 Ticket #215 (Overhaul support for packages' tests).
] 
[Added convenience functions and default instances making export of 'Test' constructors unnecessary
Thomas Tuegel <ttue...@gmail.com>**20100623151934
 Ignore-this: 1979265e345e268787b5b6fe49bdfd64
 Ticket #215 (Overhaul support for packages' tests).
] 
[Added support for running the default stub executables Cabal creates for library test suites
Thomas Tuegel <ttue...@gmail.com>**20100623151903
 Ignore-this: 2be1bbfb07a7fc0e3a0d2c9e5bdf2252
 Ticket #215 (Overhaul support for packages' tests).
] 
[Removed dependency on extensible-exceptions from detailed test suite interface
Thomas Tuegel <ttue...@gmail.com>**20100623150227
 Ignore-this: 50ad3ee8c2dc5f62b48aa84d0318c3e6
 Ticket #215 (Overhaul support for packages' tests).
] 
[Added support for building detailed library test suites
Thomas Tuegel <ttue...@gmail.com>**20100623150222
 Ignore-this: 1f2a6034af9adf493088265cc8481df5
 Ticket #215 (Overhaul support for packages' tests).  This patch preprocesses
 and builds library test suites.  The fake packages are created for each test
 suite, where the fake package and test suite share the same name; the packages
 and libraries are registered in the inplace package database so that test
 agents can build stub executables against them.
] 
[Improved security of test log file creation
Thomas Tuegel <ttue...@gmail.com>**20100621114726
 Ignore-this: 6fed3aa4ebcb587b48bb2a256fcbc61b
 Ticket #215 (Overhaul support for packages' tests).  The algorithm previously
 used to name the log files for test output suffers from a known vulnerability
 due to the predictability of chosen names.
] 
[Added detailed test interface
Thomas Tuegel <ttue...@gmail.com>**20100617210631
 Ignore-this: 161624662d6ec7946a33415ddbff4445
 Ticket #215 (Overhaul support for packages' tests).  This patch provides the
 detailed test interface for exposing individual tests to Cabal and other test
 agents.  It also provides the simple function Cabal will provide as the default
 test runner.
] 
[Fixed test suite breakage due to TestSuite API changes
Thomas Tuegel <ttue...@gmail.com>**20100629212935
 Ignore-this: 8de228836efb206e1adb833c841ae757
 Ticket #215 (Overhaul support for packages' tests).  The update to the
 TestSuite parser which stopped disallowed configurations during parsing also
 broke the existing test suite with API changes.
] 
[Added --test-filter flag
Thomas Tuegel <ttue...@gmail.com>**20100624175917
 Ignore-this: e8fcaddf34a42326d0f3a1081aafb724
 Ticket #215 (Overhaul support for packages' tests).
] 
[Qualified import of Distribution.Simple.Setup in Distribution.Simple.Haddock
Thomas Tuegel <ttue...@gmail.com>**20100623193755
 Ignore-this: ec5750f56b22f67e5862036fcdd8ecee
] 
[Using path templates to name test log files
Thomas Tuegel <ttue...@gmail.com>**20100622162317
 Ignore-this: af6564bf6154e29e363ee343c9fc5806
 Ticket #215 (Overhaul support for packages' tests).
] 
[More docs about the meaning of the cabal-version field
Duncan Coutts <dun...@haskell.org>**20101010154251
 Ignore-this: 381ede9227f7a9db78f1007364660648
] 
[Document how Cabal-Version affects behaviour of build-depends
Ben Millwood <hask...@benmachine.co.uk>**20100926025550
 Ignore-this: ba6367db93c15906331457a0468db436
] 
[initial support for building executables with UHC
Atze Dijkstra <a...@cs.uu.nl>**20100923214130
 Ignore-this: bbbf1adcec2fcfe87ce1db18c804f21a
] 
[Added flags related to UHC, uhcbase package
Atze Dijkstra <a...@cs.uu.nl>**20100706115341
 Ignore-this: f7dd2b14e3146f8844635ddcb70ac3b9
] 
[Minor changes to the auto-reconfiguration feature.
Duncan Coutts <dun...@haskell.org>**20101010144111
 Ignore-this: 944f595482ea42eb1907fb1150d6d4c0
 Change the messages slightly. Make configure return the
 new lbi, rather than having to re-read the lbi from file
 (avoiding potential infinite loop if the IO failed).
] 
[Auto-reconfiguration when .cabal is newer than setup-config
Dmitry Astapov <dasta...@gmail.com>**20100825131106
 Ignore-this: 22ab2b6de0251f6cf1da7c2538544d4
 
 This patch adds "ConfigFlags" to the "LocalBuildInfo" and reuses them to
 perform "configureAction" when .cabal file is changed. This has
 the same effect as re-running "configure" with the most recent used
 set of options, which should be the sensible thing to do.
 
 Closes #294, #477, #309 and #518.
] 
[Fix processing of ghc-shared-options
Duncan Coutts <dun...@haskell.org>**20101009204809
 Ignore-this: 571b3d70fbc705282b9fdfdafdc2f009
 Original patch was:
   Sun Oct  7 13:41:53 BST 2007  Thorkil Naur <n...@post11.tele.dk>
     * Fix processing of shared options
 Re-recorded due to code churn
] 
[Correct spelling of 'transative'
Duncan Coutts <dun...@haskell.org>**20101009202836
 Ignore-this: fe7ec5ae621135024403ae0aa42094c2
 Original patch by:
   Thu Aug 21 21:19:51 MDT 2008  dbu...@gmail.com
     * Correct spelling of 'transative'.
 Re-recorded due to conflict.
] 
[print a warning if repository location isn't specified and the cabal project looks like being tracked by a version control system
marco-owe...@gmx.de**20091129192013
 Ignore-this: 5ce5073f1793193e437353490eff0276
] 
[Bump Cabal HEAD version to 1.11.0
Duncan Coutts <dun...@haskell.org>**20101010154518
 Ignore-this: 407e2b1c0de8c10f399841b3fbea1dd3
] 
[TAG 1.10 branch forked
Duncan Coutts <dun...@haskell.org>**20101010155050
 Ignore-this: 7b0241166f919e2a374a2a69669b2e6b
] 
Patch bundle hash:
5885b666a95fa5ac860b153c8cf604898ef90328
_______________________________________________
cabal-devel mailing list
cabal-devel@haskell.org
http://www.haskell.org/mailman/listinfo/cabal-devel

Reply via email to