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