From 8be4bb772d44ab4d42d4cfbb726df7186ca797ce Mon Sep 17 00:00:00 2001
From: ijones <ijones@syntaxpolice.org>
Date: Mon, 5 Dec 2005 01:45:53 +0000
Subject: [PATCH] check for correct cabal version during parsing

I throw a parse error if this package has the wrong cabal version.
This is so that the user can get this error before getting an error
for eg. an unknown field.  Also check it in the sanity checker.

I just hard-code the cabal version in the source, it would be nicer if
we got it from the .cabal file.  cabal could include the version in
the cpp flags, but cabal's setup file needs to build without cabal, so
that wouldn't actually work for us ahem.
---
 Distribution/PackageDescription.hs | 30 +++++++++++++++++++++---------
 Distribution/ParseUtils.hs         |  2 +-
 Distribution/PreProcess.hs         |  2 +-
 Distribution/Simple.hs             |  5 ++---
 4 files changed, 25 insertions(+), 14 deletions(-)

diff --git a/Distribution/PackageDescription.hs b/Distribution/PackageDescription.hs
index 8c30f5cd67..756e41fc1c 100644
--- a/Distribution/PackageDescription.hs
+++ b/Distribution/PackageDescription.hs
@@ -93,7 +93,7 @@ import System.Exit
 import Distribution.ParseUtils
 import Distribution.Package(PackageIdentifier(..),showPackageId,
                             parsePackageName)
