first cut at configurations patch, and a couple more

Simon Marlow simonmarhaskell at gmail.com
Tue Aug 1 11:07:01 EDT 2006


Ok, spurned on by the possibiliy of worse merges to come, I've cleaned up my 
current code, merged it up to date, and made it work (where "work" means 
"doesn't make anything worse" - i.e. there is no new functionality exposed to 
the user yet).

I also merged Bertram Felgenhauer patches with my own, and I've included updated 
versions of his patches in this bundle:  1 patch for cleanups to parsing, I just 
took some docs from Bertram's patch because everything else is already in my 
changes, and 1 patch to add the exposed field.

If anyone wishes to continue with this configurations work, be my guest - I'll 
be busy for a while with GHC contractor interviews and stuff.  But please let me 
know if you plan to hack on it, to prevent any possible overlap.

Cheers,
	Simon
-------------- next part --------------

New patches:

[Partial support for configurations
Simon Marlow <simonmar at microsoft.com>**20060801075456
 This commit gets us part of the way to supporting "configurations"
 (conditional sections in the package description file).  The changes
 to Distribution.PackageDescription are done, what remains is to hook
 this up properly to the rest of the system.  So right now, while you
 can add "configuration:" stanzas to a .cabal file, they have no
 effect.
 
 While I was here, I cleaned up various things I found along the way,
 including refactoring the parsing machinery a fair bit.
] {
hunk ./Distribution/Compiler.hs 71
-              deriving (Show, Read, Eq)
+              deriving (Show, Read, Eq, Ord)
hunk ./Distribution/InstalledPackageInfo.hs 58
-	StanzaField(..), singleStanza, ParseResult(..), LineNo,
+	FieldDescr(..), readFields, ParseResult(..), LineNo,
hunk ./Distribution/InstalledPackageInfo.hs 152
-  stLines <- singleStanza inp
+  stLines <- readFields inp
hunk ./Distribution/InstalledPackageInfo.hs 157
-parseBasicStanza :: [StanzaField a]
+parseBasicStanza :: [FieldDescr a]
hunk ./Distribution/InstalledPackageInfo.hs 161
-parseBasicStanza ((StanzaField name _ set):fields) pkg (lineNo, f, val)
+parseBasicStanza ((FieldDescr name _ set):fields) pkg (lineNo, f, val)
hunk ./Distribution/InstalledPackageInfo.hs 173
-    ppFields ((StanzaField name get' _):flds) = 
+    ppFields ((FieldDescr name get' _):flds) = 
hunk ./Distribution/InstalledPackageInfo.hs 180
-  = case [ (f,get') | (StanzaField f get' _) <- fields, f == field ] of
+  = case [ (f,get') | (FieldDescr f get' _) <- fields, f == field ] of
hunk ./Distribution/InstalledPackageInfo.hs 189
-fields :: [StanzaField InstalledPackageInfo]
-fields = basicStanzaFields ++ installedStanzaFields
+fields :: [FieldDescr InstalledPackageInfo]
+fields = basicFieldDescrs ++ installedFieldDescrs
hunk ./Distribution/InstalledPackageInfo.hs 192
-basicStanzaFields :: [StanzaField InstalledPackageInfo]
-basicStanzaFields =
+basicFieldDescrs :: [FieldDescr InstalledPackageInfo]
+basicFieldDescrs =
hunk ./Distribution/InstalledPackageInfo.hs 229
-installedStanzaFields :: [StanzaField InstalledPackageInfo]
-installedStanzaFields = [
+installedFieldDescrs :: [FieldDescr InstalledPackageInfo]
+installedFieldDescrs = [
hunk ./Distribution/Make.hs 119
-                (flags, _, args) <- parseConfigureArgs defaultProgramConfiguration flags args []
+                (flags, _, args) <- parseConfigureArgs defaultProgramConfiguration flags args [] []
hunk ./Distribution/PackageDescription.hs 47
-        parseDescription,
-        StanzaField(..),
-        LineNo,
-        basicStanzaFields,
hunk ./Distribution/PackageDescription.hs 49
-        sanityCheckPackage, errorOut,
-        setupMessage,
+
+	-- ** Libraries
hunk ./Distribution/PackageDescription.hs 55
+
+	-- ** Executables
hunk ./Distribution/PackageDescription.hs 60
+
+        -- ** Configurations
+        Configuration(..), emptyConfiguration,
+	Cond(..), showCond, parseCond,
+        condUserSymbols,
+
+	-- ** Parsing
+        FieldDescr(..),
+        LineNo,
+
+	-- ** Sanity checking
+        sanityCheckPackage,
+
hunk ./Distribution/PackageDescription.hs 76
+
hunk ./Distribution/PackageDescription.hs 85
+
hunk ./Distribution/PackageDescription.hs 87
+	satisfyDependency,
hunk ./Distribution/PackageDescription.hs 89
-        PError, showError,
hunk ./Distribution/PackageDescription.hs 92
+        setupMessage,
+
hunk ./Distribution/PackageDescription.hs 95
+	-- * Debugging
hunk ./Distribution/PackageDescription.hs 104
-import Data.List (nub,lookup)
-import Text.PrettyPrint.HughesPJ
+import Data.List (nub,lookup,maximumBy)
+import Text.PrettyPrint.HughesPJ as Pretty
hunk ./Distribution/PackageDescription.hs 110
+import qualified System.Info
hunk ./Distribution/PackageDescription.hs 125
+import Distribution.ParseUtils  (runP)
hunk ./Distribution/PackageDescription.hs 129
-import Distribution.ParseUtils  (runP)
+import Data.List (sortBy)
hunk ./Distribution/PackageDescription.hs 135
+
+-- -----------------------------------------------------------------------------
+-- The PackageDescription type
hunk ./Distribution/PackageDescription.hs 168
-        extraTmpFiles  :: [FilePath]
+        extraTmpFiles  :: [FilePath],
+	configurations :: [Configuration]
hunk ./Distribution/PackageDescription.hs 172
-
-data Library = Library {
-        exposedModules    :: [String],
-        libBuildInfo      :: BuildInfo
-    }
-    deriving (Show, Eq, Read)
-
-emptyLibrary :: Library
-emptyLibrary = Library [] emptyBuildInfo
hunk ./Distribution/PackageDescription.hs 194
-                      extraTmpFiles = []
+                      extraTmpFiles = [],
+                      configurations = []
hunk ./Distribution/PackageDescription.hs 197
+
+
+-- the strings for the required fields are necessary here, and so we
+-- don't repeat ourselves, I name them:
+reqNameName       = "name"
+reqNameVersion    = "version"
+reqNameCopyright  = "copyright"
+reqNameMaintainer = "maintainer"
+reqNameSynopsis   = "synopsis"
+
+pkgDescrFieldDescrs :: [FieldDescr PackageDescription]
+pkgDescrFieldDescrs =
+ [ simpleField reqNameName
+           text                   parsePackageName
+           (pkgName . package)    (\name pkg -> pkg{package=(package pkg){pkgName=name}})
+ , simpleField reqNameVersion
+           (text . showVersion)   parseVersion
+           (pkgVersion . package) (\ver pkg -> pkg{package=(package pkg){pkgVersion=ver}})
+ , simpleField "cabal-version"
+           (text . showVersionRange) parseVersionRange
+           descCabalVersion       (\v pkg -> pkg{descCabalVersion=v})
+ , simpleField "license"
+           (text . show)          parseLicenseQ
+           license                (\l pkg -> pkg{license=l})
+ , simpleField "license-file"
+           showFilePath           parseFilePathQ
+           licenseFile            (\l pkg -> pkg{licenseFile=l})
+ , simpleField reqNameCopyright
+           showFreeText           (munch (const True))
+           copyright              (\val pkg -> pkg{copyright=val})
+ , simpleField reqNameMaintainer
+           showFreeText           (munch (const True))
+           maintainer             (\val pkg -> pkg{maintainer=val})
+ , commaListField  "build-depends"
+           showDependency         parseDependency
+           buildDepends           (\xs    pkg -> pkg{buildDepends=xs})
+ , simpleField "stability"
+           showFreeText           (munch (const True))
+           stability              (\val pkg -> pkg{stability=val})
+ , simpleField "homepage"
+           showFreeText           (munch (const True))
+           homepage               (\val pkg -> pkg{homepage=val})
+ , simpleField "package-url"
+           showFreeText           (munch (const True))
+           pkgUrl                 (\val pkg -> pkg{pkgUrl=val})
+ , simpleField reqNameSynopsis
+           showFreeText           (munch (const True))
+           synopsis               (\val pkg -> pkg{synopsis=val})
+ , simpleField "description"
+           showFreeText           (munch (const True))
+           description            (\val pkg -> pkg{description=val})
+ , simpleField "category"
+           showFreeText           (munch (const True))
+           category               (\val pkg -> pkg{category=val})
+ , simpleField "author"
+           showFreeText           (munch (const True))
+           author                 (\val pkg -> pkg{author=val})
+ , listField "tested-with"
+           showTestedWith         parseTestedWithQ
+           testedWith             (\val pkg -> pkg{testedWith=val})
+ , listField "data-files"  
+           showFilePath           parseFilePathQ
+           dataFiles              (\val pkg -> pkg{dataFiles=val})
+ , listField "extra-source-files" 
+           showFilePath    parseFilePathQ
+           extraSrcFiles          (\val pkg -> pkg{extraSrcFiles=val})
+ , listField "extra-tmp-files" 
+           showFilePath       parseFilePathQ
+           extraTmpFiles          (\val pkg -> pkg{extraTmpFiles=val})
+ ]
+
+-- ---------------------------------------------------------------------------
+-- The Library type
+
+data Library = Library {
+        exposedModules    :: [String],
+        libBuildInfo      :: BuildInfo
+    }
+    deriving (Show, Eq, Read)
+
+emptyLibrary :: Library
+emptyLibrary = Library [] emptyBuildInfo
+
+-- |does this package have any libraries?
+hasLibs :: PackageDescription -> Bool
+hasLibs p = maybe False (buildable . libBuildInfo) (library p)
+
+-- |'Maybe' version of 'hasLibs'
+maybeHasLibs :: PackageDescription -> Maybe Library
+maybeHasLibs p =
+   library p >>= (\lib -> toMaybe (buildable (libBuildInfo lib)) lib)
+
+-- |If the package description has a library section, call the given
+--  function with the library build info as argument.
+withLib :: PackageDescription -> a -> (Library -> IO a) -> IO a
+withLib pkg_descr a f =
+   maybe (return a) f (maybeHasLibs pkg_descr)
hunk ./Distribution/PackageDescription.hs 300
+
+libFieldDescrs :: [FieldDescr Library]
+libFieldDescrs = map biToLib binfoFieldDescrs
+  ++ [
+      listField "exposed-modules" text parseModuleNameQ
+	 exposedModules (\mods lib -> lib{exposedModules=mods})
+     ]
+  where biToLib = liftField libBuildInfo (\bi lib -> lib{libBuildInfo=bi})
+
+-- ---------------------------------------------------------------------------
+-- The Executable type
+
+data Executable = Executable {
+        exeName    :: String,
+        modulePath :: FilePath,
+        buildInfo  :: BuildInfo
+    }
+    deriving (Show, Read, Eq)
+
+emptyExecutable :: Executable
+emptyExecutable = Executable {
+                      exeName = "",
+                      modulePath = "",
+                      buildInfo = emptyBuildInfo
+                     }
+
+-- | Perform the action on each buildable 'Executable' in the package
+-- description.
+withExe :: PackageDescription -> (Executable -> IO a) -> IO ()
+withExe pkg_descr f =
+  sequence_ [f exe | exe <- executables pkg_descr, buildable (buildInfo exe)]
hunk ./Distribution/PackageDescription.hs 337
--- |does this package have any libraries?
-hasLibs :: PackageDescription -> Bool
-hasLibs p = maybe False (buildable . libBuildInfo) (library p)
+executableFieldDescrs :: [FieldDescr Executable]
+executableFieldDescrs = 
+  [ -- note ordering: configuration must come first, for
+    -- showPackageDescription.
+    simpleField "executable"
+                           showFreeText       (munch (const True))
+                           exeName            (\xs    exe -> exe{exeName=xs})
+  , simpleField "main-is"
+                           showFilePath       parseFilePathQ
+                           modulePath         (\xs    exe -> exe{modulePath=xs})
+  ]
+  ++ map biToExe binfoFieldDescrs
+  where biToExe = liftField buildInfo (\bi exe -> exe{buildInfo=bi})
hunk ./Distribution/PackageDescription.hs 351
--- |'Maybe' version of 'hasLibs'
-maybeHasLibs :: PackageDescription -> Maybe Library
-maybeHasLibs p =
-   library p >>= (\lib -> toMaybe (buildable (libBuildInfo lib)) lib)
+-- ---------------------------------------------------------------------------
+-- The BuildInfo type
hunk ./Distribution/PackageDescription.hs 370
-        ghcProfOptions       :: [String]
+        ghcProfOptions    :: [String]
hunk ./Distribution/PackageDescription.hs 391
-                     }
-
-data Executable = Executable {
-        exeName    :: String,
-        modulePath :: FilePath,
-        buildInfo  :: BuildInfo
-    }
-    deriving (Show, Read, Eq)
-
-emptyExecutable :: Executable
-emptyExecutable = Executable {
-                      exeName = "",
-                      modulePath = "",
-                      buildInfo = emptyBuildInfo
hunk ./Distribution/PackageDescription.hs 392
-
--- | Perform the action on each buildable 'Executable' in the package
--- description.
-withExe :: PackageDescription -> (Executable -> IO a) -> IO ()
-withExe pkg_descr f =
-  sequence_ [f exe | exe <- executables pkg_descr, buildable (buildInfo exe)]
hunk ./Distribution/PackageDescription.hs 397
+
+binfoFieldDescrs :: [FieldDescr BuildInfo]
+binfoFieldDescrs =
+ [ simpleField "buildable"
+           (text . show)      parseReadS
+           buildable          (\val binfo -> binfo{buildable=val})
+ , listField "cc-options"
+           showToken          parseTokenQ
+           ccOptions          (\val binfo -> binfo{ccOptions=val})
+ , listField "ld-options"
+           showToken          parseTokenQ
+           ldOptions          (\val binfo -> binfo{ldOptions=val})
+ , listField "frameworks"
+           showToken          parseTokenQ
+           frameworks         (\val binfo -> binfo{frameworks=val})
+ , listField   "c-sources"
+           showFilePath       parseFilePathQ
+           cSources           (\paths binfo -> binfo{cSources=paths})
+ , listField   "extensions"
+           (text . show)      parseExtensionQ
+           extensions         (\exts  binfo -> binfo{extensions=exts})
+ , listField   "extra-libraries"
+           showToken          parseTokenQ
+           extraLibs          (\xs    binfo -> binfo{extraLibs=xs})
+ , listField   "extra-lib-dirs"
+           showFilePath       parseFilePathQ
+           extraLibDirs       (\xs    binfo -> binfo{extraLibDirs=xs})
+ , listField   "includes"
+           showFilePath       parseFilePathQ
+           includes           (\paths binfo -> binfo{includes=paths})
+ , listField   "install-includes"
+           showFilePath       parseFilePathQ
+           installIncludes    (\paths binfo -> binfo{installIncludes=paths})
+ , listField   "include-dirs"
+           showFilePath       parseFilePathQ
+           includeDirs        (\paths binfo -> binfo{includeDirs=paths})
+ , listField   "hs-source-dirs"
+           showFilePath       parseFilePathQ
+           hsSourceDirs       (\paths binfo -> binfo{hsSourceDirs=paths})
+ , listField   "other-modules"         
+           text               parseModuleNameQ
+           otherModules       (\val binfo -> binfo{otherModules=val})
+ , listField   "ghc-prof-options"         
+           text               parseTokenQ
+           ghcProfOptions        (\val binfo -> binfo{ghcProfOptions=val})
+ , optsField   "ghc-options"  GHC
+           options            (\path  binfo -> binfo{options=path})
+ , optsField   "hugs-options" Hugs
+           options            (\path  binfo -> binfo{options=path})
+ , optsField   "nhc-options"  NHC
+           options            (\path  binfo -> binfo{options=path})
+ , optsField   "jhc-options"  JHC
+           options            (\path  binfo -> binfo{options=path})
+ ]
+
+-- ----------------------------------------------------------------------
+-- Configurations
+
+data Configuration = Configuration {
+  configCond		:: Cond,
+  configBuildDepends	:: [Dependency],
+  configBuildInfo	:: BuildInfo
+ } deriving (Show, Read, Eq)
+
+emptyConfiguration = Configuration {
+  configCond		= error "configCond",
+  configBuildDepends	= [],
+  configBuildInfo	= emptyBuildInfo
+ }
+
+configFieldDescrs :: [FieldDescr Configuration]
+configFieldDescrs = 
+  [   -- note ordering: configuration must come first, for
+      -- showPackageDescription.
+      simpleField "configuration" showCond parseCond
+         configCond (\cond conf -> conf{configCond = cond}),
+
+      commaListField  "build-depends" showDependency parseDependency
+               configBuildDepends (\xs conf -> conf{configBuildDepends = xs})
+  ]
+  ++ map biToConfig binfoFieldDescrs
+  where biToConfig = liftField configBuildInfo 
+                                (\bi conf -> conf{configBuildInfo=bi})
+
+-- ----------------------------------------------------------------------
+-- Conditionals
+
+data Cond
+  = CEnabled String
+  | CPackage Dependency VersionRange
+  | COS String
+  | CArch String
+  | CNot Cond
+  | CAnd Cond Cond
+  | COr  Cond Cond
+  deriving (Show, Read, Eq)
+
+showCond :: Cond -> Doc
+showCond (CAnd c1 c2) = 
+  showCond1 c1 <> comma <+> showCond c2
+showCond c = showCond1 c
+
+showCond1 (COr c1 c2) = 
+  showCond2 c1 <+> Pretty.char '|' <+> showCond1 c2
+showCond1 c = showCond2 c
+
+showCond2 (CEnabled s) = text s
+showCond2 (CPackage (Dependency p vr1) vr2) = text "package" <> 
+	parens (text (show p) <> text (showVersionRange vr1)
+		 <> comma <> text (showVersionRange vr2))
+showCond2 (COS s)   = text "os" <> parens (text s)
+showCond2 (CArch s) = text "arch" <> parens (text s)
+showCond2 (CNot s) = Pretty.char '!' <> showCond2 s
+showCond2 c         = parens (showCond c)
+
+condUserSymbols :: Cond -> [String]
+condUserSymbols (CEnabled s) = [s]
+condUserSymbols (CNot c) = condUserSymbols c
+condUserSymbols (CAnd c1 c2) = condUserSymbols c1 ++ condUserSymbols c2
+condUserSymbols (COr c1 c2) = condUserSymbols c1 ++ condUserSymbols c2
+
+parseCond :: ReadP Cond Cond
+parseCond = cc0
+  where  
+  cc0 = 
+    cc1 <++ (do cs <- parseSepList (ReadP.string "||") cc0
+	        return (foldr1 COr cs))
+  cc1 = 
+    cc2 <++ (do cs <- parseSepList (ReadP.string "&&") cc0
+	        return (foldr1 CAnd cs))
+  cc2 =
+	CEnabled `liftM` symbol
+           <++ (do ReadP.char '!'; c <- cc0; return (CNot c))
+	   <++ (do ReadP.string "os"; skipSpaces; COS `liftM` pparens symbol)
+	   <++ (do ReadP.string "arch"; skipSpaces; CArch `liftM` pparens symbol)
+	   <++ (do ReadP.string "package"; 
+		   skipSpaces
+		   pparens (pkg1 <++ pkg2))
+
+  pkg1 = do d <- parseDependency; return (CPackage d AnyVersion)
+  pkg2 = do d <- parseDependency
+	    skipSpaces; ReadP.char ','; skipSpaces
+	    v <- parseVersionRange
+	    return (CPackage d v)
+
+  symbol = munch1 (\x -> not (isSpace x) && x `notElem` "()|,!")
+
+pparens p = between (ReadP.char '(') (ReadP.char ')') 
+		(do skipSpaces; x <- p; skipSpaces; return x)
+
hunk ./Distribution/PackageDescription.hs 551
-
--- |If the package description has a library section, call the given
---  function with the library build info as argument.
-withLib :: PackageDescription -> a -> (Library -> IO a) -> IO a
-withLib pkg_descr a f =
-   maybe (return a) f (maybeHasLibs pkg_descr)
hunk ./Distribution/PackageDescription.hs 552
-setupMessage :: String -> PackageDescription -> IO ()
-setupMessage msg pkg_descr = 
-   putStrLn (msg ++ ' ':showPackageId (package pkg_descr) ++ "...")
+satisfyDependency :: [PackageIdentifier] -> Dependency
+	-> Maybe PackageIdentifier
+satisfyDependency pkgs (Dependency pkgname vrange) =
+  case filter ok pkgs of
+    [] -> Nothing 
+    qs -> Just (maximumBy versions qs)
+  where
+	ok p = pkgName p == pkgname && pkgVersion p `withinRange` vrange
+        versions a b = pkgVersion a `compare` pkgVersion b
hunk ./Distribution/PackageDescription.hs 628
-
--- ------------------------------------------------------------
--- * Parsing & Pretty printing
--- ------------------------------------------------------------
-
--- the strings for the required fields are necessary here, and so we
--- don't repeat ourselves, I name them:
-
-reqNameName       = "name"
-reqNameVersion    = "version"
-reqNameCopyright  = "copyright"
-reqNameMaintainer = "maintainer"
-reqNameSynopsis   = "synopsis"
-
-basicStanzaFields :: [StanzaField PackageDescription]
-basicStanzaFields =
- [ simpleField reqNameName
-                           text                   parsePackageName
-                           (pkgName . package)    (\name pkg -> pkg{package=(package pkg){pkgName=name}})
- , simpleField reqNameVersion
-                           (text . showVersion)   parseVersion
-                           (pkgVersion . package) (\ver pkg -> pkg{package=(package pkg){pkgVersion=ver}})
- , simpleField "cabal-version"
-                           (text . showVersionRange) parseVersionRange
-                           descCabalVersion       (\v pkg -> pkg{descCabalVersion=v})
- , simpleField "license"
-                           (text . show)          parseLicenseQ
-                           license                (\l pkg -> pkg{license=l})
- , simpleField "license-file"
-                           showFilePath           parseFilePathQ
-                           licenseFile            (\l pkg -> pkg{licenseFile=l})
- , simpleField reqNameCopyright
-                           showFreeText           (munch (const True))
-                           copyright              (\val pkg -> pkg{copyright=val})
- , simpleField reqNameMaintainer
-                           showFreeText           (munch (const True))
-                           maintainer             (\val pkg -> pkg{maintainer=val})
- , commaListField  "build-depends"
-                           showDependency         parseDependency
-                           buildDepends           (\xs    pkg -> pkg{buildDepends=xs})
- , simpleField "stability"
-                           showFreeText           (munch (const True))
-                           stability              (\val pkg -> pkg{stability=val})
- , simpleField "homepage"
-                           showFreeText           (munch (const True))
-                           homepage               (\val pkg -> pkg{homepage=val})
- , simpleField "package-url"
-                           showFreeText           (munch (const True))
-                           pkgUrl                 (\val pkg -> pkg{pkgUrl=val})
- , simpleField reqNameSynopsis
-                           showFreeText           (munch (const True))
-                           synopsis               (\val pkg -> pkg{synopsis=val})
- , simpleField "description"
-                           showFreeText           (munch (const True))
-                           description            (\val pkg -> pkg{description=val})
- , simpleField "category"
-                           showFreeText           (munch (const True))
-                           category               (\val pkg -> pkg{category=val})
- , simpleField "author"
-                           showFreeText           (munch (const True))
-                           author                 (\val pkg -> pkg{author=val})
- , listField "tested-with"
-                           showTestedWith         parseTestedWithQ
-                           testedWith             (\val pkg -> pkg{testedWith=val})
- , listField "data-files"  showFilePath           parseFilePathQ
-                           dataFiles              (\val pkg -> pkg{dataFiles=val})
- , listField "extra-source-files" showFilePath    parseFilePathQ
-                           extraSrcFiles          (\val pkg -> pkg{extraSrcFiles=val})
- , listField "extra-tmp-files" showFilePath       parseFilePathQ
-                           extraTmpFiles          (\val pkg -> pkg{extraTmpFiles=val})
- ]
-
-executableStanzaFields :: [StanzaField Executable]
-executableStanzaFields =
- [ simpleField "executable"
-                           showFreeText       (munch (const True))
-                           exeName            (\xs    exe -> exe{exeName=xs})
- , simpleField "main-is"
-                           showFilePath       parseFilePathQ
-                           modulePath         (\xs    exe -> exe{modulePath=xs})
- ]
-
-binfoFields :: [StanzaField BuildInfo]
-binfoFields =
- [ simpleField "buildable"
-                           (text . show)      parseReadS
-                           buildable          (\val binfo -> binfo{buildable=val})
- , listField "cc-options"
-                           showToken          parseTokenQ
-                           ccOptions          (\val binfo -> binfo{ccOptions=val})
- , listField "ld-options"
-                           showToken          parseTokenQ
-                           ldOptions          (\val binfo -> binfo{ldOptions=val})
- , listField "frameworks"
-                           showToken          parseTokenQ
-                           frameworks         (\val binfo -> binfo{frameworks=val})
- , listField   "c-sources"
-                           showFilePath       parseFilePathQ
-                           cSources           (\paths binfo -> binfo{cSources=paths})
- , listField   "extensions"
-                           (text . show)      parseExtensionQ
-                           extensions         (\exts  binfo -> binfo{extensions=exts})
- , listField   "extra-libraries"
-                           showToken          parseTokenQ
-                           extraLibs          (\xs    binfo -> binfo{extraLibs=xs})
- , listField   "extra-lib-dirs"
-                           showFilePath       parseFilePathQ
-                           extraLibDirs       (\xs    binfo -> binfo{extraLibDirs=xs})
- , listField   "includes"
-                           showFilePath       parseFilePathQ
-                           includes           (\paths binfo -> binfo{includes=paths})
- , listField   "install-includes"
-                           showFilePath       parseFilePathQ
-                           includes           (\paths binfo -> binfo{installIncludes=paths})
- , listField   "include-dirs"
-                           showFilePath       parseFilePathQ
-                           includeDirs        (\paths binfo -> binfo{includeDirs=paths})
- , listField   "hs-source-dirs"
-                           showFilePath       parseFilePathQ
-                           hsSourceDirs       (\paths binfo -> binfo{hsSourceDirs=paths})
- , listField   "other-modules"         
-                           text               parseModuleNameQ
-                           otherModules       (\val binfo -> binfo{otherModules=val})
- , listField   "ghc-prof-options"         
-                           text               parseTokenQ
-                           ghcProfOptions        (\val binfo -> binfo{ghcProfOptions=val})
- , optsField   "ghc-options"  GHC
-                           options            (\path  binfo -> binfo{options=path})
- , optsField   "hugs-options" Hugs
-                           options            (\path  binfo -> binfo{options=path})
- , optsField   "nhc-options"  NHC
-                           options            (\path  binfo -> binfo{options=path})
- , optsField   "jhc-options"  JHC
-                           options            (\path  binfo -> binfo{options=path})
- ]
hunk ./Distribution/PackageDescription.hs 629
+setupMessage :: String -> PackageDescription -> IO ()
+setupMessage msg pkg_descr = 
+   putStrLn (msg ++ ' ':showPackageId (package pkg_descr) ++ "...")
hunk ./Distribution/PackageDescription.hs 633
--- --------------------------------------------
--- ** Parsing
+-- ---------------------------------------------------------------
+-- Parsing
hunk ./Distribution/PackageDescription.hs 650
-
--- |Parse the given package file.
-readPackageDescription :: FilePath -> IO PackageDescription
-readPackageDescription = readAndParseFile parseDescription 
hunk ./Distribution/PackageDescription.hs 653
+
+-- |Parse the given package file.
+readPackageDescription :: FilePath -> IO PackageDescription
+readPackageDescription = readAndParseFile parseDescription
hunk ./Distribution/PackageDescription.hs 659
-parseDescription inp = do (st:sts) <- splitStanzas inp
-                          pkg <- foldM (parseBasicStanza basicStanzaFields) emptyPackageDescription st
-                          exes <- mapM parseExecutableStanza sts
-                          return pkg{executables=exes}
-  where -- The basic stanza, with library building info
-        parseBasicStanza ((StanzaField name _ set):fields) pkg (lineNo, f, val)
-          | name == f = set lineNo val pkg
-          | otherwise = parseBasicStanza fields pkg (lineNo, f, val)
-          {-     
-     , listField   "exposed-modules"
-                           text               parseModuleNameQ
-                           (\p -> maybe [] exposedModules (library p))
-                           (\xs    pkg -> let lib = fromMaybe emptyLibrary (library pkg) in
-                                              pkg{library = Just lib{exposedModules=xs}})
--}
-        parseBasicStanza [] pkg (lineNo, f, val)
-          | "exposed-modules" == f = do
-               mods <- runP lineNo f (parseOptCommaList parseModuleNameQ) val
-               return pkg{library=Just lib{exposedModules=mods}}
-          | otherwise = do
-               bi <- parseBInfoField binfoFields (libBuildInfo lib) (lineNo, f, val)
-               return pkg{library=Just lib{libBuildInfo=bi}}
-          where
-            lib = fromMaybe emptyLibrary (library pkg)
+parseDescription str = do 
+  all_fields0 <- readFields str
+  all_fields <- mapM deprecField all_fields0
+  let (st:sts) = stanzas all_fields
+  pkg <- parseFields basic_field_descrs emptyPackageDescription st
+  foldM parseExtraStanza pkg sts
+  where
+        parseExtraStanza pkg st@((lineNo, "executable",eName):_) = do
+		exe <- parseFields executableFieldDescrs emptyExecutable st
+		return pkg{executables= executables pkg ++ [exe]}
+        parseExtraStanza pkg st@((lineNo, "configuration",eName):_) = do
+		cf <- parseFields configFieldDescrs emptyConfiguration st
+		return pkg{configurations = configurations pkg ++ [cf]}
+        parseExtraStanza _ x = error ("This shouldn't happen!" ++ show x)
+
+basic_field_descrs = pkgDescrFieldDescrs ++ map liftToPkg libFieldDescrs
+  where liftToPkg = liftField (fromMaybe emptyLibrary . library)
+			      (\lib pkg -> pkg{library = Just lib})
+
+stanzas :: [Field] -> [[Field]]
+stanzas [] = []
+stanzas (f:fields) = (f:this) : stanzas rest
+  where (this, rest) = break isStanzaHeader fields
+
+isStanzaHeader (_,f,_) = f `elem` ["executable", "configuration"]
hunk ./Distribution/PackageDescription.hs 685
-        parseExecutableStanza st@((lineNo, "executable",eName):_) =
-          case lookupField "main-is" st of
-            Just (_,_) -> foldM (parseExecutableField executableStanzaFields) emptyExecutable st
-            Nothing    -> syntaxError lineNo $ "No 'Main-Is' field found for " ++ eName ++ " stanza"
-        parseExecutableStanza ((lineNo, f,_):_) = 
-          syntaxError lineNo $ "'Executable' stanza starting with field '" ++ f ++ "'"
-        parseExecutableStanza _ = error "This shouldn't happen!"
+parseFields :: [FieldDescr a] -> a  -> [Field] -> ParseResult a
+parseFields descrs init fields = foldM (parseField descrs) init fields
hunk ./Distribution/PackageDescription.hs 688
-        parseExecutableField ((StanzaField name _ set):fields) exe (lineNo, f, val)
-          | name == f = set lineNo val exe
-          | otherwise = parseExecutableField fields exe (lineNo, f, val)
-        parseExecutableField [] exe (lineNo, f, val) = do
-          binfo <- parseBInfoField binfoFields (buildInfo exe) (lineNo, f, val)
-          return exe{buildInfo=binfo}
+parseField :: [FieldDescr a] -> a -> Field -> ParseResult a
+parseField ((FieldDescr name _ parse):fields) a (lineNo, f, val)
+  | name == f = parse lineNo val a
+  | otherwise = parseField fields a (lineNo, f, val)
+-- ignore "x-" extension fields without a warning
+parseField [] a (lineNo, 'x':'-':f, _) = return a
+parseField [] a (lineNo, f, _) = do
+          warning $ "Unknown field '" ++ f ++ "'"
+          return a
hunk ./Distribution/PackageDescription.hs 698
-        -- ...
-        lookupField :: String -> Stanza -> Maybe (LineNo,String)
-        lookupField x sts = lookup x (map (\(n,f,v) -> (f,(n,v))) sts)
+-- Handle deprecated fields
+deprecField (line,fld,val) = do
+  fld' <- case fld of
+	     "hs-source-dir"
+		-> do warning "The field \"hs-source-dir\" is deprecated, please use hs-source-dirs."
+		      return "hs-source-dirs"
+	     "other-files"
+		-> do warning "The field \"other-files\" is deprecated, please use extra-source-files."
+		      return "extra-source-files"
+	     _ -> return fld
+  return (line,fld',val)
hunk ./Distribution/PackageDescription.hs 713
-  stanzas@(mLibStr:exes) <- splitStanzas inp
-  mLib <- parseLib mLibStr
-  biExes <- mapM parseExe (maybe stanzas (const exes) mLib)
+  fields <- readFields inp
+  let ss@(mLibFields:exes) = stanzas fields
+  mLib <- parseLib mLibFields
+  biExes <- mapM parseExe (maybe ss (const exes) mLib)
hunk ./Distribution/PackageDescription.hs 719
-    parseLib :: Stanza -> ParseResult (Maybe BuildInfo)
+    parseLib :: [Field] -> ParseResult (Maybe BuildInfo)
hunk ./Distribution/PackageDescription.hs 723
-    parseExe :: Stanza -> ParseResult (String, BuildInfo)
+
+    parseExe :: [Field] -> ParseResult (String, BuildInfo)
hunk ./Distribution/PackageDescription.hs 731
-    parseBI :: Stanza -> ParseResult BuildInfo
-    parseBI st = foldM (parseBInfoField binfoFields) emptyBuildInfo st
hunk ./Distribution/PackageDescription.hs 732
-parseBInfoField :: [StanzaField a] -> a -> (LineNo, String, String) -> ParseResult a
-parseBInfoField ((StanzaField name _ set):fields) binfo (lineNo, f, val)
-          | name == f = set lineNo val binfo
-          | otherwise = parseBInfoField fields binfo (lineNo, f, val)
--- ignore "x-" extension fields without a warning
-parseBInfoField [] binfo (lineNo, 'x':'-':f, _) = return binfo
-parseBInfoField [] binfo (lineNo, f, _) = do
-          warning $ "Unknown field '" ++ f ++ "'"
-          return binfo
+    parseBI st = parseFields binfoFieldDescrs emptyBuildInfo st
hunk ./Distribution/PackageDescription.hs 734
--- --------------------------------------------
--- ** Pretty printing
+-- ---------------------------------------------------------------------------
+-- Pretty printing
hunk ./Distribution/PackageDescription.hs 742
-  ppFields pkg basicStanzaFields $$
+  ppFields pkg pkgDescrFieldDescrs $$
hunk ./Distribution/PackageDescription.hs 745
-     Just lib -> 
-        text "exposed-modules" <> colon <+> fsep (punctuate comma (map text (exposedModules lib))) $$
-        ppFields (libBuildInfo lib) binfoFields) $$
-  vcat (map ppExecutable (executables pkg))
+     Just lib -> ppFields lib libFieldDescrs) $$
+  vcat (map ppExecutable (executables pkg)) $$
+  vcat (map ppConfiguration (configurations pkg))
hunk ./Distribution/PackageDescription.hs 749
-    ppExecutable exe =
-      space $$
-      ppFields exe executableStanzaFields $$
-      ppFields (buildInfo exe) binfoFields
-
-    ppFields _ [] = empty
-    ppFields pkg' ((StanzaField name get _):flds) =
-           ppField name (get pkg') $$ ppFields pkg' flds
-
-ppField name field = text name <> colon <+> field
+    ppExecutable exe = space $$ ppFields exe executableFieldDescrs
+    ppConfiguration exe = space $$ ppFields exe configFieldDescrs
hunk ./Distribution/PackageDescription.hs 759
-     Just bi -> ppFields bi binfoFields) $$
+     Just bi -> ppFields bi binfoFieldDescrs) $$
hunk ./Distribution/PackageDescription.hs 765
-      ppFields bi binfoFields
+      ppFields bi binfoFieldDescrs
hunk ./Distribution/PackageDescription.hs 767
-    ppFields _  [] = empty
-    ppFields bi ((StanzaField name get _):flds) =
-           ppField name (get bi) $$ ppFields bi flds
+ppFields _ [] = empty
+ppFields pkg' ((FieldDescr name get _):flds) =
+     ppField name (get pkg') $$ ppFields pkg' flds
hunk ./Distribution/PackageDescription.hs 771
+ppField name field = text name <> colon <+> field
hunk ./Distribution/PackageDescription.hs 798
-
-         in return $ (catMaybes [nothingToDo, noModules,
-                                 allRights, noLicenseFile]
-                     ,catMaybes $ libSane:goodCabal:(checkMissingFields pkg_descr))
-
--- |Output warnings and errors. Exit if any errors.
-errorOut :: [String]  -- ^Warnings
-         -> [String]  -- ^errors
-         -> IO ()
-errorOut warnings errors = do
-  mapM warn warnings
-  when (not (null errors)) $ do
-    pname <- getProgName
-    mapM (hPutStrLn stderr . ((pname ++ ": Error: ") ++)) errors
-    exitWith (ExitFailure 1)
+         in return $ ( catMaybes [nothingToDo, noModules, allRights, noLicenseFile],
+                       catMaybes (libSane:goodCabal: checkMissingFields pkg_descr
+			  ++ map sanityCheckExe (executables pkg_descr)) )
hunk ./Distribution/PackageDescription.hs 822
+
+sanityCheckExe :: Executable -> Maybe String
+sanityCheckExe exe
+   = if null (modulePath exe)
+	then Just ("No 'Main-Is' field found for executable " ++ exeName exe)
+	else Nothing
hunk ./Distribution/PackageDescription.hs 890
+        "Hugs-Options: ",
+        "Nhc-Options: ",
+        "Jhc-Options: ",
+	"",
+	"configuration: debug",
+	"ghc-options: -DDEBUG",
hunk ./Distribution/PackageDescription.hs 926
+		    configurations=[
+			Configuration {
+				configCond = CEnabled "debug",
+				configBuildDepends = [], 
+				configBuildInfo = BuildInfo {
+					buildable = True, 
+					ccOptions = [], 
+					ldOptions = [], 
+					frameworks = [], 
+					cSources = [], 
+					hsSourceDirs = ["."], 
+					otherModules = [], 
+					extensions = [], 
+					extraLibs = [], 
+					extraLibDirs = [], 
+					includeDirs = [], 
+					includes = [], 
+					installIncludes = [], 
+		                        options = [(GHC,["-DDEBUG"]),(Hugs,[]),(NHC,[]),(JHC,[])],
+					ghcProfOptions = []}
+			}],
hunk ./Distribution/PackageDescription.hs 966
-                           -- Note reversed order:
hunk ./Distribution/PackageDescription.hs 967
-                           options = [(JHC,[]),(NHC, []), (Hugs,["+TH"]), (GHC,["-fTH","-fglasgow-exts"])]}
-                    },
+                           options = [(GHC,["-fTH","-fglasgow-exts"]),(Hugs,["+TH"]),(NHC,[]),(JHC,[])]
+                    }},
hunk ./Distribution/PackageDescription.hs 975
-                        options = [(JHC,[]),(NHC,[]),(Hugs,[]),(GHC,[])]
+                        options = [(GHC,[]),(Hugs,[]),(NHC,[]),(JHC,[])]
hunk ./Distribution/PackageDescription.hs 977
-}
+  }
hunk ./Distribution/PackageDescription.hs 1009
-                                                         (parseDescription testPkgDesc),
+                                               (parseDescription testPkgDesc),
hunk ./Distribution/PackageDescription.hs 1018
-                                                ++"   Incorrect fields:"
-                                                ++ (show $ comparePackageDescriptions d d'))
+                                                ++"   Incorrect fields:\n"
+                                                ++ (unlines $ comparePackageDescriptions d d'))
hunk ./Distribution/PackageDescription.hs 1032
-    = catMaybes $ myCmp package "package" : myCmp license "license": myCmp licenseFile "licenseFile":  myCmp copyright "copyright":  myCmp maintainer "maintainer":  myCmp author "author":  myCmp stability "stability":  myCmp testedWith "testedWith":  myCmp homepage "homepage":  myCmp pkgUrl "pkgUrl":  myCmp synopsis "synopsis":  myCmp description "description":  myCmp category "category":  myCmp buildDepends "buildDepends":  myCmp library "library":  myCmp executables "executables": myCmp descCabalVersion "cabal-version":[]
-
-
-      where myCmp :: (Eq a, Show a) => (PackageDescription -> a)
+    = catMaybes $ myCmp package          "package" 
+                : myCmp license          "license"
+                : myCmp licenseFile      "licenseFile"
+                : myCmp copyright        "copyright"
+                : myCmp maintainer       "maintainer"
+                : myCmp author           "author"
+                : myCmp stability        "stability"
+                : myCmp testedWith       "testedWith"
+                : myCmp homepage         "homepage"
+                : myCmp pkgUrl           "pkgUrl"
+                : myCmp synopsis         "synopsis"
+                : myCmp description      "description"
+                : myCmp category         "category"
+                : myCmp buildDepends     "buildDepends"
+                : myCmp library          "library"
+                : myCmp executables      "executables"
+                : myCmp descCabalVersion "cabal-version"
+                : myCmp configurations   "configurations" : []
+      where canon_p1 = canonOptions p1
+            canon_p2 = canonOptions p2
+        
+            myCmp :: (Eq a, Show a) => (PackageDescription -> a)
hunk ./Distribution/PackageDescription.hs 1056
-            myCmp f er = let e1 = f p1
-                             e2 = f p2
+            myCmp f er = let e1 = f canon_p1
+                             e2 = f canon_p2
hunk ./Distribution/PackageDescription.hs 1061
+
+canonOptions :: PackageDescription -> PackageDescription
+canonOptions pd =
+   pd{ library = fmap canonLib (library pd),
+       executables = map canonExe (executables pd) }
+  where
+        canonLib l = l { libBuildInfo = canonBI (libBuildInfo l) }
+        canonExe e = e { buildInfo = canonBI (buildInfo e) }
+
+        canonBI bi = bi { options = canonOptions (options bi) }
+
+        canonOptions opts = sortBy (comparing fst) opts
+
+        comparing f a b = f a `compare` f b
hunk ./Distribution/PackageDescription.hs 1087
+
hunk ./Distribution/ParseUtils.hs 47
-        LineNo, PError(..), locatedErrorMsg, showError, syntaxError, warning,
+        LineNo, PError(..), locatedErrorMsg, syntaxError, warning,
hunk ./Distribution/ParseUtils.hs 49
-	StanzaField(..), splitStanzas, Stanza, singleStanza,
+	Field,
+	FieldDescr(..), readFields,
hunk ./Distribution/ParseUtils.hs 54
-	parseTestedWithQ, parseLicenseQ, parseExtensionQ, parseCommaList, parseOptCommaList,
+	parseTestedWithQ, parseLicenseQ, parseExtensionQ, 
+	parseSepList, parseCommaList, parseOptCommaList,
hunk ./Distribution/ParseUtils.hs 57
-	simpleField, listField, commaListField, optsField, 
+	field, simpleField, listField, commaListField, optsField, liftField,
hunk ./Distribution/ParseUtils.hs 61
-import Text.PrettyPrint.HughesPJ
hunk ./Distribution/ParseUtils.hs 67
+import Language.Haskell.Extension (Extension)
+
+import Text.PrettyPrint.HughesPJ
hunk ./Distribution/ParseUtils.hs 72
-import Language.Haskell.Extension (Extension)
+import Data.Maybe	( fromMaybe)
hunk ./Distribution/ParseUtils.hs 107
--- TODO: deprecated
-showError :: PError -> String
-showError e =
-  case locatedErrorMsg e of
-    (Just n,  s) -> "Line "++show n++": " ++ s
-    (Nothing, s) -> s
-
hunk ./Distribution/ParseUtils.hs 118
-data StanzaField a 
-  = StanzaField 
+data FieldDescr a 
+  = FieldDescr 
hunk ./Distribution/ParseUtils.hs 125
-simpleField :: String -> (a -> Doc) -> (ReadP a a) -> (b -> a) -> (a -> b -> b) -> StanzaField b
-simpleField name showF readF get set = StanzaField name
-   (\st -> showF (get st))
-   (\lineNo val st -> do
-       x <- runP lineNo name readF val
-       return (set x st))
+field :: String -> (a -> Doc) -> (ReadP a a) -> FieldDescr a
+field name showF readF = 
+  FieldDescr name showF (\lineNo val st -> runP lineNo name readF val)
hunk ./Distribution/ParseUtils.hs 129
-commaListField :: String -> (a -> Doc) -> (ReadP [a] a) -> (b -> [a]) -> ([a] -> b -> b) -> StanzaField b
-commaListField name showF readF get set = StanzaField name
-   (\st -> fsep (punctuate comma (map showF (get st))))
-   (\lineNo val st -> do
-       xs <- runP lineNo name (parseCommaList readF) val
-       return (set xs st))
+liftField :: (b -> a) -> (a -> b -> b) -> FieldDescr a -> FieldDescr b
+liftField get set (FieldDescr name showF parseF)
+ = FieldDescr name (\b -> showF (get b))
+	(\lineNo str b -> do
+	    a <- parseF lineNo str (get b)
+	    return (set a b))
hunk ./Distribution/ParseUtils.hs 136
-listField :: String -> (a -> Doc) -> (ReadP [a] a) -> (b -> [a]) -> ([a] -> b -> b) -> StanzaField b
-listField name showF readF get set = StanzaField name
-   (\st -> fsep (map showF (get st)))
-   (\lineNo val st -> do
-       xs <- runP lineNo name (parseOptCommaList readF) val
-       return (set xs st))
+simpleField name showF readF get set
+  = liftField get set $ field name showF readF
hunk ./Distribution/ParseUtils.hs 139
-optsField :: String -> CompilerFlavor -> (b -> [(CompilerFlavor,[String])]) -> ([(CompilerFlavor,[String])] -> b -> b) -> StanzaField b
-optsField name flavor get set = StanzaField name
-   (\st -> case lookup flavor (get st) of
-        Just args -> hsep (map text args)
-        Nothing   -> empty)
-   (\_ val st -> 
-       let
-         old_val  = get st
-         old_args = case lookup flavor old_val of
-                       Just args -> args
-                       Nothing   -> []
-         val'     = filter (\(f,_) -> f/=flavor) old_val
-       in return (set ((flavor,words val++old_args) : val') st))
+commaListField :: String -> (a -> Doc) -> (ReadP [a] a)
+		 -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr b
+commaListField name showF readF get set = 
+  liftField get set $ 
+    field name (fsep . punctuate comma . map showF) (parseCommaList readF)
hunk ./Distribution/ParseUtils.hs 145
-type Stanza = [(LineNo,String,String)]
+listField :: String -> (a -> Doc) -> (ReadP [a] a)
+		 -> (b -> [a]) -> ([a] -> b -> b) -> FieldDescr b
+listField name showF readF get set = 
+  liftField get set $ 
+    field name (fsep . map showF) (parseOptCommaList readF)
hunk ./Distribution/ParseUtils.hs 151
--- |Split a string into blank line-separated stanzas of
--- "Field: value" groups
-splitStanzas :: String -> ParseResult [Stanza]
-splitStanzas = mapM mkStanza . map merge . groupStanzas . filter validLine . zip [1..] . lines
-  where validLine (_,s) = case dropWhile isSpace s of
-                            '-':'-':_ -> False      -- Comment
-                            _         -> True
-        groupStanzas :: [(Int,String)] -> [[(Int,String)]]
-        groupStanzas [] = []
-        groupStanzas xs = let (ys,zs) = break allSpaces xs
-                           in ys : groupStanzas (dropWhile allSpaces zs)
+optsField :: String -> CompilerFlavor -> (b -> [(CompilerFlavor,[String])]) -> ([(CompilerFlavor,[String])] -> b -> b) -> FieldDescr b
+optsField name flavor get set = 
+   liftField (fromMaybe [] . lookup flavor . get) 
+	     (\opts b -> set (update flavor opts (get b)) b) $
+	field name (hsep . map text)
+		   (sepBy parseTokenQ' (munch1 isSpace))
+  where
+        update f opts [] = [(f,opts)]
+	update f opts ((f',opts'):rest)
+           | f == f'   = (f, opts ++ opts') : rest
+           | otherwise = (f',opts') : update f opts rest
hunk ./Distribution/ParseUtils.hs 163
-allSpaces :: (a, String) -> Bool
-allSpaces (_,xs) = all isSpace xs
+type Field  = (LineNo,String,String)
hunk ./Distribution/ParseUtils.hs 165
--- |Split a file into "Field: value" groups, but blank lines have no
--- significance, unlike 'splitStanzas'.  A field value may span over blank
--- lines.
-singleStanza :: String -> ParseResult Stanza
-singleStanza = mkStanza . merge . filter validLine . zip [1..] . lines
+-- |Split a file into "Field: value" groups
+readFields :: String -> ParseResult [Field]
+readFields = mkStanza . merge . filter validLine . zip [1..] . lines
hunk ./Distribution/ParseUtils.hs 181
-mkStanza :: [(Int,String)] -> ParseResult Stanza
+mkStanza :: [(Int,String)] -> ParseResult [Field]
hunk ./Distribution/ParseUtils.hs 183
+mkStanza ((n,'#':xs):ys) | not (isSpace (head xs)) = do
+  ss <- mkStanza ys
+  return ((n, '#':dir, dropWhile isSpace val) : ss)
+  where (dir,val) = break isSpace xs
hunk ./Distribution/ParseUtils.hs 189
-    (fld', ':':val) -> do
-       let fld'' = map toLower fld'
-       fld <- case () of
-                _ | fld'' == "hs-source-dir"
-                           -> do warning "The field \"hs-source-dir\" is deprecated, please use hs-source-dirs."
-                                 return "hs-source-dirs"
-                  | fld'' == "other-files"
-                           -> do warning "The field \"other-files\" is deprecated, please use extra-source-files."
-                                 return "extra-source-files"
-                  | otherwise -> return fld''
+    (fld0, ':':val) -> do
+       let fld = map toLower fld0
hunk ./Distribution/ParseUtils.hs 192
-       checkDuplField fld ss
hunk ./Distribution/ParseUtils.hs 194
-  where
-    checkDuplField _ [] = return ()
-    checkDuplField fld ((n',fld',_):xs')
-      | fld' == fld = syntaxError (max n n') $ "The field "++fld++" was already defined on line " ++ show (min n n')
-      | otherwise   = checkDuplField fld xs'
hunk ./Distribution/ParseUtils.hs 249
+parseTokenQ' :: ReadP r String
+parseTokenQ' = parseReadS <++ munch1 (\x -> not (isSpace x))
+
+parseSepList :: ReadP r b
+	     -> ReadP r a -- ^The parser for the stuff between commas
+             -> ReadP r [a]
+parseSepList sep p = sepBy p separator
+    where separator = skipSpaces >> sep >> skipSpaces
+
hunk ./Distribution/ParseUtils.hs 260
-parseCommaList p = sepBy p separator
-    where separator = skipSpaces >> ReadP.char ',' >> skipSpaces
+parseCommaList = parseSepList (ReadP.char ',')
hunk ./Distribution/ParseUtils.hs 263
-               -> ReadP r [a]
-parseOptCommaList p = sepBy p separator
-    where separator = skipSpaces >> optional (ReadP.char ',') >> skipSpaces
+                  -> ReadP r [a]
+parseOptCommaList = parseSepList (optional (ReadP.char ','))
hunk ./Distribution/Setup.hs 118
+
hunk ./Distribution/Setup.hs 141
+	configEnabled  :: [String],
+		-- ^ selected by --enable-* options to setup configure.
hunk ./Distribution/Setup.hs 172
+	configEnabled  = [],
hunk ./Distribution/Setup.hs 254
+	  | Enable String
+
hunk ./Distribution/Setup.hs 494
-parseConfigureArgs :: ProgramConfiguration -> ConfigFlags -> [String] -> [OptDescr a] ->
-                      IO (ConfigFlags, [a], [String])
-parseConfigureArgs progConf = parseArgs (configureCmd progConf) updateCfg
-  where updateCfg t GhcFlag              = t { configHcFlavor = Just GHC }
+parseConfigureArgs
+  :: ProgramConfiguration
+  -> ConfigFlags		-- initial flags
+  -> [String]			-- command line args
+  -> [String]			-- configuration names (from .cabal file)
+  -> [OptDescr a]		-- extra options from the caller
+  -> IO (ConfigFlags, [a], [String])
+parseConfigureArgs progConf flags args conf_syms customOpts
+  = parseArgs configureCmd' updateCfg flags args customOpts
+  where
+	cmd = configureCmd progConf
+	configureCmd' = cmd{ cmdOptions = cmdOptions cmd ++ enableOpts }
+
+	enableOpts = map enableOpt conf_syms
+	
+	enableOpt sym = 
+		Option "" ["enable-"++sym] (NoArg (Enable sym))
+		  ("enable configuration option " ++ sym)
+
+	updateCfg t GhcFlag              = t { configHcFlavor = Just GHC }
hunk ./Distribution/Setup.hs 546
+
+	updateCfg t (Enable opt)         = t { configEnabled = opt : configEnabled t }
+
hunk ./Distribution/Setup.hs 759
-      let flags' = filter (not.isLift) flags in
+     let flags' = filter (not.isLift) flags in
hunk ./Distribution/Simple.hs 89
-import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..))
+import Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..), distPref, 
+                                            srcPref, haddockPref )
hunk ./Distribution/Simple.hs 94
-                                  moduleToFilePath, findFile,
-                                  distPref, srcPref, haddockPref)
+                                  moduleToFilePath, findFile, warn)
hunk ./Distribution/Simple.hs 110
+import System.IO        ( hPutStrLn, stderr )
+import System.Environment ( getProgName )
hunk ./Distribution/Simple.hs 220
-defaultMain = getArgs >>=defaultMainArgs
+defaultMain = defaultMain__ Nothing Nothing Nothing
hunk ./Distribution/Simple.hs 222
+-- | A version of 'defaultMain' that is passed the command line
+-- arguments, rather than getting them from the environment.
hunk ./Distribution/Simple.hs 225
-defaultMainArgs args = do
-                 (action, args) <- parseGlobalArgs (allPrograms Nothing) args
-                 pkg_descr_file <- defaultPackageDesc
-                 pkg_descr <- readPackageDescription pkg_descr_file
-                 defaultMainWorker pkg_descr action args Nothing
-                 return ()
+defaultMainArgs args = defaultMain__ (Just args) Nothing Nothing
hunk ./Distribution/Simple.hs 229
-defaultMainWithHooks hooks
-    = do args <- getArgs
-         (action, args) <- parseGlobalArgs (allPrograms (Just hooks)) args
-         maybeDesc <- readDesc hooks
-         pkg_descr <- maybe (defaultPackageDesc >>= readPackageDescription)
-                            return maybeDesc
-         defaultMainWorker pkg_descr action args (Just hooks)
-         return ()
+defaultMainWithHooks hooks = defaultMain__ Nothing (Just hooks) Nothing
hunk ./Distribution/Simple.hs 234
-defaultMainNoRead pkg_descr
-    = do args <- getArgs
-         (action, args) <- parseGlobalArgs (allPrograms Nothing) args
-         defaultMainWorker pkg_descr action args Nothing
-         return ()
+defaultMainNoRead pkg_descr = defaultMain__ Nothing Nothing (Just pkg_descr)
+
+defaultMain__    :: Maybe [String]
+	         -> Maybe UserHooks
+		 -> Maybe PackageDescription
+		 -> IO ()
+defaultMain__ margs mhooks mdescr
+    = do args <- maybe getArgs return margs
+	 (action, args) <- parseGlobalArgs (allPrograms mhooks) args
+	 pkg_descr <- 
+		case mdescr of
+		    Just pkg_descr -> return pkg_descr
+		    Nothing -> 
+                        case mhooks of
+			    Nothing -> defaultPkgDescr
+			    Just h -> do
+				maybeDesc <- readDesc h
+				case maybeDesc of
+					Nothing -> defaultPkgDescr
+					Just p  -> return p
+         defaultMainWorker pkg_descr action args mhooks
+	 return ()
+  where
+	defaultPkgDescr = do
+		 pkg_descr_file <- defaultPackageDesc
+         	 cf <- readPackageDescription pkg_descr_file
+		 return cf
hunk ./Distribution/Simple.hs 292
+		let conf_syms = concat (map (condUserSymbols.configCond) 
+                                                (configurations pkg_descr_in))
hunk ./Distribution/Simple.hs 295
-			parseConfigureArgs (allPrograms hooks) flags args [buildDirOpt]
-                pkg_descr <- hookOrInArgs preConf args flags
+			parseConfigureArgs (allPrograms hooks) flags args
+				 conf_syms [buildDirOpt]
+                pkg_descr <- hookOrInArgs preConf args flags pkg_descr_in
hunk ./Distribution/Simple.hs 308
-                pkg_descr <- hookOrInArgs preBuild args flags
+                pkg_descr <- hookOrInArgs preBuild args flags pkg_descr_in
hunk ./Distribution/Simple.hs 316
-                pkg_descr <- hookOrInArgs preHaddock args verbose
+                pkg_descr <- hookOrInArgs preHaddock args verbose pkg_descr_in
hunk ./Distribution/Simple.hs 324
-                pkg_descr <- hookOrInArgs prePFE args verbose
+                pkg_descr <- hookOrInArgs prePFE args verbose pkg_descr_in
hunk ./Distribution/Simple.hs 332
-                pkg_descr <- hookOrInArgs preClean args verbose
+                pkg_descr <- hookOrInArgs preClean args verbose pkg_descr_in
hunk ./Distribution/Simple.hs 340
-                pkg_descr <- hookOrInArgs preCopy args flags
+                pkg_descr <- hookOrInArgs preCopy args flags pkg_descr_in
hunk ./Distribution/Simple.hs 348
-                pkg_descr <- hookOrInArgs preInst args flags
+                pkg_descr <- hookOrInArgs preInst args flags pkg_descr_in
hunk ./Distribution/Simple.hs 356
-                pkg_descr <- hookOrInArgs preSDist args flags
+                pkg_descr <- hookOrInArgs preSDist args flags pkg_descr_in
hunk ./Distribution/Simple.hs 373
-                pkg_descr <- hookOrInArgs preReg args flags
+                pkg_descr <- hookOrInArgs preReg args flags pkg_descr_in
hunk ./Distribution/Simple.hs 381
-                pkg_descr <- hookOrInArgs preUnreg args flags
+                pkg_descr <- hookOrInArgs preUnreg args flags pkg_descr_in
hunk ./Distribution/Simple.hs 389
-        hookOrInArgs :: (UserHooks -> ([String] -> b -> IO HookedBuildInfo))
+        hookOrInArgs :: (UserHooks -> [String] -> b -> IO HookedBuildInfo)
hunk ./Distribution/Simple.hs 392
+		     -> PackageDescription
hunk ./Distribution/Simple.hs 394
-        hookOrInArgs f a i
+        hookOrInArgs f args i pkg_descr
hunk ./Distribution/Simple.hs 396
-                    Nothing -> no_extra_flags a >> return pkg_descr_in
-                    Just h -> do pbi <- f h a i
-                                 return (updatePackageDescription pbi pkg_descr_in)
+                    Nothing -> no_extra_flags args >> return pkg_descr
+                    Just hooks -> do 
+			pbi <- f hooks args i
+                        return (updatePackageDescription pbi pkg_descr)
+
hunk ./Distribution/Simple.hs 701
+
+-- ------------------------------------------------------------
+-- * Utils
+-- ------------------------------------------------------------
+
+-- |Output warnings and errors. Exit if any errors.
+errorOut :: [String]  -- ^Warnings
+         -> [String]  -- ^errors
+         -> IO ()
+errorOut warnings errors = do
+  mapM warn warnings
+  when (not (null errors)) $ do
+    pname <- getProgName
+    mapM (hPutStrLn stderr . ((pname ++ ": Error: ") ++)) errors
+    exitWith (ExitFailure 1)
hunk ./Distribution/Simple/Configure.hs 75
-	BuildInfo(..), Executable(..), setupMessage )
+	BuildInfo(..), Executable(..), setupMessage, hasLibs,
+        satisfyDependency)
hunk ./Distribution/Simple/Configure.hs 138
-configure pkg_descr cfg
+configure pkg_descr0 cfg
hunk ./Distribution/Simple/Configure.hs 140
-	setupMessage "Configuring" pkg_descr
-	removeInstalledConfig
-        let lib = library pkg_descr
hunk ./Distribution/Simple/Configure.hs 143
+        -- FIXME: currently only GHC has hc-pkg
+        ipkgs <- case f' of
+                      GHC | ver >= Version [6,3] [] ->
+                        getInstalledPackagesAux comp cfg
+                      JHC ->
+                        getInstalledPackagesJHC comp cfg
+                      _ -> do
+                        return $ map setDepByVersion (buildDepends pkg_descr0)
+
+        -- ToDo: resolve configurations against set of installed packages.
+        let pkg_descr = pkg_descr0
+
+	setupMessage "Configuring" pkg_descr
+
+        dep_pkgs <- case f' of
+                      GHC | ver >= Version [6,3] [] -> do
+	                mapM (configDependency ipkgs) (buildDepends pkg_descr)
+                      JHC                           -> do
+	                mapM (configDependency ipkgs) (buildDepends pkg_descr)
+                      _                             -> do
+                        return $ map setDepByVersion (buildDepends pkg_descr)
+
+	
+
+	removeInstalledConfig
+
hunk ./Distribution/Simple/Configure.hs 188
+        let lib = library pkg_descr
hunk ./Distribution/Simple/Configure.hs 207
-        -- FIXME: currently only GHC has hc-pkg
-        dep_pkgs <- case f' of
-                      GHC | ver >= Version [6,3] [] -> do
-                        ipkgs <-  getInstalledPackagesAux comp cfg
-	                mapM (configDependency ipkgs) (buildDepends pkg_descr)
-                      JHC                           -> do
-                        ipkgs <-  getInstalledPackagesJHC comp cfg
-	                mapM (configDependency ipkgs) (buildDepends pkg_descr)
-                      _                             -> do
-                        return $ map setDepByVersion (buildDepends pkg_descr)
-
hunk ./Distribution/Simple/Configure.hs 225
+                              packagesAvail=ipkgs,
hunk ./Distribution/Simple/Configure.hs 236
-                              userConf=configUser cfg
+                              userConf=configUser cfg,
+                              enabled=configEnabled cfg
hunk ./Distribution/Simple/Configure.hs 320
-configDependency ps (Dependency pkgname vrange) = do
-  let
-	ok p = pkgName p == pkgname && pkgVersion p `withinRange` vrange
-  --
-  case filter ok ps of
-    [] -> die ("cannot satisfy dependency " ++ 
+configDependency ps dep@(Dependency pkgname vrange) =
+  case satisfyDependency ps dep of
+	Nothing -> die ("cannot satisfy dependency " ++ 
hunk ./Distribution/Simple/Configure.hs 324
-    qs -> let 
-	    pkg = maximumBy versions qs
-	    versions a b = pkgVersion a `compare` pkgVersion b
-	  in do message ("Dependency " ++ pkgname ++ showVersionRange vrange ++
-			 ": using " ++ showPackageId pkg)
+	Just pkg -> do
+		message ("Dependency " ++ pkgname ++ 
+			showVersionRange vrange ++
+		 	": using " ++ showPackageId pkg)
hunk ./Distribution/Simple/Install.hs 62
-        LocalBuildInfo(..), mkLibDir, mkBinDir, mkDataDir, mkProgDir, mkHaddockDir)
-import Distribution.Simple.Utils(copyFileVerbose, die, haddockPref,  copyDirectoryRecursiveVerbose)
+        LocalBuildInfo(..), mkLibDir, mkBinDir, mkDataDir, mkProgDir,
+        mkHaddockDir, haddockPref)
+import Distribution.Simple.Utils(copyFileVerbose, die, copyDirectoryRecursiveVerbose)
hunk ./Distribution/Simple/LocalBuildInfo.hs 56
-	distPref, srcPref, autogenModulesDir, mkIncludeDir
+	distPref, srcPref, haddockPref, autogenModulesDir, mkIncludeDir
hunk ./Distribution/Simple/LocalBuildInfo.hs 101
+	packagesAvail :: [PackageIdentifier],
+		-- ^ Which packages are installed.  This is used to
+		-- resolve conditionals in the .cabal file.
hunk ./Distribution/Simple/LocalBuildInfo.hs 116
-	splitObjs     :: Bool	-- ^Use -split-objs with GHC, if available
+	splitObjs     :: Bool,	-- ^Use -split-objs with GHC, if available
+	enabled       :: [String]	-- ^ --enable flags set
hunk ./Distribution/Simple/LocalBuildInfo.hs 129
+
+haddockPref :: FilePath
+haddockPref = foldl1 joinPaths [distPref, "doc", "html"]
hunk ./Distribution/Simple/Utils.hs 69
-        distPref,
-        haddockPref,
-        srcPref,
hunk ./Distribution/Simple/Utils.hs 313
-
--- ------------------------------------------------------------
--- * Some Paths
--- ------------------------------------------------------------
-distPref :: FilePath
-distPref = "dist"
-
-srcPref :: FilePath
-srcPref = distPref `joinFileName` "src"
-
-haddockPref :: FilePath
-haddockPref = foldl1 joinPaths [distPref, "doc", "html"]
}

