[Git][ghc/ghc][master] 3 commits: Fix fetch_cabal
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
7964763b by Julian Ospald at 2026-01-14T11:11:31-05:00
Fix fetch_cabal
* download cabal if the existing one is of an older version
* fix FreeBSD download url
* fix unpacking on FreeBSD
- - - - -
6b0129c1 by Julian Ospald at 2026-01-14T11:11:31-05:00
Bump toolchain in CI
- - - - -
0f53ccc6 by Julian Ospald at 2026-01-14T11:11:31-05:00
Use libffi-clib
Previously, we would build libffi via hadrian
and bundle it manually with the GHC bindist.
This now moves all that logic out of hadrian
and allows us to have a clean Haskell package
to build and link against and ship it without
extra logic.
This patch still retains the ability to link
against a system libffi.
The main reason of bundling libffi was that on
some platforms (e.g. FreeBSD and Mac), system libffi
is not visible to the C toolchain by default,
so users would require settings in e.g. cabal
to be able to compile anything.
This adds the submodule libffi-clib to the repository.
- - - - -
27 changed files:
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitmodules
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Unit.hs
- compiler/GHC/Unit/State.hs
- hadrian/hadrian.cabal
- hadrian/src/Builder.hs
- hadrian/src/Packages.hs
- hadrian/src/Rules.hs
- hadrian/src/Rules/Documentation.hs
- hadrian/src/Rules/Generate.hs
- − hadrian/src/Rules/Libffi.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Rules/Rts.hs
- hadrian/src/Rules/SourceDist.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
- − libffi-tarballs
- + libraries/libffi-clib
- packages
- rts/include/rts/ghc_ffi.h
- rts/rts.buildinfo.in
- rts/rts.cabal
Changes:
=====================================
.gitlab/ci.sh
=====================================
@@ -341,11 +341,27 @@ function fetch_ghc() {
}
function fetch_cabal() {
+ local should_fetch=false
+
if [ ! -e "$CABAL" ]; then
- local v="$CABAL_INSTALL_VERSION"
- if [[ -z "$v" ]]; then
- fail "neither CABAL nor CABAL_INSTALL_VERSION are not set"
+ if [ -z "${CABAL_INSTALL_VERSION:-}" ]; then
+ fail "cabal not found at '$CABAL' and CABAL_INSTALL_VERSION is not set"
+ fi
+ should_fetch=true
+ fi
+
+ if [ -e "$CABAL" ] && [ -n "${CABAL_INSTALL_VERSION:-}" ]; then
+ local current_version
+ if current_version=$($CABAL --numeric-version 2>/dev/null); then
+ if [ "$current_version" != "$CABAL_INSTALL_VERSION" ]; then
+ info "cabal version mismatch: found $current_version, expected $CABAL_INSTALL_VERSION"
+ should_fetch=true
fi
+ fi
+ fi
+
+ if [ "$should_fetch" = true ]; then
+ local v="$CABAL_INSTALL_VERSION"
start_section fetch-cabal "Fetch Cabal"
case "$(uname)" in
@@ -355,7 +371,7 @@ function fetch_cabal() {
CLANG64) cabal_arch="x86_64" ;;
*) fail "unknown MSYSTEM $MSYSTEM" ;;
esac
- url="https://downloads.haskell.org/~cabal/cabal-install-$v/cabal-install-$v-$caba..."
+ local url="https://downloads.haskell.org/~cabal/cabal-install-$v/cabal-install-$v-$caba..."
info "Fetching cabal binary distribution from $url..."
curl "$url" > "$TMP/cabal.zip"
unzip "$TMP/cabal.zip"
@@ -365,19 +381,21 @@ function fetch_cabal() {
local base_url="https://downloads.haskell.org/~cabal/cabal-install-$v/"
case "$(uname)" in
Darwin) cabal_url="$base_url/cabal-install-$v-x86_64-apple-darwin17.7.0.tar.xz" ;;
- FreeBSD) cabal_url="$base_url/cabal-install-$v-x86_64-freebsd14.tar.xz" ;;
+ FreeBSD) cabal_url="https://downloads.haskell.org/ghcup/unofficial-bindists/cabal/$v/cabal-insta..." ;;
*) fail "don't know where to fetch cabal-install for $(uname)"
esac
echo "Fetching cabal-install from $cabal_url"
curl "$cabal_url" > cabal.tar.xz
- tmp="$(tar -tJf cabal.tar.xz | head -n1)"
- $TAR -xJf cabal.tar.xz
+ local path="$(tar -tJf cabal.tar.xz | head -n1)"
+ local tmp_dir=$(mktemp -d XXXX-cabal)
+ $TAR -xJf cabal.tar.xz -C "${tmp_dir}"
# Check if the bindist has directory structure
- if [[ "$tmp" = "cabal" ]]; then
- mv cabal "$toolchain/bin"
+ if [[ "$path" = "cabal" ]]; then
+ mv "${tmp_dir}"/cabal "$toolchain/bin"
else
- mv "$tmp/cabal" "$toolchain/bin"
+ mv "${tmp_dir}/$path/cabal" "$toolchain/bin"
fi
+ rmdir "${tmp_dir}"
;;
esac
end_section fetch-cabal
=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -451,7 +451,7 @@ opsysVariables _ FreeBSD14 = mconcat
, "CC" =: "cc"
, "CXX" =: "c++"
, "FETCH_GHC_VERSION" =: "9.10.1"
- , "CABAL_INSTALL_VERSION" =: "3.10.3.0"
+ , "CABAL_INSTALL_VERSION" =: "3.14.2.0"
]
opsysVariables arch (Linux distro) = distroVariables arch distro
opsysVariables AArch64 (Darwin {}) = mconcat
@@ -480,9 +480,9 @@ opsysVariables Amd64 (Darwin {}) = mconcat
opsysVariables _ (Windows {}) = mconcat
[ "MSYSTEM" =: "CLANG64"
, "LANG" =: "en_US.UTF-8"
- , "CABAL_INSTALL_VERSION" =: "3.10.2.0"
+ , "CABAL_INSTALL_VERSION" =: "3.14.2.0"
, "HADRIAN_ARGS" =: "--docs=no-sphinx-pdfs"
- , "FETCH_GHC_VERSION" =: "9.10.1"
+ , "FETCH_GHC_VERSION" =: "9.10.3"
]
opsysVariables _ _ = mempty
=====================================
.gitlab/jobs.yaml
=====================================
@@ -1463,7 +1463,7 @@
"BIGNUM_BACKEND": "gmp",
"BIN_DIST_NAME": "ghc-x86_64-freebsd14-validate",
"BUILD_FLAVOUR": "validate",
- "CABAL_INSTALL_VERSION": "3.10.3.0",
+ "CABAL_INSTALL_VERSION": "3.14.2.0",
"CC": "cc",
"CONFIGURE_ARGS": "--with-iconv-includes=/usr/local/include --with-iconv-libraries=/usr/local/lib --with-system-libffi --with-ffi-includes=/usr/local/include --with-ffi-libraries=/usr/local/lib --with-gmp-includes=/usr/local/include --with-gmp-libraries=/usr/local/lib --enable-strict-ghc-toolchain-check",
"CXX": "c++",
@@ -3691,9 +3691,9 @@
"BIGNUM_BACKEND": "native",
"BIN_DIST_NAME": "ghc-x86_64-windows-int_native-validate",
"BUILD_FLAVOUR": "validate",
- "CABAL_INSTALL_VERSION": "3.10.2.0",
+ "CABAL_INSTALL_VERSION": "3.14.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "FETCH_GHC_VERSION": "9.10.1",
+ "FETCH_GHC_VERSION": "9.10.3",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"LANG": "en_US.UTF-8",
@@ -3754,9 +3754,9 @@
"BIGNUM_BACKEND": "gmp",
"BIN_DIST_NAME": "ghc-x86_64-windows-validate",
"BUILD_FLAVOUR": "validate",
- "CABAL_INSTALL_VERSION": "3.10.2.0",
+ "CABAL_INSTALL_VERSION": "3.14.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "FETCH_GHC_VERSION": "9.10.1",
+ "FETCH_GHC_VERSION": "9.10.3",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"LANG": "en_US.UTF-8",
@@ -4346,7 +4346,7 @@
"BIGNUM_BACKEND": "gmp",
"BIN_DIST_NAME": "ghc-x86_64-freebsd14-release+no_split_sections",
"BUILD_FLAVOUR": "release+no_split_sections",
- "CABAL_INSTALL_VERSION": "3.10.3.0",
+ "CABAL_INSTALL_VERSION": "3.14.2.0",
"CC": "cc",
"CONFIGURE_ARGS": "--with-iconv-includes=/usr/local/include --with-iconv-libraries=/usr/local/lib --with-system-libffi --with-ffi-includes=/usr/local/include --with-ffi-libraries=/usr/local/lib --with-gmp-includes=/usr/local/include --with-gmp-libraries=/usr/local/lib --enable-strict-ghc-toolchain-check",
"CXX": "c++",
@@ -5437,9 +5437,9 @@
"BIGNUM_BACKEND": "native",
"BIN_DIST_NAME": "ghc-x86_64-windows-int_native-release",
"BUILD_FLAVOUR": "release",
- "CABAL_INSTALL_VERSION": "3.10.2.0",
+ "CABAL_INSTALL_VERSION": "3.14.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "FETCH_GHC_VERSION": "9.10.1",
+ "FETCH_GHC_VERSION": "9.10.3",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"IGNORE_PERF_FAILURES": "all",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
@@ -5501,9 +5501,9 @@
"BIGNUM_BACKEND": "gmp",
"BIN_DIST_NAME": "ghc-x86_64-windows-release",
"BUILD_FLAVOUR": "release",
- "CABAL_INSTALL_VERSION": "3.10.2.0",
+ "CABAL_INSTALL_VERSION": "3.14.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "FETCH_GHC_VERSION": "9.10.1",
+ "FETCH_GHC_VERSION": "9.10.3",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"IGNORE_PERF_FAILURES": "all",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
@@ -5638,7 +5638,7 @@
"BIGNUM_BACKEND": "gmp",
"BIN_DIST_NAME": "ghc-x86_64-freebsd14-validate",
"BUILD_FLAVOUR": "validate",
- "CABAL_INSTALL_VERSION": "3.10.3.0",
+ "CABAL_INSTALL_VERSION": "3.14.2.0",
"CC": "cc",
"CONFIGURE_ARGS": "--with-iconv-includes=/usr/local/include --with-iconv-libraries=/usr/local/lib --with-system-libffi --with-ffi-includes=/usr/local/include --with-ffi-libraries=/usr/local/lib --with-gmp-includes=/usr/local/include --with-gmp-libraries=/usr/local/lib --enable-strict-ghc-toolchain-check",
"CXX": "c++",
@@ -7835,9 +7835,9 @@
"BIGNUM_BACKEND": "native",
"BIN_DIST_NAME": "ghc-x86_64-windows-int_native-validate",
"BUILD_FLAVOUR": "validate",
- "CABAL_INSTALL_VERSION": "3.10.2.0",
+ "CABAL_INSTALL_VERSION": "3.14.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "FETCH_GHC_VERSION": "9.10.1",
+ "FETCH_GHC_VERSION": "9.10.3",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"LANG": "en_US.UTF-8",
@@ -7897,9 +7897,9 @@
"BIGNUM_BACKEND": "gmp",
"BIN_DIST_NAME": "ghc-x86_64-windows-validate",
"BUILD_FLAVOUR": "validate",
- "CABAL_INSTALL_VERSION": "3.10.2.0",
+ "CABAL_INSTALL_VERSION": "3.14.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "FETCH_GHC_VERSION": "9.10.1",
+ "FETCH_GHC_VERSION": "9.10.3",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"LANG": "en_US.UTF-8",
=====================================
.gitmodules
=====================================
@@ -99,10 +99,6 @@
path = utils/hsc2hs
url = https://gitlab.haskell.org/ghc/hsc2hs.git
ignore = untracked
-[submodule "libffi-tarballs"]
- path = libffi-tarballs
- url = https://gitlab.haskell.org/ghc/libffi-tarballs.git
- ignore = untracked
[submodule "gmp-tarballs"]
path = libraries/ghc-internal/gmp/gmp-tarballs
url = https://gitlab.haskell.org/ghc/gmp-tarballs.git
@@ -124,3 +120,6 @@
[submodule "libraries/template-haskell-quasiquoter"]
path = libraries/template-haskell-quasiquoter
url = https://gitlab.haskell.org/ghc/template-haskell-quasiquoter.git
+[submodule "libraries/libffi-clib"]
+ path = libraries/libffi-clib
+ url = https://github.com/stable-haskell/libffi-clib.git
=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -1,5 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ViewPatterns #-}
--
@@ -67,6 +68,8 @@ import GHC.ByteCode.Linker
import GHC.ByteCode.Asm
import GHC.ByteCode.Types
+import GHC.Linker.Unit (getUnitDepends)
+
import GHC.Stack.CCS
import GHC.SysTools
@@ -179,10 +182,10 @@ getLoaderState :: Interp -> IO (Maybe LoaderState)
getLoaderState interp = readMVar (loader_state (interpLoader interp))
-emptyLoaderState :: LoaderState
-emptyLoaderState = LoaderState
+emptyLoaderState :: UnitEnv -> LoaderState
+emptyLoaderState unit_env = LoaderState
{ bco_loader_state = emptyBytecodeLoaderState
- , pkgs_loaded = init_pkgs
+ , pkgs_loaded = init_pkgs deps
, bcos_loaded = emptyModuleEnv
, objs_loaded = emptyModuleEnv
, temp_sos = []
@@ -192,7 +195,13 @@ emptyLoaderState = LoaderState
--
-- The linker's symbol table is populated with RTS symbols using an
-- explicit list. See rts/Linker.c for details.
- where init_pkgs = unitUDFM rtsUnitId (LoadedPkgInfo rtsUnitId [] [] [] emptyUniqDSet)
+ where
+ deps = getUnitDepends unit_env rtsUnitId
+ pkg_to_dfm unit_id = (unit_id, (LoadedPkgInfo unit_id [] [] [] emptyUniqDSet))
+ init_pkgs deps = let addToUDFM' (k, v) m = addToUDFM m k v
+ in foldr addToUDFM' emptyUDFM $ [
+ pkg_to_dfm rtsUnitId
+ ] ++ fmap pkg_to_dfm deps
extendLoadedEnv :: Interp -> BytecodeLoaderStateModifier -> [(Name,ForeignHValue)] -> IO ()
extendLoadedEnv interp modify_bytecode_loader_state new_bindings =
@@ -341,7 +350,7 @@ initLoaderState interp hsc_env = do
reallyInitLoaderState :: Interp -> HscEnv -> IO LoaderState
reallyInitLoaderState interp hsc_env = do
-- Initialise the linker state
- let pls0 = emptyLoaderState
+ let pls0 = emptyLoaderState (hsc_unit_env hsc_env)
case platformArch (targetPlatform (hsc_dflags hsc_env)) of
-- FIXME: we don't initialize anything with the JS interpreter.
@@ -1226,12 +1235,6 @@ loadPackage interp hsc_env pkgs pls
bc_dirs = [map ST.unpack $ Packages.unitLibraryBytecodeDirs pkg | pkg <- pkgs]
let hs_libs = [map ST.unpack $ Packages.unitLibraries pkg | pkg <- pkgs]
- -- The FFI GHCi import lib isn't needed as
- -- GHC.Linker.Loader + rts/Linker.c link the
- -- interpreted references to FFI to the compiled FFI.
- -- We therefore filter it out so that we don't get
- -- duplicate symbol errors.
- hs_libs' = filter ("HSffi" /=) <$> hs_libs
-- Because of slight differences between the GHC dynamic linker and
-- the native system linker some packages have to link with a
@@ -1251,7 +1254,7 @@ loadPackage interp hsc_env pkgs pls
dirs_env <- traverse (addEnvPaths "LIBRARY_PATH") dirs
hs_classifieds
- <- sequenceA [mapM (locateLib interp hsc_env True bc_dir_ dirs_env_ gcc_paths) hs_libs'_ | (bc_dir_, dirs_env_, hs_libs'_) <- zip3 bc_dirs dirs_env hs_libs' ]
+ <- sequenceA [mapM (locateLib interp hsc_env True bc_dir_ dirs_env_ gcc_paths) hs_libs'_ | (bc_dir_, dirs_env_, hs_libs'_) <- zip3 bc_dirs dirs_env hs_libs ]
extra_classifieds
<- sequenceA [mapM (locateLib interp hsc_env False [] dirs_env_ gcc_paths) extra_libs_ | (dirs_env_, extra_libs_) <- zip dirs_env extra_libs]
let classifieds = zipWith (++) hs_classifieds extra_classifieds
=====================================
compiler/GHC/Linker/Unit.hs
=====================================
@@ -6,6 +6,7 @@ module GHC.Linker.Unit
, collectArchives
, getUnitLinkOpts
, getLibs
+ , getUnitDepends
)
where
@@ -105,3 +106,9 @@ getLibs namever ways unit_env pkgs = do
, f <- (\n -> "lib" ++ n ++ ".a") <$> unitHsLibs namever ways p ]
filterM (doesFileExist . fst) candidates
+getUnitDepends :: HasDebugCallStack => UnitEnv -> UnitId -> [UnitId]
+getUnitDepends unit_env pkg =
+ let unit_state = ue_homeUnitState unit_env
+ unit_info = unsafeLookupUnitId unit_state pkg
+ in (unitDepends unit_info)
+
=====================================
compiler/GHC/Unit/State.hs
=====================================
@@ -372,7 +372,7 @@ initUnitConfig dflags cached_dbs home_units =
-- Since "base" is not wired in, then the unit-id is discovered
-- from the settings file by default, but can be overriden by power-users
-- by specifying `-base-unit-id` flag.
- | otherwise = filter (hu_id /=) [baseUnitId dflags, ghcInternalUnitId, rtsUnitId]
+ | otherwise = filter (hu_id /=) (baseUnitId dflags:wiredInUnitIds)
-- if the home unit is indefinite, it means we are type-checking it only
-- (not producing any code). Hence we can use virtual units instantiated
=====================================
hadrian/hadrian.cabal
=====================================
@@ -86,7 +86,6 @@ executable hadrian
, Rules.Documentation
, Rules.Generate
, Rules.Gmp
- , Rules.Libffi
, Rules.Library
, Rules.Lint
, Rules.Nofib
=====================================
hadrian/src/Builder.hs
=====================================
@@ -229,25 +229,16 @@ instance H.Builder Builder where
-- changes (#18001).
_bootGhcVersion <- setting GhcVersion
pure []
- Ghc _ st -> do
+ Ghc _ _ -> do
root <- buildRoot
unlitPath <- builderPath Unlit
distro_mingw <- lookupSystemConfig "settings-use-distro-mingw"
- libffi_adjustors <- useLibffiForAdjustors
- use_system_ffi <- flag UseSystemFfi
return $ [ unlitPath ]
++ [ root -/- mingwStamp | windowsHost, distro_mingw == "NO" ]
-- proxy for the entire mingw toolchain that
-- we have in inplace/mingw initially, and then at
-- root -/- mingw.
- -- ffi.h needed by the compiler when using libffi_adjustors (#24864)
- -- It would be nicer to not duplicate this logic between here
- -- and needRtsLibffiTargets and libffiHeaderFiles but this doesn't change
- -- very often.
- ++ [ root -/- buildDir (rtsContext st) -/- "include" -/- header
- | header <- ["ffi.h", "ffitarget.h"]
- , libffi_adjustors && not use_system_ffi ]
Hsc2Hs stage -> (\p -> [p]) <$> templateHscPath stage
Make dir -> return [dir -/- "Makefile"]
=====================================
hadrian/src/Packages.hs
=====================================
@@ -110,7 +110,7 @@ hpc = lib "hpc"
hpcBin = util "hpc-bin" `setPath` "utils/hpc"
integerGmp = lib "integer-gmp"
iservProxy = util "iserv-proxy"
-libffi = top "libffi"
+libffi = lib "libffi-clib"
mtl = lib "mtl"
osString = lib "os-string"
parsec = lib "parsec"
=====================================
hadrian/src/Rules.hs
=====================================
@@ -21,7 +21,6 @@ import qualified Rules.Dependencies
import qualified Rules.Documentation
import qualified Rules.Generate
import qualified Rules.Gmp
-import qualified Rules.Libffi
import qualified Rules.Library
import qualified Rules.Program
import qualified Rules.Register
@@ -80,7 +79,7 @@ packageTargets stage pkg = do
then return [] -- Skip inactive packages.
else if isLibrary pkg
then do -- Collect all targets of a library package.
- let pkgWays = if pkg == rts then getRtsWays else getLibraryWays
+ let pkgWays = if pkg `elem` [rts, libffi] then getRtsWays else getLibraryWays
ways <- interpretInContext context pkgWays
libs <- mapM (\w -> pkgLibraryFile (Context stage pkg w (error "unused"))) (Set.toList ways)
more <- Rules.Library.libraryTargets context
@@ -126,7 +125,6 @@ buildRules = do
Rules.Generate.generateRules
Rules.Generate.templateRules
Rules.Gmp.gmpRules
- Rules.Libffi.libffiRules
Rules.Library.libraryRules
Rules.Rts.rtsRules
packageRules
=====================================
hadrian/src/Rules/Documentation.hs
=====================================
@@ -232,6 +232,9 @@ buildSphinxHtml path = do
------------------------------------ Haddock -----------------------------------
+haddockExclude :: [FilePath]
+haddockExclude = ["rts", "libffi-clib"]
+
-- | Build the haddocks for GHC's libraries.
buildLibraryDocumentation :: Rules ()
buildLibraryDocumentation = do
@@ -241,11 +244,11 @@ buildLibraryDocumentation = do
root -/- htmlRoot -/- "libraries/index.html" %> \file -> do
need [ "libraries/prologue.txt" ]
- -- We want Haddocks for everything except `rts` to be built, but we
+ -- We want Haddocks for everything except `rts` and `libffi-clib` to be built, but we
-- don't want the index to be polluted by stuff from `ghc`-the-library
-- (there will be a separate top-level link to those Haddocks).
haddocks <- allHaddocks
- let neededDocs = filter (\x -> takeFileName x /= "rts.haddock") haddocks
+ let neededDocs = filter (\x -> takeFileName x `notElem` ((<.> "haddock") <$> haddockExclude)) haddocks
libDocs = filter (\x -> takeFileName x /= "ghc.haddock") neededDocs
need neededDocs
@@ -255,7 +258,7 @@ allHaddocks :: Action [FilePath]
allHaddocks = do
pkgs <- stagePackages Stage1
sequence [ pkgHaddockFile $ vanillaContext Stage1 pkg
- | pkg <- pkgs, isLibrary pkg, pkgName pkg /= "rts" ]
+ | pkg <- pkgs, isLibrary pkg, pkgName pkg `notElem` haddockExclude ]
-- Note: this build rule creates plenty of files, not just the .haddock one.
-- All of them go into the 'docRoot' subdirectory. Pedantically tracking all
@@ -427,4 +430,4 @@ haddockDependencies :: Context -> Action [(Package, FilePath)]
haddockDependencies context = do
depNames <- interpretInContext context (getContextData depNames)
sequence [ (,) <$> pure depPkg <*> (pkgHaddockFile $ vanillaContext Stage1 depPkg)
- | Just depPkg <- map findPackageByName depNames, depPkg /= rts ]
+ | Just depPkg <- map findPackageByName depNames, (pkgName depPkg) `notElem` haddockExclude ]
=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -18,7 +18,6 @@ import Hadrian.Haskell.Cabal.Type (PackageData(version))
import Hadrian.Haskell.Cabal
import Hadrian.Oracles.Cabal (readPackageData)
import Packages
-import Rules.Libffi
import Settings
import Target
import Utilities
@@ -57,7 +56,6 @@ rtsDependencies = do
stage <- getStage
rtsPath <- expr (rtsBuildPath stage)
jsTarget <- expr isJsTarget
- useSystemFfi <- expr (flag UseSystemFfi)
let -- headers common to native and JS RTS
common_headers =
@@ -69,7 +67,6 @@ rtsDependencies = do
[ "rts" -/- "EventTypes.h"
, "rts" -/- "EventLogConstants.h"
]
- ++ (if useSystemFfi then [] else libffiHeaderFiles)
headers
| jsTarget = common_headers
| otherwise = common_headers ++ native_headers
=====================================
hadrian/src/Rules/Libffi.hs deleted
=====================================
@@ -1,243 +0,0 @@
-{-# LANGUAGE TypeFamilies #-}
-
-module Rules.Libffi (
- LibffiDynLibs(..),
- needLibffi, askLibffilDynLibs, libffiRules, libffiLibrary, libffiHeaderFiles,
- libffiHeaderDir, libffiSystemHeaderDir, libffiName
- ) where
-
-import Hadrian.Utilities
-
-import Packages
-import Settings.Builders.Common
-import Target
-import Utilities
-import GHC.Toolchain (targetPlatformTriple)
-
-{- Note [Libffi indicating inputs]
- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-First see https://gitlab.haskell.org/ghc/ghc/wikis/Developing-Hadrian for an
-explanation of "indicating input". Part of the definition is copied here for
-your convenience:
-
- change in the vital output -> change in the indicating inputs
-
-In the case of building libffi `vital output = built libffi library files` and
-we can consider the libffi archive file (i.e. the "libffi-tarballs/libffi*.tar.gz"
-file) to be the only indicating input besides the build tools (e.g. make).
-Note building libffi is split into a few rules, but we also expect that:
-
- no change in the archive file -> no change in the intermediate build artifacts
-
-and so the archive file is still a valid choice of indicating input for
-all libffi rules. Hence we can get away with `need`ing only the archive file and
-don't have to `need` intermediate build artifacts (besides those to trigger
-dependant libffi rules i.e. to generate vital inputs as is noted on the wiki).
-It is then safe to `trackAllow` the libffi build directory as is done in
-`needLibfffiArchive`.
-
-A disadvantage to this approach is that changing the archive file forces a clean
-build of libffi i.e. we cannot incrementally build libffi. This seems like a
-performance issue, but is justified as building libffi is fast and the archive
-file is rarely changed.
-
--}
-
--- | Oracle question type. The oracle returns the list of dynamic
--- libffi library file paths (all but one of which should be symlinks).
-newtype LibffiDynLibs = LibffiDynLibs Stage
- deriving (Eq, Show, Hashable, Binary, NFData)
-type instance RuleResult LibffiDynLibs = [FilePath]
-
-askLibffilDynLibs :: Stage -> Action [FilePath]
-askLibffilDynLibs stage = askOracle (LibffiDynLibs stage)
-
--- | The path to the dynamic library manifest file. The file contains all file
--- paths to libffi dynamic library file paths.
--- The path is calculated but not `need`ed.
-dynLibManifest' :: Monad m => m FilePath -> Stage -> m FilePath
-dynLibManifest' getRoot stage = do
- root <- getRoot
- return $ root -/- stageString stage -/- pkgName libffi -/- ".dynamiclibs"
-
-dynLibManifestRules :: Stage -> Rules FilePath
-dynLibManifestRules = dynLibManifest' buildRootRules
-
-dynLibManifest :: Stage -> Action FilePath
-dynLibManifest = dynLibManifest' buildRoot
-
--- | Need the (locally built) libffi library.
-needLibffi :: Stage -> Action ()
-needLibffi stage = do
- jsTarget <- isJsTarget
- unless jsTarget $ do
- manifest <- dynLibManifest stage
- need [manifest]
-
--- | Context for @libffi@.
-libffiContext :: Stage -> Action Context
-libffiContext stage = do
- ways <- interpretInContext
- (Context stage libffi (error "libffiContext: way not set") (error "libffiContext: iplace not set"))
- getLibraryWays
- return $ (\w -> Context stage libffi w Final) (if any (wayUnit Dynamic) ways
- then dynamic
- else vanilla)
-
--- | The name of the library
-libffiName :: Expr String
-libffiName = do
- useSystemFfi <- expr (flag UseSystemFfi)
- if useSystemFfi
- then pure "ffi"
- else libffiLocalName Nothing
-
--- | The name of the (locally built) library
-libffiLocalName :: Maybe Bool -> Expr String
-libffiLocalName force_dynamic = do
- way <- getWay
- winTarget <- expr isWinTarget
- let dynamic = fromMaybe (Dynamic `wayUnit` way) force_dynamic
- pure $ mconcat
- [ if dynamic then "" else "C"
- , if winTarget then "ffi-6" else "ffi"
- ]
-
-libffiLibrary :: FilePath
-libffiLibrary = "inst/lib/libffi.a"
-
--- | These are the headers that we must package with GHC since foreign export
--- adjustor code produced by GHC depends upon them.
--- See Note [Packaging libffi headers] in GHC.Driver.CodeOutput.
-libffiHeaderFiles :: [FilePath]
-libffiHeaderFiles = ["ffi.h", "ffitarget.h"]
-
-libffiHeaderDir :: Stage -> Action FilePath
-libffiHeaderDir stage = do
- path <- libffiBuildPath stage
- return $ path -/- "inst/include"
-
-libffiSystemHeaderDir :: Action FilePath
-libffiSystemHeaderDir = setting FfiIncludeDir
-
-fixLibffiMakefile :: FilePath -> String -> String
-fixLibffiMakefile top =
- replace "-MD" "-MMD"
- . replace "@toolexeclibdir@" "$(libdir)"
- . replace "@INSTALL@" ("$(subst ../install-sh," ++ top ++ "/install-sh,@INSTALL@)")
-
--- TODO: check code duplication w.r.t. ConfCcArgs
-configureEnvironment :: Stage -> Action [CmdOption]
-configureEnvironment stage = do
- context <- libffiContext stage
- cFlags <- interpretInContext context getStagedCCFlags
- sequence [ builderEnvironment "CC" $ Cc CompileC stage
- , builderEnvironment "CXX" $ Cc CompileC stage
- , builderEnvironment "AR" $ Ar Unpack stage
- , builderEnvironment "NM" Nm
- , builderEnvironment "RANLIB" Ranlib
- , return . AddEnv "CFLAGS" $ unwords cFlags ++ " -w"
- , return . AddEnv "LDFLAGS" $ "-w" ]
-
--- Need the libffi archive and `trackAllow` all files in the build directory.
--- See [Libffi indicating inputs].
-needLibfffiArchive :: FilePath -> Action FilePath
-needLibfffiArchive buildPath = do
- top <- topDirectory
- tarball <- unifyPath
- . fromSingleton "Exactly one LibFFI tarball is expected"
- <$> getDirectoryFiles top ["libffi-tarballs/libffi*.tar.gz"]
- need [top -/- tarball]
- trackAllow [buildPath -/- "**"]
- return tarball
-
-libffiRules :: Rules ()
-libffiRules = do
- _ <- addOracleCache $ \ (LibffiDynLibs stage)
- -> do
- jsTarget <- isJsTarget
- if jsTarget
- then return []
- else readFileLines =<< dynLibManifest stage
- forM_ [Stage1, Stage2, Stage3] $ \stage -> do
- root <- buildRootRules
- let path = root -/- stageString stage
- libffiPath = path -/- pkgName libffi -/- "build"
-
- -- We set a higher priority because this rule overlaps with the build rule
- -- for static libraries 'Rules.Library.libraryRules'.
- dynLibMan <- dynLibManifestRules stage
- let topLevelTargets = [ libffiPath -/- libffiLibrary
- , dynLibMan
- ]
- priority 2 $ topLevelTargets &%> \_ -> do
- _ <- needLibfffiArchive libffiPath
- context <- libffiContext stage
-
- -- Note this build needs the Makefile, triggering the rules bellow.
- build $ target context (Make libffiPath) [] []
- libffiName' <- interpretInContext context (libffiLocalName (Just True))
-
- -- Produces all install files.
- produces =<< (\\ topLevelTargets)
- <$> liftIO (getDirectoryFilesIO "." [libffiPath -/- "inst//*"])
-
- -- Find dynamic libraries.
- osxTarget <- isOsxTarget
- winTarget <- isWinTarget
-
- dynLibFiles <- do
- let libfilesDir = libffiPath -/-
- (if winTarget then "inst" -/- "bin" else "inst" -/- "lib")
- dynlibext
- | winTarget = "dll"
- | osxTarget = "dylib"
- | otherwise = "so"
- filepat = "lib" ++ libffiName' ++ "." ++ dynlibext ++ "*"
- liftIO $ getDirectoryFilesIO "." [libfilesDir -/- filepat]
-
- writeFileLines dynLibMan dynLibFiles
- putSuccess "| Successfully build libffi."
-
- fmap (libffiPath -/-) ( "Makefile.in" :& "configure" :& Nil ) &%>
- \ ( mkIn :& _ ) -> do
- -- Extract libffi tar file
- context <- libffiContext stage
- removeDirectory libffiPath
- tarball <- needLibfffiArchive libffiPath
- -- Go from 'libffi-3.99999+git20171002+77e130c.tar.gz' to 'libffi-3.99999'
- let libname = takeWhile (/= '+') $ fromJust $ stripExtension "tar.gz" $ takeFileName tarball
-
- -- Move extracted directory to libffiPath.
- root <- buildRoot
- removeDirectory (root -/- libname)
- actionFinally (do
- build $ target context (Tar Extract) [tarball] [path]
- moveDirectory (path -/- libname) libffiPath) $
- -- And finally:
- removeFiles (path) [libname -/- "**"]
-
- top <- topDirectory
- fixFile mkIn (fixLibffiMakefile top)
-
- files <- liftIO $ getDirectoryFilesIO "." [libffiPath -/- "**"]
- produces files
-
- fmap (libffiPath -/-) ("Makefile" :& "config.guess" :& "config.sub" :& Nil)
- &%> \( mk :& _ ) -> do
- _ <- needLibfffiArchive libffiPath
- context <- libffiContext stage
-
- -- This need rule extracts the libffi tar file to libffiPath.
- need [mk <.> "in"]
-
- -- Configure.
- forM_ ["config.guess", "config.sub"] $ \file -> do
- copyFile file (libffiPath -/- file)
- env <- configureEnvironment stage
- buildWithCmdOptions env $
- target context (Configure libffiPath) [mk <.> "in"] [mk]
-
- dir <- queryBuildTarget targetPlatformTriple
- files <- liftIO $ getDirectoryFilesIO "." [libffiPath -/- dir -/- "**"]
- produces files
=====================================
hadrian/src/Rules/Register.hs
=====================================
@@ -147,7 +147,7 @@ buildConfFinal :: [(Resource, Int)] -> Context -> FilePath -> Action ()
buildConfFinal rs context@Context {..} _conf = do
depPkgIds <- cabalDependencies context
ensureConfigured context
- ways <- interpretInContext context (getLibraryWays <> if package == rts then getRtsWays else mempty)
+ ways <- interpretInContext context (getLibraryWays <> if package `elem` [rts, libffi] then getRtsWays else mempty)
stamps <- mapM pkgStampFile [ context { way = w } | w <- Set.toList ways ]
confs <- mapM (\pkgId -> packageDbPath (PackageDbLoc stage Final) <&> (-/- pkgId <.> "conf")) depPkgIds
-- Important to need these together to avoid introducing a linearisation. This is not the most critical place
@@ -295,20 +295,10 @@ parseCabalName s = bimap show id (Cabal.runParsecParser parser "<parseCabalName>
where
component = CabalCharParsing.munch1 (\c -> Char.isAlphaNum c || c == '.')
-
-
--- | Return extra library targets.
-extraTargets :: Context -> Action [FilePath]
-extraTargets context
- | package context == rts = needRtsLibffiTargets (Context.stage context)
- | otherwise = return []
-
-- | Given a library 'Package' this action computes all of its targets. Needing
-- all the targets should build the library such that it is ready to be
-- registered into the package database.
libraryTargets :: Context -> Action [FilePath]
libraryTargets context = do
libFile <- pkgLibraryFile context
- extra <- extraTargets context
- return $ [ libFile ]
- ++ extra
+ return [ libFile ]
=====================================
hadrian/src/Rules/Rts.hs
=====================================
@@ -1,14 +1,12 @@
{-# LANGUAGE MultiWayIf #-}
-module Rules.Rts (rtsRules, needRtsLibffiTargets, needRtsSymLinks) where
+module Rules.Rts (rtsRules, needRtsSymLinks) where
import qualified Data.Set as Set
import Packages (rts)
-import Rules.Libffi
import Hadrian.Utilities
import Settings.Builders.Common
-import Context.Type
-- | This rule has priority 3 to override the general rule for generating shared
-- library files (see Rules.Library.libraryRules).
@@ -26,134 +24,6 @@ rtsRules = priority 3 $ do
(addRtsDummyVersion $ takeFileName rtsLibFilePath')
rtsLibFilePath'
- -- Libffi
- forM_ [Stage1, Stage2, Stage3 ] $ \ stage -> do
- let buildPath = root -/- buildDir (rtsContext stage)
-
- -- Header files
- -- See Note [Packaging libffi headers] in GHC.Driver.CodeOutput.
- forM_ libffiHeaderFiles $ \header ->
- buildPath -/- "include" -/- header %> copyLibffiHeader stage
-
- -- Static libraries.
- buildPath -/- "libCffi*.a" %> copyLibffiStatic stage
-
- -- Dynamic libraries
- buildPath -/- "libffi*.dylib*" %> copyLibffiDynamicUnix stage ".dylib"
- buildPath -/- "libffi*.so*" %> copyLibffiDynamicUnix stage ".so"
- buildPath -/- "libffi*.dll*" %> copyLibffiDynamicWin stage
-
-withLibffi :: Stage -> (FilePath -> FilePath -> Action a) -> Action a
-withLibffi stage action = needLibffi stage
- >> (join $ action <$> libffiBuildPath stage
- <*> rtsBuildPath stage)
-
--- | Copy a header files wither from the system libffi or from the libffi
--- build dir to the rts build dir.
---
--- See Note [Packaging libffi headers] in GHC.Driver.CodeOutput.
-copyLibffiHeader :: Stage -> FilePath -> Action ()
-copyLibffiHeader stage header = do
- useSystemFfi <- flag UseSystemFfi
- (fromStr, headerDir) <- if useSystemFfi
- then ("system",) <$> libffiSystemHeaderDir
- else needLibffi stage
- >> ("custom",) <$> libffiHeaderDir stage
- copyFile
- (headerDir -/- takeFileName header)
- header
- putSuccess $ "| Successfully copied " ++ fromStr ++ " FFI library header "
- ++ "files to RTS build directory."
-
--- | Copy a static library file from the libffi build dir to the rts build dir.
-copyLibffiStatic :: Stage -> FilePath -> Action ()
-copyLibffiStatic stage target = withLibffi stage $ \ libffiPath _ -> do
- -- Copy the vanilla library, and symlink the rest to it.
- vanillaLibFile <- rtsLibffiLibrary stage vanilla
- if target == vanillaLibFile
- then copyFile' (libffiPath -/- libffiLibrary) target
- else createFileLink (takeFileName vanillaLibFile) target
-
-
--- | Copy a dynamic library file from the libffi build dir to the rts build dir.
-copyLibffiDynamicUnix :: Stage -> String -> FilePath -> Action ()
-copyLibffiDynamicUnix stage libSuf target = do
- needLibffi stage
- dynLibs <- askLibffilDynLibs stage
-
- -- If no version number suffix, then copy else just symlink.
- let versionlessSourceFilePath = fromMaybe
- (error $ "Needed " ++ show target ++ " which is not any of " ++
- "libffi's built shared libraries: " ++ show dynLibs)
- (find (libSuf `isSuffixOf`) dynLibs)
- let versionlessSourceFileName = takeFileName versionlessSourceFilePath
- if versionlessSourceFileName == takeFileName target
- then do
- copyFile' versionlessSourceFilePath target
-
- -- On OSX the dylib's id must be updated to a relative path.
- when osxHost $ cmd
- [ "install_name_tool"
- , "-id", "@rpath/" ++ takeFileName target
- , target
- ]
- else createFileLink versionlessSourceFileName target
-
--- | Copy a dynamic library file from the libffi build dir to the rts build dir.
-copyLibffiDynamicWin :: Stage -> FilePath -> Action ()
-copyLibffiDynamicWin stage target = do
- needLibffi stage
- dynLibs <- askLibffilDynLibs stage
- let source = fromMaybe
- (error $ "Needed " ++ show target ++ " which is not any of " ++
- "libffi's built shared libraries: " ++ show dynLibs)
- (find (\ lib -> takeFileName target == takeFileName lib) dynLibs)
- copyFile' source target
-
-rtsLibffiLibrary :: Stage -> Way -> Action FilePath
-rtsLibffiLibrary stage way = do
- name <- interpretInContext ((rtsContext stage) { way = way }) libffiName
- suf <- if wayUnit Dynamic way
- then do
- extension <- setting DynamicExtension -- e.g., .dll or .so
- let suffix = waySuffix (removeWayUnit Dynamic way)
- return (suffix ++ extension)
- -- Static suffix
- else return (waySuffix way ++ ".a") -- e.g., _p.a
- rtsPath <- rtsBuildPath stage
- return $ rtsPath -/- "lib" ++ name ++ suf
-
--- | Get the libffi files bundled with the rts (header and library files).
--- Unless using the system libffi, this needs the libffi library. It must be
--- built before the targets can be calculated.
-needRtsLibffiTargets :: Stage -> Action [FilePath]
-needRtsLibffiTargets stage = do
- rtsPath <- rtsBuildPath stage
- useSystemFfi <- flag UseSystemFfi
- jsTarget <- isJsTarget
-
- -- Header files (in the rts build dir).
- let headers = fmap ((rtsPath -/- "include") -/-) libffiHeaderFiles
-
- if | jsTarget -> return []
- | useSystemFfi -> return []
- | otherwise -> do
- -- Need Libffi
- -- This returns the dynamic library files (in the Libffi build dir).
- needLibffi stage
- dynLibffSource <- askLibffilDynLibs stage
-
- -- Dynamic library files (in the rts build dir).
- let dynLibffis = fmap (\ lib -> rtsPath -/- takeFileName lib)
- dynLibffSource
-
- -- Libffi files (in the rts build dir).
- libffis_libs <- do
- ways <- interpretInContext (stageContext stage)
- (getLibraryWays <> getRtsWays)
- mapM (rtsLibffiLibrary stage) (Set.toList ways)
- return $ concat [ headers, dynLibffis, libffis_libs ]
-
-- Need symlinks generated by rtsRules.
needRtsSymLinks :: Stage -> Set.Set Way -> Action ()
needRtsSymLinks stage rtsWays
=====================================
hadrian/src/Rules/SourceDist.hs
=====================================
@@ -155,6 +155,9 @@ prepareTree dest = do
, pkgPath time -/- "lib" -/- "include" -/- "HsTimeConfig.h.in"
, pkgPath unix -/- "configure"
, pkgPath unix -/- "include" -/- "HsUnixConfig.h.in"
+ , pkgPath libffi -/- "configure"
+ , pkgPath libffi -/- "fficonfig.h.in"
+ , pkgPath libffi -/- "include" -/- "ffi.h.in"
, pkgPath terminfo -/- "configure"
, "configure"
, "aclocal.m4"
=====================================
hadrian/src/Settings/Builders/Cabal.hs
=====================================
@@ -184,7 +184,8 @@ configureArgs cFlags' ldFlags' = do
, arg $ top -/- pkgPath pkg
, cFlags'
]
- mconcat
+ useSystemFfi <- getFlag UseSystemFfi
+ mconcat $
[ conf "CFLAGS" cFlags
, conf "LDFLAGS" ldFlags'
, conf "--with-iconv-includes" $ arg =<< getSetting IconvIncludeDir
@@ -198,7 +199,7 @@ configureArgs cFlags' ldFlags' = do
, conf "--host" $ arg =<< getSetting TargetPlatformFull
, conf "--with-cc" $ arg =<< getBuilderPath . (Cc CompileC) =<< getStage
, ghcVersionH
- ]
+ ] ++ if useSystemFfi then [arg "--configure-option=--with-system-libffi"] else []
bootPackageConstraints :: Args
bootPackageConstraints = (stage0InTree ==) <$> getStage ? do
=====================================
hadrian/src/Settings/Builders/Ghc.hs
=====================================
@@ -10,7 +10,6 @@ import Packages
import Settings.Builders.Common
import Settings.Warnings
import qualified Context as Context
-import Rules.Libffi (libffiName)
import qualified Data.Set as Set
import Data.Version.Extra
@@ -106,9 +105,6 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
context <- getContext
distPath <- expr (Context.distDynDir context)
- useSystemFfi <- expr (flag UseSystemFfi)
- buildPath <- getBuildPath
- libffiName' <- libffiName
debugged <- buildingCompilerStage' . ghcDebugged =<< expr flavour
osxTarget <- expr isOsxTarget
@@ -127,17 +123,6 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
metaOrigin | osxTarget = "@loader_path"
| otherwise = "$ORIGIN"
- -- TODO: an alternative would be to generalize by linking with extra
- -- bundled libraries, but currently the rts is the only use case. It is
- -- a special case when `useSystemFfi == True`: the ffi library files
- -- are not actually bundled with the rts. Perhaps ffi should be part of
- -- rts's extra libraries instead of extra bundled libraries in that
- -- case. Care should be take as to not break the make build.
- rtsFfiArg = package rts ? not useSystemFfi ? mconcat
- [ arg ("-L" ++ buildPath)
- , arg ("-l" ++ libffiName')
- ]
-
-- This is the -rpath argument that is required for the bindist scenario
-- to work. Indeed, when you install a bindist, the actual executables
-- end up nested somewhere under $libdir, with the wrapper scripts
@@ -166,7 +151,6 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
, (not (nonHsMainPackage pkg) && not (isLibrary pkg)) ? arg "-rtsopts"
, pure [ "-l" ++ lib | lib <- libs ]
, pure [ "-L" ++ libDir | libDir <- libDirs ]
- , rtsFfiArg
, osxTarget ? pure (concat [ ["-framework", fmwk] | fmwk <- fmwks ])
, debugged ? packageOneOf [ghc, iservProxy, remoteIserv] ?
arg "-debug"
=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -141,7 +141,9 @@ stage1Packages = do
libraries0 <- filter good_stage0_package <$> stage0Packages
cross <- flag CrossCompiling
winTarget <- isWinTarget
+ jsTarget <- isJsTarget
haveCurses <- any (/= "") <$> traverse setting [ CursesIncludeDir, CursesLibDir ]
+ useSystemFfi <- flag UseSystemFfi
let when c xs = if c then xs else mempty
@@ -194,6 +196,10 @@ stage1Packages = do
[
terminfo
]
+ , when (not jsTarget && not useSystemFfi)
+ [
+ libffi
+ ]
]
-- | Packages built in 'Stage2' by default. You can change this in "UserSettings".
=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -215,6 +215,7 @@ packageArgs = do
---------------------------------- rts ---------------------------------
, package rts ? rtsPackageArgs -- RTS deserves a separate function
+ , package libffi ? libffiPackageArgs
-------------------------------- runGhc --------------------------------
, package runGhc ?
@@ -275,6 +276,19 @@ ghcInternalArgs = package ghcInternal ? do
]
+-- libffi and rts have to have the same flavour configuration
+libffiPackageArgs :: Args
+libffiPackageArgs = package libffi ? do
+ rtsWays <- getRtsWays
+ mconcat
+ [ builder (Cabal Flags) ? mconcat
+ [ any (wayUnit Profiling) rtsWays `cabalFlag` "profiling"
+ , any (wayUnit Debug) rtsWays `cabalFlag` "debug"
+ , any (wayUnit Dynamic) rtsWays `cabalFlag` "dynamic"
+ , any (wayUnit Threaded) rtsWays `cabalFlag` "threaded"
+ ]
+ ]
+
-- | RTS-specific command line arguments.
rtsPackageArgs :: Args
rtsPackageArgs = package rts ? do
@@ -285,8 +299,6 @@ rtsPackageArgs = package rts ? do
path <- getBuildPath
top <- expr topDirectory
useSystemFfi <- getFlag UseSystemFfi
- ffiIncludeDir <- getSetting FfiIncludeDir
- ffiLibraryDir <- getSetting FfiLibDir
libdwIncludeDir <- queryTarget (Lib.includePath <=< tgtRTSWithLibdw)
libdwLibraryDir <- queryTarget (Lib.libraryPath <=< tgtRTSWithLibdw)
libnumaIncludeDir <- getSetting LibnumaIncludeDir
@@ -428,7 +440,6 @@ rtsPackageArgs = package rts ? do
[ useLibdw ? cabalExtraDirs (fromMaybe "" libdwIncludeDir) (fromMaybe "" libdwLibraryDir)
, cabalExtraDirs libnumaIncludeDir libnumaLibraryDir
, cabalExtraDirs libzstdIncludeDir libzstdLibraryDir
- , useSystemFfi ? cabalExtraDirs ffiIncludeDir ffiLibraryDir
]
, builder (Cc (FindCDependencies CDep)) ? cArgs
, builder (Cc (FindCDependencies CxxDep)) ? cArgs
=====================================
libffi-tarballs deleted
=====================================
@@ -1 +0,0 @@
-Subproject commit 7c51059557b68d29820a0a87cebfa6fe73c8adf5
=====================================
libraries/libffi-clib
=====================================
@@ -0,0 +1 @@
+Subproject commit 5323bdcc5229191884edb186709b7b91fe5117ee
=====================================
packages
=====================================
@@ -37,7 +37,6 @@
# localpath tag remotepath upstreamurl
# ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
ghc-tarballs windows ghc-tarballs.git -
-libffi-tarballs - - -
utils/hsc2hs - - ssh://git@github.com/haskell/hsc2hs.git
libraries/array - - -
libraries/binary - - https://github.com/kolmodin/binary.git
=====================================
rts/include/rts/ghc_ffi.h
=====================================
@@ -25,4 +25,4 @@
#endif
#endif
-#include "ffi.h"
+#include
participants (1)
-
Marge Bot (@marge-bot)