Repository : ssh://darcs.haskell.org//srv/darcs/packages/Cabal

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/15b2cf452f5526cafba0756bf454f703a67f5c2b

>---------------------------------------------------------------

commit 15b2cf452f5526cafba0756bf454f703a67f5c2b
Author: Johan Tibell <[email protected]>
Date:   Wed Oct 12 20:16:04 2011 +0000

    Add package checks for benchmarks
    Refactor duplicate names check to avoid having to manually write all
    O(n^2) possible collision cases between executables, test suites, and
    benchmarks.

>---------------------------------------------------------------

 Cabal/Distribution/PackageDescription/Check.hs |   76 +++++++++++++++++------
 1 files changed, 56 insertions(+), 20 deletions(-)

diff --git a/Cabal/Distribution/PackageDescription/Check.hs 
b/Cabal/Distribution/PackageDescription/Check.hs
index 5354376..09f98c0 100644
--- a/Cabal/Distribution/PackageDescription/Check.hs
+++ b/Cabal/Distribution/PackageDescription/Check.hs
@@ -204,23 +204,17 @@ checkSanity pkg =
       PackageBuildImpossible
         "No executables and no library found. Nothing to do."
 
-  , check (not (null exeDuplicates)) $
-      PackageBuildImpossible $ "Duplicate executable sections "
-        ++ commaSep exeDuplicates
-  , check (not (null testDuplicates)) $
-      PackageBuildImpossible $ "Duplicate test sections "
-        ++ commaSep testDuplicates
-
-    --TODO: this seems to duplicate a check on the testsuites
-  , check (not (null testsThatAreExes)) $
-      PackageBuildImpossible $ "These test sections share names with 
executable sections: "
-        ++ commaSep testsThatAreExes
+  , check (not (null duplicateNames)) $
+      PackageBuildImpossible $ "Duplicate sections: " ++ commaSep 
duplicateNames
+        ++ ". The name of every executable, test suite, and benchmark section 
in"
+        ++ " the package must be unique."
   ]
   --TODO: check for name clashes case insensitively: windows file systems 
cannot cope.
 
   ++ maybe []  checkLibrary    (library pkg)
   ++ concatMap checkExecutable (executables pkg)
   ++ concatMap (checkTestSuite pkg) (testSuites pkg)
+  ++ concatMap (checkBenchmark pkg) (benchmarks pkg)
 
   ++ catMaybes [
 
@@ -233,9 +227,8 @@ checkSanity pkg =
   where
     exeNames = map exeName $ executables pkg
     testNames = map testName $ testSuites pkg
-    exeDuplicates = dups exeNames
-    testDuplicates = dups testNames
-    testsThatAreExes = filter (flip elem exeNames) testNames
+    bmNames = map benchmarkName $ benchmarks pkg
+    duplicateNames = dups $ exeNames ++ testNames ++ bmNames
 
 checkLibrary :: Library -> [PackageCheck]
 checkLibrary lib =
@@ -300,11 +293,9 @@ checkTestSuite pkg test =
            "The 'main-is' field must specify a '.hs' or '.lhs' file "
         ++ "(even if it is generated by a preprocessor)."
 
-  , check exeNameClash $
-      PackageBuildImpossible $
-           "The test suite " ++ testName test
-        ++ " has the same name as an executable."
-
+    -- Test suites might be built as (internal) libraries named after
+    -- the test suite and thus their names must not clash with the
+    -- name of the package.
   , check libNameClash $
       PackageBuildImpossible $
            "The test suite " ++ testName test
@@ -317,12 +308,57 @@ checkTestSuite pkg test =
       TestSuiteExeV10 _ f -> takeExtension f `notElem` [".hs", ".lhs"]
       _                   -> False
 
-    exeNameClash = testName test `elem` [ exeName exe | exe <- executables pkg 
]
     libNameClash = testName test `elem` [ libName
                                         | _lib <- maybeToList (library pkg)
                                         , let PackageName libName =
                                                 pkgName (package pkg) ]
 
+checkBenchmark :: PackageDescription -> Benchmark -> [PackageCheck]
+checkBenchmark pkg bm =
+  catMaybes [
+
+    case benchmarkInterface bm of
+      BenchmarkUnsupported tt@(BenchmarkTypeUnknown _ _) -> Just $
+        PackageBuildWarning $
+             quote (display tt) ++ " is not a known type of benchmark. "
+          ++ "The known benchmark types are: "
+          ++ commaSep (map display knownBenchmarkTypes)
+
+      BenchmarkUnsupported tt -> Just $
+        PackageBuildWarning $
+             quote (display tt) ++ " is not a supported benchmark version. "
+          ++ "The known benchmark types are: "
+          ++ commaSep (map display knownBenchmarkTypes)
+      _ -> Nothing
+
+  , check (not $ null moduleDuplicates) $
+      PackageBuildWarning $
+           "Duplicate modules in benchmark '" ++ benchmarkName bm ++ "': "
+        ++ commaSep (map display moduleDuplicates)
+
+  , check mainIsWrongExt $
+      PackageBuildImpossible $
+           "The 'main-is' field must specify a '.hs' or '.lhs' file "
+        ++ "(even if it is generated by a preprocessor)."
+
+    -- See comment for similar check on test suites.
+  , check libNameClash $
+      PackageBuildImpossible $
+           "The benchmark " ++ benchmarkName bm
+        ++ " has the same name as the package."
+  ]
+  where
+    moduleDuplicates = dups $ benchmarkModules bm
+
+    mainIsWrongExt = case benchmarkInterface bm of
+      BenchmarkExeV10 _ f -> takeExtension f `notElem` [".hs", ".lhs"]
+      _                   -> False
+
+    libNameClash = benchmarkName bm `elem` [ libName
+                                           | _lib <- maybeToList (library pkg)
+                                           , let PackageName libName =
+                                                   pkgName (package pkg) ]
+
 -- ------------------------------------------------------------
 -- * Additional pure checks
 -- ------------------------------------------------------------



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to