Skip to content
Snippets Groups Projects
Commit b0fdabd3 authored by Iain Nicol's avatar Iain Nicol Committed by tibbe
Browse files

Fix: "cabal haddock" uses CPP overzealously

Until recently we supported ancient versions of Haddock, pre v2.0.  To
support the CPP extension with such versions, cabal had to invoke the
CPP before invoking Haddock on the output.  For simplicity cabal would
invoke the CPP on all Haskell files, if any Haskell file required CPP.
However, invoking CPP on a file which does not require it can cause
build failures.

Haddock v2.0+ supports the CPP via GHC, and even automatically
preprocesses any file with the {-# LANGUAGE CPP #-} pragma. Hence we
simply need only tell Haddock to enable the CPP when the CPP is a
package level default extension.

Fixes issue #1808.

(cherry picked from commit ba4ae3d0)
parent 2d4ea06f
No related branches found
No related tags found
No related merge requests found
...@@ -83,6 +83,7 @@ extra-source-files: ...@@ -83,6 +83,7 @@ extra-source-files:
tests/PackageTests/Haddock/CPP.hs tests/PackageTests/Haddock/CPP.hs
tests/PackageTests/Haddock/Literate.lhs tests/PackageTests/Haddock/Literate.lhs
tests/PackageTests/Haddock/my.cabal tests/PackageTests/Haddock/my.cabal
tests/PackageTests/Haddock/NoCPP.hs
tests/PackageTests/Haddock/Simple.hs tests/PackageTests/Haddock/Simple.hs
tests/PackageTests/OrderFlags/Foo.hs tests/PackageTests/OrderFlags/Foo.hs
tests/PackageTests/OrderFlags/my.cabal tests/PackageTests/OrderFlags/my.cabal
......
...@@ -27,7 +27,7 @@ import Distribution.Package ...@@ -27,7 +27,7 @@ import Distribution.Package
, PackageName(..), packageName ) , PackageName(..), packageName )
import qualified Distribution.ModuleName as ModuleName import qualified Distribution.ModuleName as ModuleName
import Distribution.PackageDescription as PD import Distribution.PackageDescription as PD
( PackageDescription(..), BuildInfo(..), allExtensions ( PackageDescription(..), BuildInfo(..), usedExtensions
, Library(..), hasLibs, Executable(..) , Library(..), hasLibs, Executable(..)
, TestSuite(..), TestSuiteInterface(..) , TestSuite(..), TestSuiteInterface(..)
, Benchmark(..), BenchmarkInterface(..) ) , Benchmark(..), BenchmarkInterface(..) )
...@@ -365,7 +365,7 @@ getGhcCppOpts haddockVersion bi = ...@@ -365,7 +365,7 @@ getGhcCppOpts haddockVersion bi =
ghcOptCppOptions = defines ghcOptCppOptions = defines
} }
where where
needsCpp = EnableExtension CPP `elem` allExtensions bi needsCpp = EnableExtension CPP `elem` usedExtensions bi
defines = [haddockVersionMacro] defines = [haddockVersionMacro]
haddockVersionMacro = "-D__HADDOCK_VERSION__=" haddockVersionMacro = "-D__HADDOCK_VERSION__="
++ show (v1 * 1000 + v2 * 10 + v3) ++ show (v1 * 1000 + v2 * 10 + v3)
......
...@@ -26,7 +26,7 @@ suite ghcPath = TestCase $ do ...@@ -26,7 +26,7 @@ suite ghcPath = TestCase $ do
assertHaddockSucceeded hResult assertHaddockSucceeded hResult
let docFiles = map (haddocksDir </>) let docFiles = map (haddocksDir </>)
["CPP.html", "Literate.html", "Simple.html"] ["CPP.html", "Literate.html", "NoCPP.html", "Simple.html"]
mapM_ (assertFindInFile "For hiding needles.") docFiles mapM_ (assertFindInFile "For hiding needles.") docFiles
assertFindInFile :: String -> FilePath -> Assertion assertFindInFile :: String -> FilePath -> Assertion
......
module NoCPP (Haystack) where
-- | For hiding needles.
data Haystack = Haystack
-- | Causes a build failure if the CPP language extension is enabled.
stringGap = "Foo\
\Bar"
...@@ -11,6 +11,6 @@ description: ...@@ -11,6 +11,6 @@ description:
Check that Cabal successfully invokes Haddock. Check that Cabal successfully invokes Haddock.
Library Library
exposed-modules: CPP, Literate, Simple exposed-modules: CPP, Literate, NoCPP, Simple
other-extensions: CPP other-extensions: CPP
build-depends: base build-depends: base
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment