Support GHC 9.12
[cabal.git] / Cabal / src / Distribution / Simple / GHC / Build.hs
blobcc50e3bdb3cc43c47707e64435a1dd3190f5c2d0
1 module Distribution.Simple.GHC.Build where
3 import Distribution.Compat.Prelude
4 import Prelude ()
6 import Control.Monad.IO.Class
7 import qualified Data.Set as Set
8 import Distribution.PackageDescription as PD hiding (buildInfo)
9 import Distribution.Simple.Build.Inputs
10 import Distribution.Simple.Flag (Flag)
11 import Distribution.Simple.GHC.Build.ExtraSources
12 import Distribution.Simple.GHC.Build.Link
13 import Distribution.Simple.GHC.Build.Modules
14 import Distribution.Simple.GHC.Build.Utils (withDynFLib)
15 import Distribution.Simple.LocalBuildInfo
16 import Distribution.Simple.Program
17 import Distribution.Simple.Utils
18 import Distribution.Types.ComponentLocalBuildInfo (componentIsIndefinite)
19 import Distribution.Types.ParStrat
20 import Distribution.Utils.NubList (fromNubListR)
21 import System.Directory hiding (exeExtension)
22 import System.FilePath
25 Note [Build Target Dir vs Target Dir]
26 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
28 Where to place the build result (targetDir) and the build artifacts (buildTargetDir).
30 \* For libraries, targetDir == buildTargetDir, where both the library and
31 artifacts are put together.
33 \* For executables or foreign libs, buildTargetDir == targetDir/<name-of-target-dir>-tmp, where
34 the targetDir is the location where the target (e.g. the executable) is written to
35 and buildTargetDir is where the compilation artifacts (e.g. Main.o) will live
36 Arguably, this difference should not exist (#9498) (TODO)
38 For instance, for a component `cabal-benchmarks`:
39 targetDir == <buildDir>/cabal-benchmarks
40 buildTargetDir == <buildDir>/cabal-benchmarks/cabal-benchmarks-tmp
42 Or, for a library `Cabal`:
43 targetDir == <buildDir>/.
44 buildTargetDir == targetDir
46 Furthermore, we need to account for the limit of characters in ghc
47 invocations that different OSes constrain us to. Cabal invocations can
48 rapidly reach this limit, in part, due to the long length of cabal v2
49 prefixes. To minimize the likelihood, we use
50 `makeRelativeToCurrentDirectory` to shorten the paths used in invocations
51 (see da6321bb).
53 However, in executables, we don't do this. It seems that we don't need to do it
54 for executable-like components because the linking step, instead of passing as
55 an argument the path to each module, it simply passes the module name, the sources dir, and --make.
56 RM: I believe we can use --make + module names instead of paths-to-objects
57 for linking libraries too (2024-01) (TODO)
60 -- | The main build phase of building a component.
61 -- Includes building Haskell modules, extra build sources, and linking.
62 build
63 :: Flag ParStrat
64 -> PackageDescription
65 -> PreBuildComponentInputs
66 -- ^ The context and component being built in it.
67 -> IO ()
68 build numJobs pkg_descr pbci = do
69 let
70 verbosity = buildVerbosity pbci
71 component = buildComponent pbci
72 isLib = buildIsLib pbci
73 lbi = localBuildInfo pbci
74 clbi = buildCLBI pbci
76 -- Create a few directories for building the component
77 -- See Note [Build Target Dir vs Target Dir]
78 let targetDir_absolute = componentBuildDir lbi clbi
79 buildTargetDir_absolute
80 -- Libraries use the target dir for building (see above)
81 | isLib = targetDir_absolute
82 -- In other cases, use targetDir/<name-of-target-dir>-tmp
83 | targetDirName : _ <- reverse $ splitDirectories targetDir_absolute =
84 targetDir_absolute </> (targetDirName ++ "-tmp")
85 | otherwise = error "GHC.build: targetDir is empty"
87 liftIO $ do
88 createDirectoryIfMissingVerbose verbosity True targetDir_absolute
89 createDirectoryIfMissingVerbose verbosity True buildTargetDir_absolute
91 -- See Note [Build Target Dir vs Target Dir] as well
92 _targetDir <- liftIO $ makeRelativeToCurrentDirectory targetDir_absolute
93 buildTargetDir <-
94 -- To preserve the previous behaviour, we don't use relative dirs for
95 -- executables. Historically, this isn't needed to reduce the CLI limit
96 -- (unlike for libraries) because we link executables with the module names
97 -- instead of passing the path to object file -- that's something else we
98 -- can now fix after the refactor lands.
99 if isLib
100 then liftIO $ makeRelativeToCurrentDirectory buildTargetDir_absolute
101 else return buildTargetDir_absolute
103 (ghcProg, _) <- liftIO $ requireProgram verbosity ghcProgram (withPrograms lbi)
105 -- Determine in which ways we want to build the component
107 wantVanilla = if isLib then withVanillaLib lbi else False
108 -- Arguably, wantStatic should be "withFullyStaticExe lbi" for executables,
109 -- but it was not before the refactor.
110 wantStatic = if isLib then withStaticLib lbi else not (wantDynamic || wantProf)
111 wantDynamic = case component of
112 CLib{} -> withSharedLib lbi
113 CFLib flib -> withDynFLib flib
114 CExe{} -> withDynExe lbi
115 CTest{} -> withDynExe lbi
116 CBench{} -> withDynExe lbi
117 wantProf = if isLib then withProfLib lbi else withProfExe lbi
119 -- See also Note [Building Haskell Modules accounting for TH] in Distribution.Simple.GHC.Build.Modules
120 -- We build static by default if no other way is wanted.
121 -- For executables and foreign libraries, there should only be one wanted way.
122 wantedWays =
123 Set.fromList $
124 -- If building a library, we accumulate all the ways,
125 -- otherwise, we take just one.
126 (if isLib then id else take 1) $
127 [ProfWay | wantProf]
128 -- I don't see why we shouldn't build with dynamic
129 -- indefinite components.
130 <> [DynWay | wantDynamic && not (componentIsIndefinite clbi)]
131 <> [StaticWay | wantStatic || wantVanilla || not (wantDynamic || wantProf)]
133 liftIO $ info verbosity ("Wanted build ways: " ++ show (Set.toList wantedWays))
135 -- We need a separate build and link phase, and C sources must be compiled
136 -- after Haskell modules, because C sources may depend on stub headers
137 -- generated from compiling Haskell modules (#842, #3294).
138 buildOpts <- buildHaskellModules numJobs ghcProg pkg_descr buildTargetDir_absolute wantedWays pbci
139 extraSources <- buildAllExtraSources ghcProg buildTargetDir pbci
140 linkOrLoadComponent ghcProg pkg_descr (fromNubListR extraSources) (buildTargetDir, targetDir_absolute) (wantedWays, buildOpts) pbci