[add docs to liftField (from Bertram Felgenhauer <int-e at gmx.de>)
Simon Marlow <simonmar at microsoft.com>**20060801081546] {
hunk ./Distribution/ParseUtils.hs 129
+-- | given @get@ and @set@ functions for a member of type @a@ of a record of
+-- type @b@, convert a @FieldDescr a@ to a @FieldDescr b at . For example:
+--
+-- @liftField fst (\a (_, b) -> (a, b)) :: FieldDescr a -> FieldDescr (a, b)@
}

[Add 'exposed' library field to allow installing hidden packages.
Simon Marlow <simonmar at microsoft.com>**20060801082838
 Patch originally by Bertram Felgenhauer <int-e at gmx.de>, merged
 relative to the configurations patch by me.  Also I updated the
 hunit test code to match.
] {
hunk ./Distribution/PackageDescription.hs 273
+        exposed           :: Bool,
hunk ./Distribution/PackageDescription.hs 279
-emptyLibrary = Library [] emptyBuildInfo
+emptyLibrary = Library [] True emptyBuildInfo
hunk ./Distribution/PackageDescription.hs 306
-	 exposedModules (\mods lib -> lib{exposedModules=mods})
+	 exposedModules (\mods lib -> lib{exposedModules=mods}),
+      simpleField "exposed"
+         (text . show)      parseReadS
+         exposed            (\val lib -> lib{exposed = val})
hunk ./Distribution/PackageDescription.hs 876
+        "exposed: False",
hunk ./Distribution/PackageDescription.hs 955
+                        exposed = False,
hunk ./Distribution/Simple/Register.hs 270
-        IPI.exposed           = True,
+        IPI.exposed           = exposed lib,
}

