Support GHC 9.12
[cabal.git] / Cabal / src / Distribution / Simple / Build.hs
blobbc6ac7ae6be0dfe95b9c90015dc5be4ef1f2834a
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE RankNTypes #-}
4 {-# LANGUAGE TupleSections #-}
6 -----------------------------------------------------------------------------
8 -- |
9 -- Module : Distribution.Simple.Build
10 -- Copyright : Isaac Jones 2003-2005,
11 -- Ross Paterson 2006,
12 -- Duncan Coutts 2007-2008, 2012
13 -- License : BSD3
15 -- Maintainer : cabal-devel@haskell.org
16 -- Portability : portable
18 -- This is the entry point to actually building the modules in a package. It
19 -- doesn't actually do much itself, most of the work is delegated to
20 -- compiler-specific actions. It does do some non-compiler specific bits like
21 -- running pre-processors.
22 module Distribution.Simple.Build
23 ( -- * Build
24 build
26 -- * Repl
27 , repl
28 , startInterpreter
30 -- * Build preparation
31 , preBuildComponent
32 , AutogenFile (..)
33 , AutogenFileContents
34 , writeBuiltinAutogenFiles
35 , writeAutogenFiles
37 -- * Internal package database creation
38 , createInternalPackageDB
39 ) where
41 import Distribution.Compat.Prelude
42 import Distribution.Utils.Generic
43 import Prelude ()
45 import Distribution.Types.ComponentLocalBuildInfo
46 import Distribution.Types.ComponentRequestedSpec
47 import Distribution.Types.Dependency
48 import Distribution.Types.ExecutableScope
49 import Distribution.Types.ForeignLib
50 import Distribution.Types.LibraryVisibility
51 import Distribution.Types.LocalBuildInfo
52 import Distribution.Types.ModuleRenaming
53 import Distribution.Types.MungedPackageId
54 import Distribution.Types.MungedPackageName
55 import Distribution.Types.ParStrat
56 import Distribution.Types.TargetInfo
57 import Distribution.Utils.Path
59 import Distribution.Backpack
60 import Distribution.Backpack.DescribeUnitId
61 import Distribution.Package
62 import qualified Distribution.Simple.GHC as GHC
63 import qualified Distribution.Simple.GHCJS as GHCJS
64 import qualified Distribution.Simple.HaskellSuite as HaskellSuite
65 import qualified Distribution.Simple.PackageIndex as Index
66 import qualified Distribution.Simple.UHC as UHC
68 import Distribution.Simple.Build.Macros (generateCabalMacrosHeader)
69 import Distribution.Simple.Build.PackageInfoModule (generatePackageInfoModule)
70 import Distribution.Simple.Build.PathsModule (generatePathsModule)
71 import qualified Distribution.Simple.Program.HcPkg as HcPkg
73 import Distribution.InstalledPackageInfo (InstalledPackageInfo)
74 import qualified Distribution.InstalledPackageInfo as IPI
75 import Distribution.ModuleName (ModuleName)
76 import qualified Distribution.ModuleName as ModuleName
77 import Distribution.PackageDescription
78 import Distribution.Simple.Compiler
80 import Distribution.Simple.BuildPaths
81 import Distribution.Simple.BuildTarget
82 import Distribution.Simple.BuildToolDepends
83 import Distribution.Simple.Configure
84 import Distribution.Simple.Flag
85 import Distribution.Simple.LocalBuildInfo
86 import Distribution.Simple.PreProcess
87 import Distribution.Simple.Program
88 import Distribution.Simple.Program.Builtin (haskellSuiteProgram)
89 import qualified Distribution.Simple.Program.GHC as GHC
90 import Distribution.Simple.Program.Types
91 import Distribution.Simple.Register
92 import Distribution.Simple.Setup.Build
93 import Distribution.Simple.Setup.Config
94 import Distribution.Simple.Setup.Repl
95 import Distribution.Simple.ShowBuildInfo
96 import Distribution.Simple.Test.LibV09
97 import Distribution.Simple.Utils
98 import Distribution.Utils.Json
99 import Distribution.Utils.ShortText (ShortText, fromShortText, toShortText)
101 import Distribution.Pretty
102 import Distribution.System
103 import Distribution.Verbosity
104 import Distribution.Version (thisVersion)
106 import Distribution.Compat.Graph (IsNode (..))
108 import Control.Monad
109 import qualified Data.ByteString.Lazy as LBS
110 import qualified Data.Map as Map
111 import Distribution.Simple.Errors
112 import System.Directory (doesFileExist, getCurrentDirectory, removeFile)
113 import System.FilePath (takeDirectory, (<.>), (</>))
115 -- -----------------------------------------------------------------------------
117 -- | Build the libraries and executables in this package.
118 build
119 :: PackageDescription
120 -- ^ Mostly information from the .cabal file
121 -> LocalBuildInfo
122 -- ^ Configuration information
123 -> BuildFlags
124 -- ^ Flags that the user passed to build
125 -> [PPSuffixHandler]
126 -- ^ preprocessors to run before compiling
127 -> IO ()
128 build pkg_descr lbi flags suffixes = do
129 checkSemaphoreSupport verbosity (compiler lbi) flags
130 targets <- readTargetInfos verbosity pkg_descr lbi (buildArgs flags)
131 let componentsToBuild = neededTargetsInBuildOrder' pkg_descr lbi (map nodeKey targets)
132 info verbosity $
133 "Component build order: "
134 ++ intercalate
135 ", "
136 ( map
137 (showComponentName . componentLocalName . targetCLBI)
138 componentsToBuild
141 when (null targets) $
142 -- Only bother with this message if we're building the whole package
143 setupMessage verbosity "Building" (packageId pkg_descr)
145 internalPackageDB <- createInternalPackageDB verbosity lbi distPref
147 -- Before the actual building, dump out build-information.
148 -- This way, if the actual compilation failed, the options have still been
149 -- dumped.
150 dumpBuildInfo verbosity distPref (configDumpBuildInfo (configFlags lbi)) pkg_descr lbi flags
152 -- Now do the actual building
153 (\f -> foldM_ f (installedPkgs lbi) componentsToBuild) $ \index target -> do
154 preBuildComponent verbosity lbi target
155 let comp = targetComponent target
156 clbi = targetCLBI target
157 bi = componentBuildInfo comp
158 progs' = addInternalBuildTools pkg_descr lbi bi (withPrograms lbi)
159 lbi' =
161 { withPrograms = progs'
162 , withPackageDB = withPackageDB lbi ++ [internalPackageDB]
163 , installedPkgs = index
165 par_strat <-
166 toFlag <$> case buildUseSemaphore flags of
167 Flag sem_name -> case buildNumJobs flags of
168 Flag{} -> do
169 warn verbosity $ "Ignoring -j due to --semaphore"
170 return $ UseSem sem_name
171 NoFlag -> return $ UseSem sem_name
172 NoFlag -> return $ case buildNumJobs flags of
173 Flag n -> NumJobs n
174 NoFlag -> Serial
175 mb_ipi <-
176 buildComponent
177 flags
178 par_strat
179 pkg_descr
180 lbi'
181 suffixes
182 comp
183 clbi
184 distPref
185 return (maybe index (Index.insert `flip` index) mb_ipi)
187 return ()
188 where
189 distPref = fromFlag (buildDistPref flags)
190 verbosity = fromFlag (buildVerbosity flags)
192 -- | Check for conditions that would prevent the build from succeeding.
193 checkSemaphoreSupport
194 :: Verbosity -> Compiler -> BuildFlags -> IO ()
195 checkSemaphoreSupport verbosity comp flags = do
196 unless (jsemSupported comp || (isNothing (flagToMaybe (buildUseSemaphore flags)))) $
197 dieWithException verbosity CheckSemaphoreSupport
199 -- | Write available build information for 'LocalBuildInfo' to disk.
201 -- Dumps detailed build information 'build-info.json' to the given directory.
202 -- Build information contains basics such as compiler details, but also
203 -- lists what modules a component contains and how to compile the component, assuming
204 -- lib:Cabal made sure that dependencies are up-to-date.
205 dumpBuildInfo
206 :: Verbosity
207 -> FilePath
208 -- ^ To which directory should the build-info be dumped?
209 -> Flag DumpBuildInfo
210 -- ^ Should we dump detailed build information for this component?
211 -> PackageDescription
212 -- ^ Mostly information from the .cabal file
213 -> LocalBuildInfo
214 -- ^ Configuration information
215 -> BuildFlags
216 -- ^ Flags that the user passed to build
217 -> IO ()
218 dumpBuildInfo verbosity distPref dumpBuildInfoFlag pkg_descr lbi flags = do
219 when shouldDumpBuildInfo $ do
220 -- Changing this line might break consumers of the dumped build info.
221 -- Announce changes on mailing lists!
222 let activeTargets = allTargetsInBuildOrder' pkg_descr lbi
223 info verbosity $
224 "Dump build information for: "
225 ++ intercalate
226 ", "
227 ( map
228 (showComponentName . componentLocalName . targetCLBI)
229 activeTargets
231 pwd <- getCurrentDirectory
233 (compilerProg, _) <- case flavorToProgram (compilerFlavor (compiler lbi)) of
234 Nothing ->
235 dieWithException verbosity $ UnknownCompilerFlavor (compilerFlavor (compiler lbi))
236 Just program -> requireProgram verbosity program (withPrograms lbi)
238 let (warns, json) = mkBuildInfo pwd pkg_descr lbi flags (compilerProg, compiler lbi) activeTargets
239 buildInfoText = renderJson json
240 unless (null warns) $
241 warn verbosity $
242 "Encountered warnings while dumping build-info:\n"
243 ++ unlines warns
244 LBS.writeFile (buildInfoPref distPref) buildInfoText
246 when (not shouldDumpBuildInfo) $ do
247 -- Remove existing build-info.json as it might be outdated now.
248 exists <- doesFileExist (buildInfoPref distPref)
249 when exists $ removeFile (buildInfoPref distPref)
250 where
251 shouldDumpBuildInfo = fromFlagOrDefault NoDumpBuildInfo dumpBuildInfoFlag == DumpBuildInfo
253 -- \| Given the flavor of the compiler, try to find out
254 -- which program we need.
255 flavorToProgram :: CompilerFlavor -> Maybe Program
256 flavorToProgram GHC = Just ghcProgram
257 flavorToProgram GHCJS = Just ghcjsProgram
258 flavorToProgram UHC = Just uhcProgram
259 flavorToProgram JHC = Just jhcProgram
260 flavorToProgram HaskellSuite{} = Just haskellSuiteProgram
261 flavorToProgram _ = Nothing
263 repl
264 :: PackageDescription
265 -- ^ Mostly information from the .cabal file
266 -> LocalBuildInfo
267 -- ^ Configuration information
268 -> ReplFlags
269 -- ^ Flags that the user passed to build
270 -> [PPSuffixHandler]
271 -- ^ preprocessors to run before compiling
272 -> [String]
273 -> IO ()
274 repl pkg_descr lbi flags suffixes args = do
275 let distPref = fromFlag (replDistPref flags)
276 verbosity = fromFlag (replVerbosity flags)
278 target <-
279 readTargetInfos verbosity pkg_descr lbi args >>= \r -> case r of
280 -- This seems DEEPLY questionable.
281 [] -> case allTargetsInBuildOrder' pkg_descr lbi of
282 (target : _) -> return target
283 [] -> dieWithException verbosity $ FailedToDetermineTarget
284 [target] -> return target
285 _ -> dieWithException verbosity $ NoMultipleTargets
286 let componentsToBuild = neededTargetsInBuildOrder' pkg_descr lbi [nodeKey target]
287 debug verbosity $
288 "Component build order: "
289 ++ intercalate
290 ", "
291 ( map
292 (showComponentName . componentLocalName . targetCLBI)
293 componentsToBuild
296 internalPackageDB <- createInternalPackageDB verbosity lbi distPref
298 let lbiForComponent comp lbi' =
299 lbi'
300 { withPackageDB = withPackageDB lbi ++ [internalPackageDB]
301 , withPrograms =
302 addInternalBuildTools
303 pkg_descr
304 lbi'
305 (componentBuildInfo comp)
306 (withPrograms lbi')
309 -- build any dependent components
310 sequence_
311 [ do
312 let clbi = targetCLBI subtarget
313 comp = targetComponent subtarget
314 lbi' = lbiForComponent comp lbi
315 preBuildComponent verbosity lbi subtarget
316 buildComponent
317 mempty{buildVerbosity = toFlag verbosity}
318 NoFlag
319 pkg_descr
320 lbi'
321 suffixes
322 comp
323 clbi
324 distPref
325 | subtarget <- safeInit componentsToBuild
328 -- REPL for target components
329 let clbi = targetCLBI target
330 comp = targetComponent target
331 lbi' = lbiForComponent comp lbi
332 preBuildComponent verbosity lbi target
333 replComponent flags verbosity pkg_descr lbi' suffixes comp clbi distPref
335 -- | Start an interpreter without loading any package files.
336 startInterpreter
337 :: Verbosity
338 -> ProgramDb
339 -> Compiler
340 -> Platform
341 -> PackageDBStack
342 -> IO ()
343 startInterpreter verbosity programDb comp platform packageDBs =
344 case compilerFlavor comp of
345 GHC -> GHC.startInterpreter verbosity programDb comp platform packageDBs
346 GHCJS -> GHCJS.startInterpreter verbosity programDb comp platform packageDBs
347 _ -> dieWithException verbosity REPLNotSupported
349 buildComponent
350 :: BuildFlags
351 -> Flag ParStrat
352 -> PackageDescription
353 -> LocalBuildInfo
354 -> [PPSuffixHandler]
355 -> Component
356 -> ComponentLocalBuildInfo
357 -> FilePath
358 -> IO (Maybe InstalledPackageInfo)
359 buildComponent flags _ _ _ _ (CTest TestSuite{testInterface = TestSuiteUnsupported tt}) _ _ =
360 dieWithException (fromFlag $ buildVerbosity flags) $ NoSupportBuildingTestSuite tt
361 buildComponent flags _ _ _ _ (CBench Benchmark{benchmarkInterface = BenchmarkUnsupported tt}) _ _ =
362 dieWithException (fromFlag $ buildVerbosity flags) $ NoSupportBuildingBenchMark tt
363 buildComponent
364 flags
365 numJobs
366 pkg_descr
367 lbi0
368 suffixes
369 comp@( CTest
370 test@TestSuite{testInterface = TestSuiteLibV09{}}
372 clbi -- This ComponentLocalBuildInfo corresponds to a detailed
373 -- test suite and not a real component. It should not
374 -- be used, except to construct the CLBIs for the
375 -- library and stub executable that will actually be
376 -- built.
377 distPref =
379 let verbosity = fromFlag $ buildVerbosity flags
380 pwd <- getCurrentDirectory
381 let (pkg, lib, libClbi, lbi, ipi, exe, exeClbi) =
382 testSuiteLibV09AsLibAndExe pkg_descr test clbi lbi0 distPref pwd
383 preprocessComponent pkg_descr comp lbi clbi False verbosity suffixes
384 extras <- preprocessExtras verbosity comp lbi -- TODO find cpphs processed files
385 (genDir, generatedExtras) <- generateCode (testCodeGenerators test) (testName test) pkg_descr (testBuildInfo test) lbi clbi verbosity
386 setupMessage'
387 verbosity
388 "Building"
389 (packageId pkg_descr)
390 (componentLocalName clbi)
391 (maybeComponentInstantiatedWith clbi)
392 let libbi = libBuildInfo lib
393 lib' = lib{libBuildInfo = addSrcDir (addExtraOtherModules libbi generatedExtras) genDir}
394 buildLib flags numJobs pkg lbi lib' libClbi
395 -- NB: need to enable multiple instances here, because on 7.10+
396 -- the package name is the same as the library, and we still
397 -- want the registration to go through.
398 registerPackage
399 verbosity
400 (compiler lbi)
401 (withPrograms lbi)
402 (withPackageDB lbi)
404 HcPkg.defaultRegisterOptions
405 { HcPkg.registerMultiInstance = True
407 let ebi = buildInfo exe
408 -- NB: The stub executable is linked against the test-library
409 -- which already contains all `other-modules`, so we need
410 -- to remove those from the stub-exe's build-info
411 exe' = exe{buildInfo = (addExtraCSources ebi extras){otherModules = []}}
412 buildExe verbosity numJobs pkg_descr lbi exe' exeClbi
413 return Nothing -- Can't depend on test suite
414 buildComponent
415 flags
416 numJobs
417 pkg_descr
419 suffixes
420 comp
421 clbi
422 distPref =
424 let verbosity = fromFlag $ buildVerbosity flags
425 preprocessComponent pkg_descr comp lbi clbi False verbosity suffixes
426 extras <- preprocessExtras verbosity comp lbi
427 setupMessage'
428 verbosity
429 "Building"
430 (packageId pkg_descr)
431 (componentLocalName clbi)
432 (maybeComponentInstantiatedWith clbi)
433 case comp of
434 CLib lib -> do
435 let libbi = libBuildInfo lib
436 lib' =
438 { libBuildInfo =
439 flip addExtraAsmSources extras $
440 flip addExtraCmmSources extras $
441 flip addExtraCxxSources extras $
442 flip addExtraCSources extras $
443 flip addExtraJsSources extras $
444 libbi
447 buildLib flags numJobs pkg_descr lbi lib' clbi
449 let oneComponentRequested (OneComponentRequestedSpec _) = True
450 oneComponentRequested _ = False
451 -- Don't register inplace if we're only building a single component;
452 -- it's not necessary because there won't be any subsequent builds
453 -- that need to tag us
454 if (not (oneComponentRequested (componentEnabledSpec lbi)))
455 then do
456 -- Register the library in-place, so exes can depend
457 -- on internally defined libraries.
458 pwd <- getCurrentDirectory
460 -- The in place registration uses the "-inplace" suffix, not an ABI hash
461 installedPkgInfo =
462 inplaceInstalledPackageInfo
464 distPref
465 pkg_descr
466 -- NB: Use a fake ABI hash to avoid
467 -- needing to recompute it every build.
468 (mkAbiHash "inplace")
469 lib'
471 clbi
472 debug verbosity $ "Registering inplace:\n" ++ (IPI.showInstalledPackageInfo installedPkgInfo)
473 registerPackage
474 verbosity
475 (compiler lbi)
476 (withPrograms lbi)
477 (withPackageDB lbi)
478 installedPkgInfo
479 HcPkg.defaultRegisterOptions
480 { HcPkg.registerMultiInstance = True
482 return (Just installedPkgInfo)
483 else return Nothing
484 CFLib flib -> do
485 buildFLib verbosity numJobs pkg_descr lbi flib clbi
486 return Nothing
487 CExe exe -> do
488 let ebi = buildInfo exe
489 exe' = exe{buildInfo = addExtraCSources ebi extras}
490 buildExe verbosity numJobs pkg_descr lbi exe' clbi
491 return Nothing
492 CTest test@TestSuite{testInterface = TestSuiteExeV10{}} -> do
493 let exe = testSuiteExeV10AsExe test
494 (genDir, generatedExtras) <- generateCode (testCodeGenerators test) (testName test) pkg_descr (testBuildInfo test) lbi clbi verbosity
495 let ebi = buildInfo exe
496 exe' = exe{buildInfo = addSrcDir (addExtraOtherModules (addExtraCSources ebi extras) generatedExtras) genDir} -- todo extend hssrcdirs
497 buildExe verbosity numJobs pkg_descr lbi exe' clbi
498 return Nothing
499 CBench bm@Benchmark{benchmarkInterface = BenchmarkExeV10{}} -> do
500 let exe = benchmarkExeV10asExe bm
501 let ebi = buildInfo exe
502 exe' = exe{buildInfo = addExtraCSources ebi extras}
503 buildExe verbosity numJobs pkg_descr lbi exe' clbi
504 return Nothing
505 #if __GLASGOW_HASKELL__ < 811
506 -- silence pattern-match warnings prior to GHC 9.0
507 _ -> error "impossible"
508 #endif
510 generateCode
511 :: [String]
512 -> UnqualComponentName
513 -> PackageDescription
514 -> BuildInfo
515 -> LocalBuildInfo
516 -> ComponentLocalBuildInfo
517 -> Verbosity
518 -> IO (FilePath, [ModuleName.ModuleName])
519 generateCode codeGens nm pdesc bi lbi clbi verbosity = do
520 when (not . null $ codeGens) $ createDirectoryIfMissingVerbose verbosity True tgtDir
521 (\x -> (tgtDir, x)) . concat <$> mapM go codeGens
522 where
523 allLibs = (maybe id (:) $ library pdesc) (subLibraries pdesc)
524 dependencyLibs = filter (const True) allLibs -- intersect with componentPackageDeps of clbi
525 srcDirs = concatMap (hsSourceDirs . libBuildInfo) dependencyLibs
526 nm' = unUnqualComponentName nm
527 tgtDir = buildDir lbi </> nm' </> nm' ++ "-gen"
528 go :: String -> IO [ModuleName.ModuleName]
529 go codeGenProg =
530 fmap fromString . lines
531 <$> getDbProgramOutput
532 verbosity
533 (simpleProgram codeGenProg)
534 (withPrograms lbi)
535 ( (tgtDir : map getSymbolicPath srcDirs)
536 ++ ( "--"
537 : GHC.renderGhcOptions (compiler lbi) (hostPlatform lbi) (GHC.componentGhcOptions verbosity lbi bi clbi tgtDir)
541 -- | Add extra C sources generated by preprocessing to build
542 -- information.
543 addExtraCSources :: BuildInfo -> [FilePath] -> BuildInfo
544 addExtraCSources bi extras = bi{cSources = new}
545 where
546 new = ordNub (extras ++ cSources bi)
548 -- | Add extra C++ sources generated by preprocessing to build
549 -- information.
550 addExtraCxxSources :: BuildInfo -> [FilePath] -> BuildInfo
551 addExtraCxxSources bi extras = bi{cxxSources = new}
552 where
553 new = ordNub (extras ++ cxxSources bi)
555 -- | Add extra C-- sources generated by preprocessing to build
556 -- information.
557 addExtraCmmSources :: BuildInfo -> [FilePath] -> BuildInfo
558 addExtraCmmSources bi extras = bi{cmmSources = new}
559 where
560 new = ordNub (extras ++ cmmSources bi)
562 -- | Add extra ASM sources generated by preprocessing to build
563 -- information.
564 addExtraAsmSources :: BuildInfo -> [FilePath] -> BuildInfo
565 addExtraAsmSources bi extras = bi{asmSources = new}
566 where
567 new = ordNub (extras ++ asmSources bi)
569 -- | Add extra JS sources generated by preprocessing to build
570 -- information.
571 addExtraJsSources :: BuildInfo -> [FilePath] -> BuildInfo
572 addExtraJsSources bi extras = bi{jsSources = new}
573 where
574 new = ordNub (extras ++ jsSources bi)
576 -- | Add extra HS modules generated by preprocessing to build
577 -- information.
578 addExtraOtherModules :: BuildInfo -> [ModuleName.ModuleName] -> BuildInfo
579 addExtraOtherModules bi extras = bi{otherModules = new}
580 where
581 new = ordNub (extras ++ otherModules bi)
583 -- | Add extra source dir for generated modules.
584 addSrcDir :: BuildInfo -> FilePath -> BuildInfo
585 addSrcDir bi extra = bi{hsSourceDirs = new}
586 where
587 new = ordNub (unsafeMakeSymbolicPath extra : hsSourceDirs bi)
589 replComponent
590 :: ReplFlags
591 -> Verbosity
592 -> PackageDescription
593 -> LocalBuildInfo
594 -> [PPSuffixHandler]
595 -> Component
596 -> ComponentLocalBuildInfo
597 -> FilePath
598 -> IO ()
599 replComponent _ verbosity _ _ _ (CTest TestSuite{testInterface = TestSuiteUnsupported tt}) _ _ =
600 dieWithException verbosity $ NoSupportBuildingTestSuite tt
601 replComponent _ verbosity _ _ _ (CBench Benchmark{benchmarkInterface = BenchmarkUnsupported tt}) _ _ =
602 dieWithException verbosity $ NoSupportBuildingBenchMark tt
603 replComponent
604 replFlags
605 verbosity
606 pkg_descr
607 lbi0
608 suffixes
609 comp@( CTest
610 test@TestSuite{testInterface = TestSuiteLibV09{}}
612 clbi
613 distPref = do
614 pwd <- getCurrentDirectory
615 let (pkg, lib, libClbi, lbi, _, _, _) =
616 testSuiteLibV09AsLibAndExe pkg_descr test clbi lbi0 distPref pwd
617 preprocessComponent pkg_descr comp lbi clbi False verbosity suffixes
618 extras <- preprocessExtras verbosity comp lbi
619 let libbi = libBuildInfo lib
620 lib' = lib{libBuildInfo = libbi{cSources = cSources libbi ++ extras}}
621 replLib replFlags pkg lbi lib' libClbi
622 replComponent
623 replFlags
624 verbosity
625 pkg_descr
627 suffixes
628 comp
629 clbi
632 preprocessComponent pkg_descr comp lbi clbi False verbosity suffixes
633 extras <- preprocessExtras verbosity comp lbi
634 case comp of
635 CLib lib -> do
636 let libbi = libBuildInfo lib
637 lib' = lib{libBuildInfo = libbi{cSources = cSources libbi ++ extras}}
638 replLib replFlags pkg_descr lbi lib' clbi
639 CFLib flib ->
640 replFLib replFlags pkg_descr lbi flib clbi
641 CExe exe -> do
642 let ebi = buildInfo exe
643 exe' = exe{buildInfo = ebi{cSources = cSources ebi ++ extras}}
644 replExe replFlags pkg_descr lbi exe' clbi
645 CTest test@TestSuite{testInterface = TestSuiteExeV10{}} -> do
646 let exe = testSuiteExeV10AsExe test
647 let ebi = buildInfo exe
648 exe' = exe{buildInfo = ebi{cSources = cSources ebi ++ extras}}
649 replExe replFlags pkg_descr lbi exe' clbi
650 CBench bm@Benchmark{benchmarkInterface = BenchmarkExeV10{}} -> do
651 let exe = benchmarkExeV10asExe bm
652 let ebi = buildInfo exe
653 exe' = exe{buildInfo = ebi{cSources = cSources ebi ++ extras}}
654 replExe replFlags pkg_descr lbi exe' clbi
655 #if __GLASGOW_HASKELL__ < 811
656 -- silence pattern-match warnings prior to GHC 9.0
657 _ -> error "impossible"
658 #endif
660 ----------------------------------------------------
661 -- Shared code for buildComponent and replComponent
664 -- | Translate a exe-style 'TestSuite' component into an exe for building
665 testSuiteExeV10AsExe :: TestSuite -> Executable
666 testSuiteExeV10AsExe test@TestSuite{testInterface = TestSuiteExeV10 _ mainFile} =
667 Executable
668 { exeName = testName test
669 , modulePath = mainFile
670 , exeScope = ExecutablePublic
671 , buildInfo = testBuildInfo test
673 testSuiteExeV10AsExe TestSuite{} = error "testSuiteExeV10AsExe: wrong kind"
675 -- | Translate a exe-style 'Benchmark' component into an exe for building
676 benchmarkExeV10asExe :: Benchmark -> Executable
677 benchmarkExeV10asExe bm@Benchmark{benchmarkInterface = BenchmarkExeV10 _ mainFile} =
678 Executable
679 { exeName = benchmarkName bm
680 , modulePath = mainFile
681 , exeScope = ExecutablePublic
682 , buildInfo = benchmarkBuildInfo bm
684 benchmarkExeV10asExe Benchmark{} = error "benchmarkExeV10asExe: wrong kind"
686 -- | Translate a lib-style 'TestSuite' component into a lib + exe for building
687 testSuiteLibV09AsLibAndExe
688 :: PackageDescription
689 -> TestSuite
690 -> ComponentLocalBuildInfo
691 -> LocalBuildInfo
692 -> FilePath
693 -> FilePath
694 -> ( PackageDescription
695 , Library
696 , ComponentLocalBuildInfo
697 , LocalBuildInfo
698 , IPI.InstalledPackageInfo
699 , Executable
700 , ComponentLocalBuildInfo
702 testSuiteLibV09AsLibAndExe
703 pkg_descr
704 test@TestSuite{testInterface = TestSuiteLibV09 _ m}
705 clbi
707 distPref
708 pwd =
709 (pkg, lib, libClbi, lbi, ipi, exe, exeClbi)
710 where
711 bi = testBuildInfo test
712 lib =
713 Library
714 { libName = LMainLibName
715 , exposedModules = [m]
716 , reexportedModules = []
717 , signatures = []
718 , libExposed = True
719 , libVisibility = LibraryVisibilityPrivate
720 , libBuildInfo = bi
722 -- This is, like, the one place where we use a CTestName for a library.
723 -- Should NOT use library name, since that could conflict!
724 PackageIdentifier pkg_name pkg_ver = package pkg_descr
725 -- Note: we do make internal library from the test!
726 compat_name = MungedPackageName pkg_name (LSubLibName (testName test))
727 compat_key = computeCompatPackageKey (compiler lbi) compat_name pkg_ver (componentUnitId clbi)
728 libClbi =
729 LibComponentLocalBuildInfo
730 { componentPackageDeps = componentPackageDeps clbi
731 , componentInternalDeps = componentInternalDeps clbi
732 , componentIsIndefinite_ = False
733 , componentExeDeps = componentExeDeps clbi
734 , componentLocalName = CLibName $ LSubLibName $ testName test
735 , componentIsPublic = False
736 , componentIncludes = componentIncludes clbi
737 , componentUnitId = componentUnitId clbi
738 , componentComponentId = componentComponentId clbi
739 , componentInstantiatedWith = []
740 , componentCompatPackageName = compat_name
741 , componentCompatPackageKey = compat_key
742 , componentExposedModules = [IPI.ExposedModule m Nothing]
744 pkgName' = mkPackageName $ prettyShow compat_name
745 pkg =
746 pkg_descr
747 { package = (package pkg_descr){pkgName = pkgName'}
748 , executables = []
749 , testSuites = []
750 , subLibraries = [lib]
752 ipi = inplaceInstalledPackageInfo pwd distPref pkg (mkAbiHash "") lib lbi libClbi
753 testDir =
754 buildDir lbi
755 </> stubName test
756 </> stubName test
757 ++ "-tmp"
758 testLibDep =
759 Dependency
760 pkgName'
761 (thisVersion $ pkgVersion $ package pkg_descr)
762 mainLibSet
763 exe =
764 Executable
765 { exeName = mkUnqualComponentName $ stubName test
766 , modulePath = stubFilePath test
767 , exeScope = ExecutablePublic
768 , buildInfo =
769 (testBuildInfo test)
770 { hsSourceDirs = [unsafeMakeSymbolicPath testDir]
771 , targetBuildDepends =
772 testLibDep
773 : targetBuildDepends (testBuildInfo test)
776 -- \| The stub executable needs a new 'ComponentLocalBuildInfo'
777 -- that exposes the relevant test suite library.
778 deps =
779 (IPI.installedUnitId ipi, mungedId ipi)
780 : ( filter
781 ( \(_, x) ->
782 let name = prettyShow $ mungedName x
783 in name == "Cabal" || name == "base"
785 (componentPackageDeps clbi)
787 exeClbi =
788 ExeComponentLocalBuildInfo
789 { -- TODO: this is a hack, but as long as this is unique
790 -- (doesn't clobber something) we won't run into trouble
791 componentUnitId = mkUnitId (stubName test)
792 , componentComponentId = mkComponentId (stubName test)
793 , componentInternalDeps = [componentUnitId clbi]
794 , componentExeDeps = []
795 , componentLocalName = CExeName $ mkUnqualComponentName $ stubName test
796 , componentPackageDeps = deps
797 , -- Assert DefUnitId invariant!
798 -- Executable can't be indefinite, so dependencies must
799 -- be definite packages.
800 componentIncludes =
801 map ((,defaultRenaming) . DefiniteUnitId . unsafeMkDefUnitId . fst) deps
803 testSuiteLibV09AsLibAndExe _ TestSuite{} _ _ _ _ = error "testSuiteLibV09AsLibAndExe: wrong kind"
805 -- | Initialize a new package db file for libraries defined
806 -- internally to the package.
807 createInternalPackageDB
808 :: Verbosity
809 -> LocalBuildInfo
810 -> FilePath
811 -> IO PackageDB
812 createInternalPackageDB verbosity lbi distPref = do
813 existsAlready <- doesPackageDBExist dbPath
814 when existsAlready $ deletePackageDB dbPath
815 createPackageDB verbosity (compiler lbi) (withPrograms lbi) False dbPath
816 return (SpecificPackageDB dbPath)
817 where
818 dbPath = internalPackageDBPath lbi distPref
820 addInternalBuildTools
821 :: PackageDescription
822 -> LocalBuildInfo
823 -> BuildInfo
824 -> ProgramDb
825 -> ProgramDb
826 addInternalBuildTools pkg lbi bi progs =
827 foldr updateProgram progs internalBuildTools
828 where
829 internalBuildTools =
830 [ simpleConfiguredProgram toolName' (FoundOnSystem toolLocation)
831 | toolName <- getAllInternalToolDependencies pkg bi
832 , let toolName' = unUnqualComponentName toolName
833 , let toolLocation = buildDir lbi </> toolName' </> toolName' <.> exeExtension (hostPlatform lbi)
836 -- TODO: build separate libs in separate dirs so that we can build
837 -- multiple libs, e.g. for 'LibTest' library-style test suites
838 buildLib
839 :: BuildFlags
840 -> Flag ParStrat
841 -> PackageDescription
842 -> LocalBuildInfo
843 -> Library
844 -> ComponentLocalBuildInfo
845 -> IO ()
846 buildLib flags numJobs pkg_descr lbi lib clbi =
847 let verbosity = fromFlag $ buildVerbosity flags
848 in case compilerFlavor (compiler lbi) of
849 GHC -> GHC.buildLib flags numJobs pkg_descr lbi lib clbi
850 GHCJS -> GHCJS.buildLib verbosity numJobs pkg_descr lbi lib clbi
851 UHC -> UHC.buildLib verbosity pkg_descr lbi lib clbi
852 HaskellSuite{} -> HaskellSuite.buildLib verbosity pkg_descr lbi lib clbi
853 _ -> dieWithException verbosity BuildingNotSupportedWithCompiler
855 -- | Build a foreign library
857 -- NOTE: We assume that we already checked that we can actually build the
858 -- foreign library in configure.
859 buildFLib
860 :: Verbosity
861 -> Flag ParStrat
862 -> PackageDescription
863 -> LocalBuildInfo
864 -> ForeignLib
865 -> ComponentLocalBuildInfo
866 -> IO ()
867 buildFLib verbosity numJobs pkg_descr lbi flib clbi =
868 case compilerFlavor (compiler lbi) of
869 GHC -> GHC.buildFLib verbosity numJobs pkg_descr lbi flib clbi
870 _ -> dieWithException verbosity BuildingNotSupportedWithCompiler
872 buildExe
873 :: Verbosity
874 -> Flag ParStrat
875 -> PackageDescription
876 -> LocalBuildInfo
877 -> Executable
878 -> ComponentLocalBuildInfo
879 -> IO ()
880 buildExe verbosity numJobs pkg_descr lbi exe clbi =
881 case compilerFlavor (compiler lbi) of
882 GHC -> GHC.buildExe verbosity numJobs pkg_descr lbi exe clbi
883 GHCJS -> GHCJS.buildExe verbosity numJobs pkg_descr lbi exe clbi
884 UHC -> UHC.buildExe verbosity pkg_descr lbi exe clbi
885 _ -> dieWithException verbosity BuildingNotSupportedWithCompiler
887 replLib
888 :: ReplFlags
889 -> PackageDescription
890 -> LocalBuildInfo
891 -> Library
892 -> ComponentLocalBuildInfo
893 -> IO ()
894 replLib replFlags pkg_descr lbi lib clbi =
895 let verbosity = fromFlag $ replVerbosity replFlags
896 opts = replReplOptions replFlags
897 in case compilerFlavor (compiler lbi) of
898 -- 'cabal repl' doesn't need to support 'ghc --make -j', so we just pass
899 -- NoFlag as the numJobs parameter.
900 GHC -> GHC.replLib replFlags NoFlag pkg_descr lbi lib clbi
901 GHCJS -> GHCJS.replLib (replOptionsFlags opts) verbosity NoFlag pkg_descr lbi lib clbi
902 _ -> dieWithException verbosity REPLNotSupported
904 replExe
905 :: ReplFlags
906 -> PackageDescription
907 -> LocalBuildInfo
908 -> Executable
909 -> ComponentLocalBuildInfo
910 -> IO ()
911 replExe flags pkg_descr lbi exe clbi =
912 let verbosity = fromFlag $ replVerbosity flags
913 in case compilerFlavor (compiler lbi) of
914 GHC -> GHC.replExe flags NoFlag pkg_descr lbi exe clbi
915 GHCJS -> GHCJS.replExe (replOptionsFlags $ replReplOptions flags) verbosity NoFlag pkg_descr lbi exe clbi
916 _ -> dieWithException verbosity REPLNotSupported
918 replFLib
919 :: ReplFlags
920 -> PackageDescription
921 -> LocalBuildInfo
922 -> ForeignLib
923 -> ComponentLocalBuildInfo
924 -> IO ()
925 replFLib flags pkg_descr lbi exe clbi =
926 let verbosity = fromFlag $ replVerbosity flags
927 in case compilerFlavor (compiler lbi) of
928 GHC -> GHC.replFLib flags NoFlag pkg_descr lbi exe clbi
929 _ -> dieWithException verbosity REPLNotSupported
931 -- | Pre-build steps for a component: creates the autogenerated files
932 -- for a particular configured component.
933 preBuildComponent
934 :: Verbosity
935 -> LocalBuildInfo
936 -- ^ Configuration information
937 -> TargetInfo
938 -> IO ()
939 preBuildComponent verbosity lbi tgt = do
940 let pkg_descr = localPkgDescr lbi
941 clbi = targetCLBI tgt
942 createDirectoryIfMissingVerbose verbosity True (componentBuildDir lbi clbi)
943 writeBuiltinAutogenFiles verbosity pkg_descr lbi clbi
945 -- | Generate and write to disk all built-in autogenerated files
946 -- for the specified component. These files will be put in the
947 -- autogenerated module directory for this component
948 -- (see 'autogenComponentsModuleDir').
950 -- This includes:
952 -- - @Paths_<pkg>.hs@,
953 -- - @PackageInfo_<pkg>.hs@,
954 -- - Backpack signature files for components that are not fully instantiated,
955 -- - @cabal_macros.h@.
956 writeBuiltinAutogenFiles
957 :: Verbosity
958 -> PackageDescription
959 -> LocalBuildInfo
960 -> ComponentLocalBuildInfo
961 -> IO ()
962 writeBuiltinAutogenFiles verbosity pkg lbi clbi =
963 writeAutogenFiles verbosity lbi clbi $ builtinAutogenFiles pkg lbi clbi
965 -- | Built-in autogenerated files and their contents. This includes:
967 -- - @Paths_<pkg>.hs@,
968 -- - @PackageInfo_<pkg>.hs@,
969 -- - Backpack signature files for components that are not fully instantiated,
970 -- - @cabal_macros.h@.
971 builtinAutogenFiles
972 :: PackageDescription
973 -> LocalBuildInfo
974 -> ComponentLocalBuildInfo
975 -> Map AutogenFile AutogenFileContents
976 builtinAutogenFiles pkg lbi clbi =
977 Map.insert pathsFile pathsContents $
978 Map.insert packageInfoFile packageInfoContents $
979 Map.insert cppHeaderFile cppHeaderContents $
980 emptySignatureModules clbi
981 where
982 pathsFile = AutogenModule (autogenPathsModuleName pkg) (Suffix "hs")
983 pathsContents = toUTF8LBS $ generatePathsModule pkg lbi clbi
984 packageInfoFile = AutogenModule (autogenPackageInfoModuleName pkg) (Suffix "hs")
985 packageInfoContents = toUTF8LBS $ generatePackageInfoModule pkg lbi
986 cppHeaderFile = AutogenFile $ toShortText cppHeaderName
987 cppHeaderContents = toUTF8LBS $ generateCabalMacrosHeader pkg lbi clbi
989 -- | An empty @".hsig"@ Backpack signature module for each requirement, so that
990 -- GHC has a source file to look at it when it needs to typecheck
991 -- a signature. It's harmless to generate these modules, even when
992 -- there is a real @hsig@ file written by the user, since
993 -- include path ordering ensures that the real @hsig@ file
994 -- will always be picked up before the autogenerated one.
995 emptySignatureModules
996 :: ComponentLocalBuildInfo
997 -> Map AutogenFile AutogenFileContents
998 emptySignatureModules clbi =
999 case clbi of
1000 LibComponentLocalBuildInfo{componentInstantiatedWith = insts} ->
1001 Map.fromList
1002 [ ( AutogenModule modName (Suffix "hsig")
1003 , emptyHsigFile modName
1005 | (modName, _) <- insts
1007 _ -> Map.empty
1008 where
1009 emptyHsigFile :: ModuleName -> AutogenFileContents
1010 emptyHsigFile modName =
1011 toUTF8LBS $
1012 "{-# OPTIONS_GHC -w #-}\n"
1013 ++ "{-# LANGUAGE NoImplicitPrelude #-}\n"
1014 ++ "signature "
1015 ++ prettyShow modName
1016 ++ " where"
1018 data AutogenFile
1019 = AutogenModule !ModuleName !Suffix
1020 | AutogenFile !ShortText
1021 deriving (Show, Eq, Ord)
1023 -- | A representation of the contents of an autogenerated file.
1024 type AutogenFileContents = LBS.ByteString
1026 -- | Write the given autogenerated files in the autogenerated modules
1027 -- directory for the component.
1028 writeAutogenFiles
1029 :: Verbosity
1030 -> LocalBuildInfo
1031 -> ComponentLocalBuildInfo
1032 -> Map AutogenFile AutogenFileContents
1033 -> IO ()
1034 writeAutogenFiles verbosity lbi clbi autogenFiles = do
1035 -- Ensure that the overall autogenerated files directory exists.
1036 createDirectoryIfMissingVerbose verbosity True autogenDir
1037 for_ (Map.assocs autogenFiles) $ \(file, contents) -> do
1038 let path = case file of
1039 AutogenModule modName (Suffix ext) ->
1040 autogenDir </> ModuleName.toFilePath modName <.> ext
1041 AutogenFile fileName ->
1042 autogenDir </> fromShortText fileName
1043 dir = takeDirectory path
1044 -- Ensure that the directory subtree for this autogenerated file exists.
1045 createDirectoryIfMissingVerbose verbosity True dir
1046 -- Write the contents of the file.
1047 rewriteFileLBS verbosity path contents
1048 where
1049 autogenDir = autogenComponentModulesDir lbi clbi