Skip to content
Snippets Groups Projects
Commit 638f6548 authored by Ben Gamari's avatar Ben Gamari Committed by Marge Bot
Browse files

hadrian: Turn the `static` flavour into a transformer

This turns the `static` flavour into the `+fully_static` flavour
transformer.
parent ed9ec655
No related branches found
No related tags found
No related merge requests found
......@@ -989,7 +989,7 @@ release-x86_64-linux-ubuntu2004:
allow_failure: true
variables:
TEST_ENV: "x86_64-linux-alpine"
BUILD_FLAVOUR: "static"
BUILD_FLAVOUR: "validate+fully_static"
BIN_DIST_NAME: "ghc-x86_64-alpine-linux"
# Can't use ld.gold due to #13958.
CONFIGURE_ARGS: "--disable-ld-override"
......@@ -1015,7 +1015,7 @@ release-x86_64-linux-alpine-integer-simple:
- .release
variables:
BIGNUM_BACKEND: native
BUILD_FLAVOUR: "static"
BUILD_FLAVOUR: "validate+fully_static"
release-x86_64-linux-alpine-integer-gmp:
extends:
......@@ -1023,7 +1023,7 @@ release-x86_64-linux-alpine-integer-gmp:
- .release
variables:
BIGNUM_BACKEND: gmp
BUILD_FLAVOUR: "static"
BUILD_FLAVOUR: "validate+fully_static"
nightly-x86_64-linux-alpine:
<<: *nightly
......
......@@ -112,7 +112,6 @@ executable hadrian
, Settings.Flavours.Quick
, Settings.Flavours.QuickCross
, Settings.Flavours.Quickest
, Settings.Flavours.Static
, Settings.Flavours.Validate
, Settings.Packages
, Settings.Parser
......
......@@ -45,6 +45,7 @@ flavourTransformers = M.fromList
, "no_profiled_libs" =: disableProfiledLibs
, "omit_pragmas" =: omitPragmas
, "ipe" =: enableIPE
, "fully_static" =: fullyStatic
]
where (=:) = (,)
......@@ -179,9 +180,12 @@ disableDynamicGhcPrograms flavour = flavour { dynamicGhcPrograms = pure False }
-- | Don't build libraries in profiled 'Way's.
disableProfiledLibs :: Flavour -> Flavour
disableProfiledLibs flavour =
flavour { libraryWays = filter (not . wayUnit Profiling) <$> libraryWays flavour
, rtsWays = filter (not . wayUnit Profiling) <$> rtsWays flavour
flavour { libraryWays = prune $ libraryWays flavour
, rtsWays = prune $ rtsWays flavour
}
where
prune :: Ways -> Ways
prune = fmap $ filter (not . wayUnit Profiling)
-- | Build stage2 compiler with -fomit-interface-pragmas to reduce
-- recompilation.
......@@ -199,6 +203,50 @@ enableIPE =
Right transformer = applySetting kv
in transformer
-- | Produce fully statically-linked executables and build libraries suitable
-- for static linking.
fullyStatic :: Flavour -> Flavour
fullyStatic flavour =
addArgs staticExec
$ flavour { dynamicGhcPrograms = return False
, libraryWays = prune $ libraryWays flavour
, rtsWays = prune $ rtsWays flavour }
where
-- Remove any Way that contains a WayUnit of Dynamic
prune :: Ways -> Ways
prune = fmap $ filter staticCompatible
staticCompatible :: Way -> Bool
staticCompatible = not . wayUnit Dynamic
staticExec :: Args
{- Some packages, especially iserv, seem to force a set of build ways,
- including some that are dynamic (in Rules.BinaryDist). Trying to
- build statically and dynamically at the same time breaks the build,
- so we respect that overriding of the Ways. Any code that overrides
- the Ways will need to include a Way that's not explicitly dynamic
- (like "vanilla").
-}
staticExec = staticCompatible <$> getWay ? mconcat
{-
- Disable dynamic linking by the built ghc executable because the
- statically-linked musl doesn't support dynamic linking, but will
- try and fail.
-}
[ package compiler ? builder (Cabal Flags) ? arg "-dynamic-system-linker"
{-
- The final executables don't work unless the libraries linked into
- it are compiled with "-fPIC." The PI stands for "position
- independent" and generates libraries that work when inlined into
- an executable (where their position is not at the beginning of
- the file).
-}
, builder (Ghc CompileHs) ? pure [ "-fPIC", "-static" ]
, builder (Ghc CompileCWithGhc) ? pure [ "-fPIC", "-optc", "-static"]
, builder (Ghc LinkHs) ? pure [ "-optl", "-static" ]
]
-- * CLI and <root>/hadrian.settings options
{-
......
......@@ -21,7 +21,6 @@ import Settings.Flavours.Performance
import Settings.Flavours.Quick
import Settings.Flavours.Quickest
import Settings.Flavours.QuickCross
import Settings.Flavours.Static
import Settings.Flavours.Validate
......@@ -57,7 +56,7 @@ hadrianFlavours =
, quickestFlavour
, quickCrossFlavour
, ghcInGhciFlavour, validateFlavour, slowValidateFlavour
, staticFlavour ]
]
-- | This action looks up a flavour with the name given on the
-- command line with @--flavour@, defaulting to 'userDefaultFlavour'
......
module Settings.Flavours.Static (staticFlavour) where
import Expression
import Flavour
import Packages
import {-# SOURCE #-} Settings.Default
import Settings.Flavours.Performance (performanceArgs)
-- Please update doc/flavours.md when changing this file.
-- |Produce statically-linked executables. Also compiles libraries
-- suitable for static linking.
staticFlavour :: Flavour
staticFlavour = defaultFlavour
{ name = "static"
, args = defaultBuilderArgs <> performanceArgs <> defaultPackageArgs <> staticExec
, dynamicGhcPrograms = return False
, libraryWays = prune $ libraryWays defaultFlavour
, rtsWays = prune $ rtsWays defaultFlavour
}
-- Remove any Way that contains a WayUnit of Dynamic
prune :: Ways -> Ways
prune = fmap $ filter staticCompatible
staticCompatible :: Way -> Bool
staticCompatible = not . wayUnit Dynamic
staticExec :: Args
{- Some packages, especially iserv, seem to force a set of build ways,
- including some that are dynamic (in Rules.BinaryDist). Trying to
- build statically and dynamically at the same time breaks the build,
- so we respect that overriding of the Ways. Any code that overrides
- the Ways will need to include a Way that's not explicitly dynamic
- (like "vanilla").
-}
staticExec = staticCompatible <$> getWay ? mconcat
{-
- Disable dynamic linking by the built ghc executable because the
- statically-linked musl doesn't support dynamic linking, but will
- try and fail.
-}
[ package compiler ? builder (Cabal Flags) ? arg "-dynamic-system-linker"
{-
- The final executables don't work unless the libraries linked into
- it are compiled with "-fPIC." The PI stands for "position
- independent" and generates libraries that work when inlined into
- an executable (where their position is not at the beginning of
- the file).
-}
, builder (Ghc CompileHs) ? pure [ "-fPIC", "-static" ]
, builder (Ghc CompileCWithGhc) ? pure [ "-fPIC", "-optc", "-static"]
, builder (Ghc LinkHs) ? pure [ "-optl", "-static" ]
]
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