Context:

[pass the whole packageId to GHC with the -package-name flag
Simon Marlow <simonmar at microsoft.com>**20060720150931
 This shouldn't make any difference to current GHC's, but will be
 required by the new GHC package code.
] 
[install: pass the verbose flag to register too
Simon Marlow <simonmar at microsoft.com>**20060728085914] 
[Add documentation of new LocalBuildInfo fields
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060726230130] 
[Wrap excessively long line
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060726221702] 
[Hold back on forcing vanilla libs for TH for the moment
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060726221532
 When we get confirmation from GHC devs that it's the right
 thing to do then we can add it in.
] 
[Add initial support for --enable/disable-library-vanilla flags
jeremy.shaw at linspireinc.com**20060720174408
 For additional information see these mail threads:
 
 http://www.haskell.org//pipermail/libraries/2006-July/005522.html
 http://urchin.earth.li/pipermail/debian-haskell/2006-July/000220.html
] 
[build and install cabal-setup as part of GHC build
Simon Marlow <simonmar at microsoft.com>**20060720140417] 
[fix indentation in do block for H'98 compatibility
Malcolm.Wallace at cs.york.ac.uk**20060711162221] 
[resolve conflicts from henning-thielemann's work.  Thanks Henning!
ijones at syntaxpolice.org**20060708185016] 
[install Haddock documentation in share/package/doc/html and register that path in the ghc-pkg
cabal at henning-thielemann.de**20060609194058] 
[PackageDescription: haddockName generates the name of the .haddock file
cabal at henning-thielemann.de**20060609193924] 
[PackageDescription: added toMaybe, some logical simplifications
cabal at henning-thielemann.de**20060609193508] 
[Distribution.Simple.Utils: copyDirectoryRecursiveVerbose
cabal at henning-thielemann.de**20060609192715] 
[Distribution.Compat.Directory: added getDirectoryContentsWithoutSpecial
cabal at henning-thielemann.de**20060609192421] 
[Distribution.simple: haddock option --use-package tells which packages to hyperlink to
cabal at henning-thielemann.de**20060605183304] 
[stripPrefix -> dropPrefix
cabal at henning-thielemann.de**20060604195549] 
[generate .haddock interface file when running haddock
cabal at henning-thielemann.de**20060604195216] 
[UNDO: Merge "unrecognized long opt" fix from 6.4.2
Simon Marlow <simonmar at microsoft.com>**20060705142842
 This patch undid the previous patch, "merge from base".  I asked Sven
 to revert it, but didn't get an answer.
   
 See GHC bug #473.
] 
[Change flags passed to hsc2hs
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060704001926
 The extra-libraries must be passed as -L-l${lib} or linking the C prog
 that hsc2hs generates may fail if any symbols are referenced.
 Also can't use cppOptions function since hsc2hs doesn't support -U.
 Need to do -U flags in ccOptions seperately.
] 
[finish interaction with remote HTTP servers
audreyt at audreyt.org**20060624233156] 
[stage 2 patch: implement the "list" command
audreyt at audreyt.org**20060624231421] 
[it's now 00-latest not latest
audreyt at audreyt.org**20060624221907] 
[implement support for flat-file layout
audreyt at audreyt.org**20060624221547] 
[parsec is not a dependency
Simon Marlow <simonmar at microsoft.com>**20060518131434
 It is apparently required for the wash2hs test, however.
] 
[Merge "unrecognized long opt" fix from 6.4.2
Sven Panne <sven.panne at aedion.de>**20060506110640] 
[Cabal.xml: entity greencard was mixed up with haddock
cabal at henning-thielemann.de**20060411161212] 
[Change calls to 'make' into '$(MAKE)'
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060502174630
 This is the portable thing to do and fixes things on FreeBSD where make/=gmake
] 
[Hugs: copy paths module to the right place, this time
Ross Paterson <ross at soi.city.ac.uk>**20060503132510] 
[pass correct -P flag to ffihugs
Ross Paterson <ross at soi.city.ac.uk>**20060503122452
 
 The -P flag wasn't superfluous, but it was wrong for executables.
] 
[Hugs: copy path module into package build dir
Ross Paterson <ross at soi.city.ac.uk>**20060503122300] 
[add header file for GetModuleFileNameA
Ross Paterson <ross at soi.city.ac.uk>**20060502141641] 
[remove superfluous ffihugs -P option
Ross Paterson <ross at soi.city.ac.uk>**20060502104635] 
[fix for Hugs
Ross Paterson <ross at soi.city.ac.uk>**20060502101054
 
 Add explicit types for a couple of constants to work around Hugs's
 imperfect implementation of the monomorphism restriction.
] 
[TAG 1.1.4
duncan.coutts at worc.ox.ac.uk**20060502095901] 
[TAG shipped in GHC 6.4.2
Simon Marlow <simonmar at microsoft.com>**20060424093133] 
[Hugs: also compile the paths module
Ross Paterson <ross at soi.city.ac.uk>**20060501171206] 
[markup fix
Ross Paterson <ross at soi.city.ac.uk>**20060501145015] 
[move cabal-install/etc-cabal-get to cabal-install/etc-cabal-install
alson at alsonkemp.com**20060430175158] 
[Complete move of cabal-get to cabal-install + some fixups
alson at alsonkemp.com**20060430174300] 
[basic information for installing
ijones at syntaxpolice.org**20060430063205] 
[build and install cabal-setup
ijones at syntaxpolice.org**20060430063144] 
[add etc-cabal-get as a data-file
ijones at syntaxpolice.org**20060430055332] 
[bumping cabal version number. 1.1.4 will be the one released with ghc 6.4.2.
ijones at syntaxpolice.org**20060430044905] 
[modify makefile for cabal-install
ijones at syntaxpolice.org**20060430041617] 
[cabal-get will become cabal-install
ijones at syntaxpolice.org**20060430025633] 
[getting rid of cabal-install in favor of cabal-get
ijones at syntaxpolice.org**20060430024951] 
[Remove erroneous exports...
alson at alsonkemp.com**20060428195702] 
[Patch to fix "-ixyz" being overwritten by "-i" and to remove Cabal's dependency on the Cabal package.
alson at alsonkemp.com**20060428055353] 
[Separate build into "make build" and "make install"
alson at alsonkemp.com**20060428034151] 
[Fixups to get cabal-get into Cabal
alson at alsonkemp.com**20060428032617] 
[Update Cabal with cabal-get
alson at alsonkemp.com**20060427204050] 
[Fix JHC command lines.
Einar Karttunen <ekarttun at cs.helsinki.fi>**20060427005922] 
[document install-includes and register --inplace
Simon Marlow <simonmar at microsoft.com>**20060428130542] 
[fix imports for Windows
simonmar at microsoft.com**20060428075617] 
[Better support for packages that need to install header files
Simon Marlow <simonmar at microsoft.com>**20060426140627
 
 There's a new field for .cabal files: 
 
      install-includes: foo.h bar.h
 
 This means the same as 'includes', except that the files named therein
 will be installed into $libdir/include.  'includes' should only be
 used for headers already installed on the system.
 
 Directories listed in 'include-dirs' still turn into -I options for
 hsc2hs, cpphs, and C compilations.  However, for installation
 purposes, relative directories in 'include-dirs' are now treated
 differently from absolute directories:
 
   - an absolute directory is copied to the include-dirs field
     of the installed package config
 
   - files names in install-includes are assumed to be found in
     one of the *relative* directories listed in include-dirs
 
 So the common pattern for providing a header file that you want to
 be available everywhere including to via-C compilations against this
 package:
 
   include-dirs: myincludes
   install-includes: foo.h
 
 will install the header file myincludes/foo.h in
 $libdir/include/foo.h.
] 
[merge from base:
Simon Marlow <simonmar at microsoft.com>**20060426121408
 
 Wed Apr 26 13:11:10 BST 2006  Simon Marlow <simonmar at microsoft.com>
   * RequireOrder: do not collect unrecognised options after a non-opt
] 
[pass unrecognised options before the command name to the command
Simon Marlow <simonmar at microsoft.com>**20060426121321
 Previously, options before the command name other than --help were
 just ignored, which is quite confusing behaviour.  So now,
 
 ./setup --with-compiler=ghc-6.4.2 configure
 
 works as you expect, instead of ignoring the --with-compiler option.
] 
[First attempt at a cabal-setup command
Simon Marlow <simonmar at microsoft.com>**20060303162233
 cabal-setup is a replacement for 'runhaskell Setup.hs'.  It accepts
 exactly the same commands.  Additionally, the following new features
 are provided:
 
  * Setup.{hs,lhs} is optional.  If omitted, cabal-setup behaves just
    like Distribution.Simple.defaultMain.
 
  * If the .cabal file contains a cabal-version field, then Setup.hs
    is built using an appropriate version of Cabal.  This might entail
    creating Setup.hs if it doesn't exist.
 
  * cabal-setup interprets the options --with-compiler and --with-hc-pkg
    to determine the compiler used to compile Setup.hs.
 
 Later, we could add support for building multiple packages in
 dependency order, as per recent discussions on libraries at haskell.org.
] 
[add new modules
Ross Paterson <ross at soi.city.ac.uk>**20060425195548] 
[Implement "setup register --inplace", and a few other minor things
Simon Marlow <simonmar at microsoft.com>**20060425144733
  
 There are a few changes in this patch:
  
    - New flag to register, --inplace.  "setup register --inplace"
      registers the package for use in the build tree, i.e. without
      installing.  It works with GHC only, currently.
      
    - The parameters to RegisterCmd, UnregisterCmd and InstallCmd are a
      legacy from before the time of hooks (or something) and don't
      serve any purpose any more, AFAICT.  So I removed them.
  
    - I don't think "setup register" worked propertly before if
      --user was given to configure.  It does now.
 
    - New flag to register: --with-hc-pkg (just the same as when
      given to configure, but lets you override it at register-time)
] 
[Refactoring only: separate compiler-specific simple build implementation
Simon Marlow <simonmar at microsoft.com>**20060425111957] 
[get LocalBuildInfo from Distribution.LocalBuildInfo
Simon Marlow <simonmar at microsoft.com>**20060425111921] 
[warning cleanup
Simon Marlow <simonmar at microsoft.com>**20060425102302] 
[Distribution.Compat.FilePath should be hidden
Simon Marlow <simonmar at microsoft.com>**20060411141305
 This also matches package.conf.in.
] 
[Hide Distribution.GetOpt; it just re-exports System.Console.GetOpt anyway
Simon Marlow <simonmar at microsoft.com>**20060411141045
 This also matches Cabal.cabal.
] 
[GHC FFI flag should be -fffi not -ffi, the latter merely happens to work.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060318022010] 
[Make ghc-6.2 packages be exposed by default.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060221135026
 For ghc-6.4 when Cabal registers packages it exposes them by default.
 However it does not do the same fo ghc-6.2. This change corrects the
 discrepancy. This patch is already being used in Gentoo with Cabal 1.1.3.
] 
[test case for buildinfo with multiple executables
ijones at syntaxpolice.org**20060408213048] 
[It is no longer necessary to run 'configure' before 'clean' or 'sdist', addressing http://haskell.galois.com/trac/hackage/ticket/12.
Nick Alexander <ncalexan at uci.edu>**20060404054127
 In order to change this behaviour, it was necessary to modify the hook interface, specifically cleanHook, postClean, sDistHook, postSDist.  They now take a Maybe LocalBuildInfo, since a LocalBuildInfo might not be available in .setup-config.
] 
[windows patch from brian.mabry.edwards at gmail.com
ijones at syntaxpolice.org**20060404171731] 
[oops, don't enable -split-objs by default
Simon Marlow <simonmar at microsoft.com>**20060314124358] 
[export configDependency
Simon Marlow <simonmar at microsoft.com>**20060303155527] 
[comment fix
Simon Marlow <simonmar at microsoft.com>**20060303155516] 
[don't check cabal-version during parsing, it doesn't work
Simon Marlow <simonmar at microsoft.com>**20060303155500
 because parsers are evaluated multiple times due to backtracking.
] 
[no need to use a verbatim copy of System.Console.GetOpt, omit if possible
Simon Marlow <simonmar at microsoft.com>**20060303144025] 
[Support for -split-objs with GHC
Simon Marlow <simonmar at microsoft.com>**20060302170907
 New configure option: --enable-split-objs creates libraries using
 -split-objs with GHC (current HEAD or later only, the configure checks
 for version 6.5).  Fixes ticket #19.
] 
[Initial support for JHC
Einar Karttunen <ekarttun at cs.helsinki.fi>**20060206233543] 
[added some fields to test suite for duncan's mods
ijones at syntaxpolice.org**20060204223256] 
[fixup PackageDescription test code
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060201183912
 just ignore the extra ParseOk warnings field
] 
[ignore "x-" extension fields without a warning
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060201183145] 
[Make unknown fields a warning rather than an error
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060201182944
 Add support for warnings to the ParseResult type. Change existing
 warnings from using Debug.Trace to use this new warning support.
] 
[fix conflict
Simon Marlow <simonmar at microsoft.com>**20060206095833] 
[push and pull all
ijones at syntaxpolice.org**20060201185441] 
[combine GNUmakefile and Makefile
Simon Marlow <simonmar at microsoft.com>**20060206095400] 
[now build Setup.lhs instead of using runghc on it. still uses runhugs.
ijones at syntaxpolice.org**20060130054810] 
[cabal-install uses defaultMain if it can't find Setup.lhs
ijones at syntaxpolice.org**20060130050710] 
[cleaned up suffix handler params to hooks
ijones at syntaxpolice.org**20060116064811
 
 Summary if last few changes: I modified the hooks interface quite a
 bit, again.  There's good news and bad news about this.  The good news
 is that it's cleaned up and should be easier to maintain and to avoid
 future modifications.  The bad news is that this change itself will
 break stuff, of course.
 
 If you have any trouble building your Setup scripts, please let me
 know.  I really think that it was best to bite the bullet right now in
 one big go instead of down the road with lots of little changes.  I
 have a lot more confidence in the hooks interface, and I don't
 actually expect that it'll change as often.
 
 I made the types more consistent, and made sure there are accessor
 functions on each of the Flags types so that if the flags types change
 in the future, it shouldn't break lots of code.
 
 Another piece of good / bad news is that I decided not to get rid of
 the pre & post hooks.  They are nice for convenience and it wouldn't
 be nearly so easy to write hooks without them.
 
 That's bad because the interface to hooks is still pretty big, which
 means that there's more likelihood that it'll change in the future.
 
 Another weakness in the Hooks interface is that with command hooks
 (like sDistHook) it's tempting to add parameters to them; basically
 the stuff that we compute between the preSDist and sDist hook.  I
 removed such params and have their values computed elsewhere.
 
 Cabal hackers, please avoid adding parameters to these command hooks
 if at all possible in order to keep the interface steady.  If you need
 to compute a value to pass to these functions, compute it in the
 function and / or make it available as a function that someone
 crafting hooks can use as well, or consider whether it belongs in one
 of the parameters already being passed to the hooks,
 PackageDescription, LocalBuildInfo, UserHooks, Flags.
 
] 
[make the order of params to cmd hooks consistent
ijones at syntaxpolice.org**20060116055858] 
[remove some flags from sdist, some cleanup
ijones at syntaxpolice.org**20060116053818] 
[clarifying and making flags types consistent
ijones at syntaxpolice.org**20060116035033] 
[changing tuple types to records w/ fields
ijones at syntaxpolice.org**20060115234317] 
[moving TODO stuff to wiki
ijones at syntaxpolice.org**20060115234303] 
[fix version number in fptools makefile to match .cabal file
ijones at syntaxpolice.org**20060201183331] 
[Add extraGHCiLibraries to the InstalledPackageInfo and extend the parser.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060131163640] 
[re-add the GNUmakefiles
Simon Marlow <simonmar at microsoft.com>*-20060123115236
 These are now safe after we added "-f Makefile" to the make args when invoked
 from the GHC build system.  This repo should now be useable as the main
 Cabal repo.
] 
[re-add the GNUmakefiles
Simon Marlow <simonmar at microsoft.com>**20060123115236
 These are now safe after we added "-f Makefile" to the make args when invoked
 from the GHC build system.  This repo should now be useable as the main
 Cabal repo.
] 
[TAG checkpoint
simonmar at microsoft.com**20060113152542] 
Patch bundle hash:
ff09e60741f188dce9df507eac6f4e4bd8cc7e09


More information about the cabal-devel mailing list