Skip to content
Snippets Groups Projects
Commit e7ab46a9 authored by Edward Z. Yang's avatar Edward Z. Yang
Browse files

Fix #3041, ifndef all CURRENT_PACKAGE_KEY and related macros.


I also realized LOCAL_COMPONENT_ID is pessimal if we don't
depend on a library, so I removed it. (It has never been
in a real Cabal release.)

Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>
parent c2c5d36b
No related branches found
No related tags found
No related merge requests found
......@@ -37,6 +37,36 @@ import Distribution.Text
-- * Generate cabal_macros.h
-- ------------------------------------------------------------
-- Invariant: HeaderLines always has a trailing newline
type HeaderLines = String
line :: String -> HeaderLines
line str = str ++ "\n"
ifndef :: String -> HeaderLines -> HeaderLines
ifndef macro body =
line ("#ifndef " ++ macro) ++
body ++
line ("#endif /* " ++ macro ++ " */")
define :: String -> Maybe [String] -> String -> HeaderLines
define macro params val =
line ("#define " ++ macro ++ f params ++ " " ++ val)
where
f Nothing = ""
f (Just xs) = "(" ++ intercalate "," xs ++ ")"
defineStr :: String -> String -> HeaderLines
defineStr macro str = define macro Nothing (show str)
ifndefDefine :: String -> Maybe [String] -> String -> HeaderLines
ifndefDefine macro params str =
ifndef macro (define macro params str)
ifndefDefineStr :: String -> String -> HeaderLines
ifndefDefineStr macro str =
ifndef macro (defineStr macro str)
-- | The contents of the @cabal_macros.h@ for the given configured package.
--
generate :: PackageDescription -> LocalBuildInfo -> ComponentLocalBuildInfo -> String
......@@ -53,7 +83,7 @@ generate pkg_descr lbi clbi =
--
generatePackageVersionMacros :: [PackageIdentifier] -> String
generatePackageVersionMacros pkgids = concat
[ "/* package " ++ display pkgid ++ " */\n"
[ line ("/* package " ++ display pkgid ++ " */")
++ generateMacros "" pkgname version
| pkgid@(PackageIdentifier name version) <- pkgids
, let pkgname = map fixchar (display name)
......@@ -64,7 +94,7 @@ generatePackageVersionMacros pkgids = concat
--
generateToolVersionMacros :: [ConfiguredProgram] -> String
generateToolVersionMacros progs = concat
[ "/* tool " ++ progid ++ " */\n"
[ line ("/* tool " ++ progid ++ " */")
++ generateMacros "TOOL_" progname version
| prog <- progs
, isJust . programVersion $ prog
......@@ -79,29 +109,30 @@ generateToolVersionMacros progs = concat
generateMacros :: String -> String -> Version -> String
generateMacros macro_prefix name version =
concat
["#define ", macro_prefix, "VERSION_",name," ",show (display version),"\n"
,"#define MIN_", macro_prefix, "VERSION_",name,"(major1,major2,minor) (\\\n"
," (major1) < ",major1," || \\\n"
," (major1) == ",major1," && (major2) < ",major2," || \\\n"
," (major1) == ",major1," && (major2) == ",major2," && (minor) <= ",minor,")"
,"\n\n"
]
[ifndefDefineStr (macro_prefix ++ "VERSION_" ++ name) (display version)
,ifndefDefine ("MIN_" ++ macro_prefix ++ "VERSION_" ++ name)
(Just ["major1","major2","minor"])
$ concat [
"(\\\n"
," (major1) < ",major1," || \\\n"
," (major1) == ",major1," && (major2) < ",major2," || \\\n"
," (major1) == ",major1," && (major2) == ",major2," && (minor) <= ",minor,")"
]
,"\n"]
where
(major1:major2:minor:_) = map show (versionBranch version ++ repeat 0)
-- | Generate the @CURRENT_COMPONENT_ID@ definition for the component ID
-- of the current package.
generateComponentIdMacro :: LocalBuildInfo -> ComponentLocalBuildInfo -> String
generateComponentIdMacro lbi clbi =
generateComponentIdMacro _lbi clbi =
concat $
(case clbi of
[case clbi of
LibComponentLocalBuildInfo{} ->
["#define CURRENT_PACKAGE_KEY \"" ++ componentCompatPackageKey clbi ++ "\"\n"]
_ -> [])
++
["#define CURRENT_COMPONENT_ID \"" ++ display (componentComponentId clbi) ++ "\"\n"
,"#define LOCAL_COMPONENT_ID \"" ++ display (localComponentId lbi) ++ "\"\n"
,"\n"]
ifndefDefineStr "CURRENT_PACKAGE_KEY" (componentCompatPackageKey clbi)
_ -> ""
,ifndefDefineStr "CURRENT_COMPONENT_ID" (display (componentComponentId clbi))
]
fixchar :: Char -> Char
fixchar '-' = '_'
......
......@@ -64,6 +64,8 @@
* New './Setup configure' flag '--cabal-file', allowing multiple
.cabal files in a single directory (#3553). Primarily intended for
internal use.
* Macros in 'cabal_macros.h' are now ifndef'd, so that they
don't cause an error if the macro is already defined. (#3041)
1.24.0.0 Ryan Thomas <ryan@ryant.org> March 2016
* Support GHC 8.
......
......@@ -101,10 +101,8 @@ import Distribution.Simple.Configure
import Distribution.Verbosity (Verbosity)
import Distribution.Simple.BuildPaths (exeExtension)
#ifndef LOCAL_COMPONENT_ID
import Distribution.Simple.Utils (cabalVersion)
import Distribution.Text (display)
#endif
import qualified Test.Tasty.HUnit as HUnit
import Text.Regex.Posix
......@@ -389,10 +387,6 @@ cabal' cmd extraArgs0 = do
-- Cabal is going to configure it and usually figure
-- out the right location in any case.
-- , "--with-ghc-pkg", withGhcPkgPath suite
-- Would really like to do this, but we're not always
-- going to be building against sufficiently recent
-- Cabal which provides this macro.
-- , "--dependency=Cabal=" ++ LOCAL_COMPONENT_ID
-- These flags make the test suite run faster
-- Can't do this unless we LD_LIBRARY_PATH correctly
-- , "--enable-executable-dynamic"
......@@ -469,11 +463,6 @@ rawCompileSetup verbosity suite e path = do
[ "--make"] ++
ghcPackageDBParams (ghcVersion suite) (packageDBStack suite) ++
[ "-hide-package Cabal"
#ifdef LOCAL_COMPONENT_ID
-- This is best, but we don't necessarily have it
-- if we're bootstrapping with old Cabal.
, "-package-id " ++ LOCAL_COMPONENT_ID
#else
-- This mostly works, UNLESS you've installed a
-- version of Cabal with the SAME version number.
-- Then old GHCs will incorrectly select the installed
......@@ -482,7 +471,6 @@ rawCompileSetup verbosity suite e path = do
-- at all, except if there's a later version of Cabal
-- installed GHC will prefer that.
, "-package Cabal-" ++ display cabalVersion
#endif
, "-O0"
, "Setup.hs" ]
unless (resultExitCode r == ExitSuccess) $
......
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