-import Distribution.Version(Version(..), VersionRange(..),
+import Distribution.Version(Version(..), VersionRange(..), withinRange,
                             showVersion, parseVersion, showVersionRange, parseVersionRange)
 import Distribution.License(License(..))
 import Distribution.Version(Dependency(..))
@@ -108,6 +108,10 @@ import HUnit (Test(..), assertBool, Assertion, runTestTT, Counts, assertEqual)
 import Distribution.ParseUtils  (runP)
 #endif
 
+-- |Fix. Figure out a way to get this from .cabal file
+cabalVersion :: Version
+cabalVersion = Version [1,1,4] []
+
 -- | This data type is the internal representation of the file @pkg.cabal@.
 -- It contains two kinds of information about the package: information
 -- which is needed for all packages, such as the package name and version, and 
@@ -131,7 +135,7 @@ data PackageDescription
         description    :: String, -- ^A more verbose description of this package
         category       :: String,
         buildDepends   :: [Dependency],
-        cabalVersion   :: VersionRange, -- ^If this package depends on a specific version of Cabal, give that here.
+        descCabalVersion :: VersionRange, -- ^If this package depends on a specific version of Cabal, give that here.
         -- components
         library        :: Maybe Library,
         executables    :: [Executable],
@@ -155,7 +159,7 @@ emptyPackageDescription
     =  PackageDescription {package      = PackageIdentifier "" (Version [] []),
                       license      = AllRightsReserved,
                       licenseFile  = "",
-                      cabalVersion = AnyVersion,
+                      descCabalVersion = AnyVersion,
                       copyright    = "",
                       maintainer   = "",
                       author       = "",
@@ -340,11 +344,11 @@ basicStanzaFields =
                            text                   parsePackageName
                            (pkgName . package)    (\name pkg -> pkg{package=(package pkg){pkgName=name}})
  , simpleField reqNameVersion
-                           (text . showVersion)   parseVersion 
+                           (text . showVersion)   parseVersion
                            (pkgVersion . package) (\ver pkg -> pkg{package=(package pkg){pkgVersion=ver}})
  , simpleField "cabal-version"
-                           (text . showVersionRange) parseVersionRange
-                           cabalVersion         (\v pkg -> pkg{cabalVersion=v})
+                           (text . showVersionRange) parseCabalVersion
+                           descCabalVersion       (\v pkg -> pkg{descCabalVersion=v})
  , simpleField "license"
                            (text . show)          parseLicenseQ
                            license                (\l pkg -> pkg{license=l})
@@ -625,10 +629,13 @@ sanityCheckPackage pkg_descr
                       "Package is copyright All Rights Reserved"
           noLicenseFile = checkSanity (null $ licenseFile pkg_descr)
                           "No license-file field."
+          goodCabal = let v = (descCabalVersion pkg_descr)
+                          in checkSanity (not $ cabalVersion  `withinRange` v)
+                                 ("This package requires Cabal verion: " ++ (showVersionRange v) ++ ".")
 
          in return $ (catMaybes [nothingToDo, noModules,
                                  allRights, noLicenseFile]
-                     ,catMaybes $ libSane:(checkMissingFields pkg_descr))
+                     ,catMaybes $ libSane:goodCabal:(checkMissingFields pkg_descr))
 
 -- |Output warnings and errors. Exit if any errors.
 errorOut :: [String]  -- ^Warnings
@@ -671,6 +678,11 @@ hasMods pkg_descr
     | otherwise = null (executables pkg_descr)
                    && null (exposedModules (fromJust (library pkg_descr)))
 
+parseCabalVersion = do v <- parseVersionRange
+                       if (cabalVersion `withinRange` v)
+                          then return v
+                          else error ("This package requires Cabal verion: " ++ (showVersionRange v) ++ ".")
+
 -- ------------------------------------------------------------
 -- * Testing
 -- ------------------------------------------------------------
@@ -739,7 +751,7 @@ testPkgDescAnswer =
                     synopsis = "a nice package!",
                     description = "a really nice package!",
                     category = "tools",
-                               cabalVersion=LaterVersion (Version [1,1,1] []),
+                               descCabalVersion=LaterVersion (Version [1,1,1] []),
                     buildDepends = [Dependency "haskell-src" AnyVersion,
                                      Dependency "HUnit"
                                      (UnionVersionRanges (ThisVersion (Version [1,0,0] ["rain"]))
@@ -835,7 +847,7 @@ comparePackageDescriptions :: PackageDescription
                            -> PackageDescription
                            -> [String]      -- ^Errors
 comparePackageDescriptions p1 p2
-    = 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 cabalVersion "cabal-version":[]
+    = 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)
diff --git a/Distribution/ParseUtils.hs b/Distribution/ParseUtils.hs
index 45ba2dc8ff..49b33f1e09 100644
--- a/Distribution/ParseUtils.hs
+++ b/Distribution/ParseUtils.hs
@@ -106,7 +106,7 @@ showError e =
 
 locatedErrorMsg :: PError -> (Maybe LineNo, String)
 locatedErrorMsg (AmbigousParse f n) = (Just n, "Ambigous parse in field '"++f++"'")
-locatedErrorMsg (NoParse f n)       = (Just n, "Parse of field '"++f++"' failed")
+locatedErrorMsg (NoParse f n)       = (Just n, "Parse of field '"++f++"' failed: ")
 locatedErrorMsg (FromString s n)    = (n, s)
 
 syntaxError :: LineNo -> String -> ParseResult a
diff --git a/Distribution/PreProcess.hs b/Distribution/PreProcess.hs
index 049a982881..2783c840a8 100644
--- a/Distribution/PreProcess.hs
+++ b/Distribution/PreProcess.hs
@@ -201,7 +201,7 @@ ppUnlit inFile outFile verbose = do
     writeFile outFile (unlit inFile contents)
     return ExitSuccess
 
-ppCpp :: PackageDescription -> LocalBuildInfo -> PreProcessor
+ppCpp :: BuildInfo -> LocalBuildInfo -> PreProcessor
 ppCpp = ppCpp' []
 
 ppCpp' :: [String] -> BuildInfo -> LocalBuildInfo -> PreProcessor
diff --git a/Distribution/Simple.hs b/Distribution/Simple.hs
index c08cbfe360..ec84bbec91 100644
--- a/Distribution/Simple.hs
+++ b/Distribution/Simple.hs
@@ -57,9 +57,9 @@ module Distribution.Simple (
         -- * Customization
         UserHooks(..), Args,
         defaultMainWithHooks, defaultUserHooks, emptyUserHooks,
-        defaultHookedPackageDesc,
+        defaultHookedPackageDesc
 #ifdef DEBUG        
-        simpleHunitTests
+        ,simpleHunitTests
 #endif
   ) where
 
@@ -116,7 +116,6 @@ import Distribution.Version hiding (hunitTests)
 import Distribution.Version
 #endif
 
-
 type Args = [String]
 
 -- | Hooks allow authors to add specific functionality before and after
-- 
GitLab