Merge pull request #10593 from cabalism/typo/prexif-reseved
[cabal.git] / Cabal / src / Distribution / Simple / Build.hs
blobe153c25b9d78b618c24aaa109c7a17a06f964236
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE DataKinds #-}
3 {-# LANGUAGE DuplicateRecordFields #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE NamedFieldPuns #-}
6 {-# LANGUAGE RankNTypes #-}
7 {-# LANGUAGE TupleSections #-}
9 -----------------------------------------------------------------------------
11 -- |
12 -- Module : Distribution.Simple.Build
13 -- Copyright : Isaac Jones 2003-2005,
14 -- Ross Paterson 2006,
15 -- Duncan Coutts 2007-2008, 2012
16 -- License : BSD3
18 -- Maintainer : cabal-devel@haskell.org
19 -- Portability : portable
21 -- This is the entry point to actually building the modules in a package. It
22 -- doesn't actually do much itself, most of the work is delegated to
23 -- compiler-specific actions. It does do some non-compiler specific bits like
24 -- running pre-processors.
25 module Distribution.Simple.Build
26 ( -- * Build
27 build
28 , build_setupHooks
30 -- * Repl
31 , repl
32 , repl_setupHooks
33 , startInterpreter
35 -- * Build preparation
36 , preBuildComponent
37 , AutogenFile (..)
38 , AutogenFileContents
39 , writeBuiltinAutogenFiles
40 , writeAutogenFiles
42 -- ** Legacy functions
43 , componentInitialBuildSteps
44 , initialBuildSteps
46 -- * Internal package database creation
47 , createInternalPackageDB
49 -- * Handling of internal build tools
50 , addInternalBuildTools
51 ) where
53 import Distribution.Compat.Prelude
54 import Distribution.Utils.Generic
55 import Prelude ()
57 import Distribution.Types.ComponentLocalBuildInfo
58 import Distribution.Types.ComponentRequestedSpec
59 import Distribution.Types.Dependency
60 import Distribution.Types.ExecutableScope
61 import Distribution.Types.ForeignLib
62 import Distribution.Types.LibraryVisibility
63 import Distribution.Types.LocalBuildInfo
64 import Distribution.Types.ModuleRenaming
65 import Distribution.Types.MungedPackageId
66 import Distribution.Types.MungedPackageName
67 import Distribution.Types.ParStrat
68 import Distribution.Types.TargetInfo
69 import Distribution.Utils.Path
71 import Distribution.Backpack
72 import Distribution.Backpack.DescribeUnitId
73 import Distribution.Package
74 import qualified Distribution.Simple.GHC as GHC
75 import qualified Distribution.Simple.GHCJS as GHCJS
76 import qualified Distribution.Simple.HaskellSuite as HaskellSuite
77 import qualified Distribution.Simple.PackageIndex as Index
78 import qualified Distribution.Simple.UHC as UHC
80 import Distribution.Simple.Build.Macros (generateCabalMacrosHeader)
81 import Distribution.Simple.Build.PackageInfoModule (generatePackageInfoModule)
82 import Distribution.Simple.Build.PathsModule (generatePathsModule, pkgPathEnvVar)
83 import qualified Distribution.Simple.Program.HcPkg as HcPkg
85 import Distribution.InstalledPackageInfo (InstalledPackageInfo)
86 import qualified Distribution.InstalledPackageInfo as IPI
87 import Distribution.ModuleName (ModuleName)
88 import qualified Distribution.ModuleName as ModuleName
89 import Distribution.PackageDescription
90 import Distribution.Simple.Compiler
92 import Distribution.Simple.BuildPaths
93 import Distribution.Simple.BuildTarget
94 import Distribution.Simple.BuildToolDepends
95 import Distribution.Simple.Configure
96 import Distribution.Simple.Flag
97 import Distribution.Simple.LocalBuildInfo
98 import Distribution.Simple.PreProcess
99 import Distribution.Simple.Program
100 import Distribution.Simple.Program.Builtin (haskellSuiteProgram)
101 import Distribution.Simple.Program.Db
102 import qualified Distribution.Simple.Program.GHC as GHC
103 import Distribution.Simple.Program.Types
104 import Distribution.Simple.Register
105 import Distribution.Simple.Setup.Build
106 import Distribution.Simple.Setup.Common
107 import Distribution.Simple.Setup.Config
108 import Distribution.Simple.Setup.Repl
109 import Distribution.Simple.SetupHooks.Internal
110 ( BuildHooks (..)
111 , BuildingWhat (..)
112 , noBuildHooks
114 import qualified Distribution.Simple.SetupHooks.Internal as SetupHooks
115 import qualified Distribution.Simple.SetupHooks.Rule as SetupHooks
116 import Distribution.Simple.ShowBuildInfo
117 import Distribution.Simple.Test.LibV09
118 import Distribution.Simple.Utils
119 import Distribution.Utils.Json
120 import Distribution.Utils.ShortText (ShortText, fromShortText, toShortText)
122 import Distribution.Pretty
123 import Distribution.System
124 import Distribution.Verbosity
125 import Distribution.Version (thisVersion)
127 import Distribution.Compat.Graph (IsNode (..))
129 import Control.Monad
130 import qualified Data.ByteString.Lazy as LBS
131 import qualified Data.Map as Map
132 import Distribution.Simple.Errors
133 import System.Directory (doesFileExist, removeFile)
134 import System.FilePath (takeDirectory)
136 -- -----------------------------------------------------------------------------
138 -- | Build the libraries and executables in this package.
139 build
140 :: PackageDescription
141 -- ^ Mostly information from the .cabal file
142 -> LocalBuildInfo
143 -- ^ Configuration information
144 -> BuildFlags
145 -- ^ Flags that the user passed to build
146 -> [PPSuffixHandler]
147 -- ^ preprocessors to run before compiling
148 -> IO ()
149 build = build_setupHooks noBuildHooks
151 build_setupHooks
152 :: BuildHooks
153 -> PackageDescription
154 -- ^ Mostly information from the .cabal file
155 -> LocalBuildInfo
156 -- ^ Configuration information
157 -> BuildFlags
158 -- ^ Flags that the user passed to build
159 -> [PPSuffixHandler]
160 -- ^ preprocessors to run before compiling
161 -> IO ()
162 build_setupHooks
163 (BuildHooks{preBuildComponentRules = mbPbcRules, postBuildComponentHook = mbPostBuild})
164 pkg_descr
166 flags
167 suffixHandlers = do
168 checkSemaphoreSupport verbosity (compiler lbi) flags
169 targets <- readTargetInfos verbosity pkg_descr lbi (buildTargets flags)
170 let componentsToBuild = neededTargetsInBuildOrder' pkg_descr lbi (map nodeKey targets)
171 info verbosity $
172 "Component build order: "
173 ++ intercalate
174 ", "
175 ( map
176 (showComponentName . componentLocalName . targetCLBI)
177 componentsToBuild
180 when (null targets) $
181 -- Only bother with this message if we're building the whole package
182 setupMessage verbosity "Building" (packageId pkg_descr)
184 internalPackageDB <- createInternalPackageDB verbosity lbi distPref
186 -- Before the actual building, dump out build-information.
187 -- This way, if the actual compilation failed, the options have still been
188 -- dumped.
189 dumpBuildInfo verbosity distPref (configDumpBuildInfo (configFlags lbi)) pkg_descr lbi flags
191 -- Now do the actual building
192 (\f -> foldM_ f (installedPkgs lbi) componentsToBuild) $ \index target -> do
193 let comp = targetComponent target
194 clbi = targetCLBI target
195 bi = componentBuildInfo comp
196 -- Include any build-tool-depends on build tools internal to the current package.
197 progs' = addInternalBuildTools pkg_descr lbi bi (withPrograms lbi)
198 lbi' =
200 { withPrograms = progs'
201 , withPackageDB = withPackageDB lbi ++ [internalPackageDB]
202 , installedPkgs = index
204 runPreBuildHooks :: LocalBuildInfo -> TargetInfo -> IO ()
205 runPreBuildHooks lbi2 tgt =
206 let inputs =
207 SetupHooks.PreBuildComponentInputs
208 { SetupHooks.buildingWhat = BuildNormal flags
209 , SetupHooks.localBuildInfo = lbi2
210 , SetupHooks.targetInfo = tgt
212 in for_ mbPbcRules $ \pbcRules -> do
213 (ruleFromId, _mons) <- SetupHooks.computeRules verbosity inputs pbcRules
214 SetupHooks.executeRules verbosity lbi2 tgt ruleFromId
215 preBuildComponent runPreBuildHooks verbosity lbi' target
216 let numJobs = buildNumJobs flags
217 par_strat <-
218 toFlag <$> case buildUseSemaphore flags of
219 Flag sem_name -> case numJobs of
220 Flag{} -> do
221 warn verbosity $ "Ignoring -j due to --semaphore"
222 return $ UseSem sem_name
223 NoFlag -> return $ UseSem sem_name
224 NoFlag -> return $ case numJobs of
225 Flag n -> NumJobs n
226 NoFlag -> Serial
227 mb_ipi <-
228 buildComponent
229 flags
230 par_strat
231 pkg_descr
232 lbi'
233 suffixHandlers
234 comp
235 clbi
236 distPref
237 let postBuildInputs =
238 SetupHooks.PostBuildComponentInputs
239 { SetupHooks.buildFlags = flags
240 , SetupHooks.localBuildInfo = lbi'
241 , SetupHooks.targetInfo = target
243 for_ mbPostBuild ($ postBuildInputs)
244 return (maybe index (Index.insert `flip` index) mb_ipi)
246 return ()
247 where
248 distPref = fromFlag (buildDistPref flags)
249 verbosity = fromFlag (buildVerbosity flags)
251 -- | Check for conditions that would prevent the build from succeeding.
252 checkSemaphoreSupport
253 :: Verbosity -> Compiler -> BuildFlags -> IO ()
254 checkSemaphoreSupport verbosity comp flags = do
255 unless (jsemSupported comp || (isNothing (flagToMaybe (buildUseSemaphore flags)))) $
256 dieWithException verbosity CheckSemaphoreSupport
258 -- | Write available build information for 'LocalBuildInfo' to disk.
260 -- Dumps detailed build information 'build-info.json' to the given directory.
261 -- Build information contains basics such as compiler details, but also
262 -- lists what modules a component contains and how to compile the component, assuming
263 -- lib:Cabal made sure that dependencies are up-to-date.
264 dumpBuildInfo
265 :: Verbosity
266 -> SymbolicPath Pkg (Dir Dist)
267 -- ^ To which directory should the build-info be dumped?
268 -> Flag DumpBuildInfo
269 -- ^ Should we dump detailed build information for this component?
270 -> PackageDescription
271 -- ^ Mostly information from the .cabal file
272 -> LocalBuildInfo
273 -- ^ Configuration information
274 -> BuildFlags
275 -- ^ Flags that the user passed to build
276 -> IO ()
277 dumpBuildInfo verbosity distPref dumpBuildInfoFlag pkg_descr lbi flags = do
278 when shouldDumpBuildInfo $ do
279 -- Changing this line might break consumers of the dumped build info.
280 -- Announce changes on mailing lists!
281 let activeTargets = allTargetsInBuildOrder' pkg_descr lbi
282 info verbosity $
283 "Dump build information for: "
284 ++ intercalate
285 ", "
286 ( map
287 (showComponentName . componentLocalName . targetCLBI)
288 activeTargets
291 (compilerProg, _) <- case flavorToProgram (compilerFlavor (compiler lbi)) of
292 Nothing ->
293 dieWithException verbosity $ UnknownCompilerFlavor (compilerFlavor (compiler lbi))
294 Just program -> requireProgram verbosity program (withPrograms lbi)
296 wdir <- absoluteWorkingDirLBI lbi
297 let (warns, json) = mkBuildInfo wdir pkg_descr lbi flags (compilerProg, compiler lbi) activeTargets
298 buildInfoText = renderJson json
299 unless (null warns) $
300 warn verbosity $
301 "Encountered warnings while dumping build-info:\n"
302 ++ unlines warns
303 LBS.writeFile buildInfoFile buildInfoText
305 when (not shouldDumpBuildInfo) $ do
306 -- Remove existing build-info.json as it might be outdated now.
307 exists <- doesFileExist buildInfoFile
308 when exists $ removeFile buildInfoFile
309 where
310 buildInfoFile = interpretSymbolicPathLBI lbi $ buildInfoPref distPref
311 shouldDumpBuildInfo = fromFlagOrDefault NoDumpBuildInfo dumpBuildInfoFlag == DumpBuildInfo
313 -- \| Given the flavor of the compiler, try to find out
314 -- which program we need.
315 flavorToProgram :: CompilerFlavor -> Maybe Program
316 flavorToProgram GHC = Just ghcProgram
317 flavorToProgram GHCJS = Just ghcjsProgram
318 flavorToProgram UHC = Just uhcProgram
319 flavorToProgram JHC = Just jhcProgram
320 flavorToProgram HaskellSuite{} = Just haskellSuiteProgram
321 flavorToProgram _ = Nothing
323 repl
324 :: PackageDescription
325 -- ^ Mostly information from the .cabal file
326 -> LocalBuildInfo
327 -- ^ Configuration information
328 -> ReplFlags
329 -- ^ Flags that the user passed to build
330 -> [PPSuffixHandler]
331 -- ^ preprocessors to run before compiling
332 -> [String]
333 -> IO ()
334 repl = repl_setupHooks noBuildHooks
336 repl_setupHooks
337 :: BuildHooks
338 -- ^ build hook
339 -> PackageDescription
340 -- ^ Mostly information from the .cabal file
341 -> LocalBuildInfo
342 -- ^ Configuration information
343 -> ReplFlags
344 -- ^ Flags that the user passed to build
345 -> [PPSuffixHandler]
346 -- ^ preprocessors to run before compiling
347 -> [String]
348 -> IO ()
349 repl_setupHooks
350 (BuildHooks{preBuildComponentRules = mbPbcRules})
351 pkg_descr
353 flags
354 suffixHandlers
355 args = do
356 let distPref = fromFlag (replDistPref flags)
357 verbosity = fromFlag (replVerbosity flags)
359 target <-
360 readTargetInfos verbosity pkg_descr lbi args >>= \r -> case r of
361 -- This seems DEEPLY questionable.
362 [] -> case allTargetsInBuildOrder' pkg_descr lbi of
363 (target : _) -> return target
364 [] -> dieWithException verbosity $ FailedToDetermineTarget
365 [target] -> return target
366 _ -> dieWithException verbosity $ NoMultipleTargets
367 let componentsToBuild = neededTargetsInBuildOrder' pkg_descr lbi [nodeKey target]
368 debug verbosity $
369 "Component build order: "
370 ++ intercalate
371 ", "
372 ( map
373 (showComponentName . componentLocalName . targetCLBI)
374 componentsToBuild
377 internalPackageDB <- createInternalPackageDB verbosity lbi distPref
379 let lbiForComponent comp lbi' =
380 lbi'
381 { withPackageDB = withPackageDB lbi ++ [internalPackageDB]
382 , withPrograms =
383 -- Include any build-tool-depends on build tools internal to the current package.
384 addInternalBuildTools
385 pkg_descr
386 lbi'
387 (componentBuildInfo comp)
388 (withPrograms lbi')
390 runPreBuildHooks :: LocalBuildInfo -> TargetInfo -> IO ()
391 runPreBuildHooks lbi2 tgt =
392 let inputs =
393 SetupHooks.PreBuildComponentInputs
394 { SetupHooks.buildingWhat = BuildRepl flags
395 , SetupHooks.localBuildInfo = lbi2
396 , SetupHooks.targetInfo = tgt
398 in for_ mbPbcRules $ \pbcRules -> do
399 (ruleFromId, _mons) <- SetupHooks.computeRules verbosity inputs pbcRules
400 SetupHooks.executeRules verbosity lbi2 tgt ruleFromId
402 -- build any dependent components
403 sequence_
404 [ do
405 let clbi = targetCLBI subtarget
406 comp = targetComponent subtarget
407 lbi' = lbiForComponent comp lbi
408 preBuildComponent runPreBuildHooks verbosity lbi' subtarget
409 buildComponent
410 (mempty{buildCommonFlags = mempty{setupVerbosity = toFlag verbosity}})
411 NoFlag
412 pkg_descr
413 lbi'
414 suffixHandlers
415 comp
416 clbi
417 distPref
418 | subtarget <- safeInit componentsToBuild
421 -- REPL for target components
422 let clbi = targetCLBI target
423 comp = targetComponent target
424 lbi' = lbiForComponent comp lbi
425 preBuildComponent runPreBuildHooks verbosity lbi' target
426 replComponent flags verbosity pkg_descr lbi' suffixHandlers comp clbi distPref
428 -- | Start an interpreter without loading any package files.
429 startInterpreter
430 :: Verbosity
431 -> ProgramDb
432 -> Compiler
433 -> Platform
434 -> PackageDBStack
435 -> IO ()
436 startInterpreter verbosity programDb comp platform packageDBs =
437 case compilerFlavor comp of
438 GHC -> GHC.startInterpreter verbosity programDb comp platform packageDBs
439 GHCJS -> GHCJS.startInterpreter verbosity programDb comp platform packageDBs
440 _ -> dieWithException verbosity REPLNotSupported
442 buildComponent
443 :: BuildFlags
444 -> Flag ParStrat
445 -> PackageDescription
446 -> LocalBuildInfo
447 -> [PPSuffixHandler]
448 -> Component
449 -> ComponentLocalBuildInfo
450 -> SymbolicPath Pkg (Dir Dist)
451 -> IO (Maybe InstalledPackageInfo)
452 buildComponent flags _ _ _ _ (CTest TestSuite{testInterface = TestSuiteUnsupported tt}) _ _ =
453 dieWithException (fromFlag $ buildVerbosity flags) $
454 NoSupportBuildingTestSuite tt
455 buildComponent flags _ _ _ _ (CBench Benchmark{benchmarkInterface = BenchmarkUnsupported tt}) _ _ =
456 dieWithException (fromFlag $ buildVerbosity flags) $
457 NoSupportBuildingBenchMark tt
458 buildComponent
459 flags
460 numJobs
461 pkg_descr
462 lbi0
463 suffixHandlers
464 comp@( CTest
465 test@TestSuite{testInterface = TestSuiteLibV09{}}
467 clbi -- This ComponentLocalBuildInfo corresponds to a detailed
468 -- test suite and not a real component. It should not
469 -- be used, except to construct the CLBIs for the
470 -- library and stub executable that will actually be
471 -- built.
472 distPref =
474 inplaceDir <- absoluteWorkingDirLBI lbi0
475 let verbosity = fromFlag $ buildVerbosity flags
476 let (pkg, lib, libClbi, lbi, ipi, exe, exeClbi) =
477 testSuiteLibV09AsLibAndExe pkg_descr test clbi lbi0 inplaceDir distPref
478 preprocessComponent pkg_descr comp lbi clbi False verbosity suffixHandlers
479 extras <- preprocessExtras verbosity comp lbi -- TODO find cpphs processed files
480 (genDir, generatedExtras) <- generateCode (testCodeGenerators test) (testName test) pkg_descr (testBuildInfo test) lbi clbi verbosity
481 setupMessage'
482 verbosity
483 "Building"
484 (packageId pkg_descr)
485 (componentLocalName clbi)
486 (maybeComponentInstantiatedWith clbi)
487 let libbi = libBuildInfo lib
488 lib' = lib{libBuildInfo = addSrcDir (addExtraOtherModules libbi generatedExtras) genDir}
489 buildLib flags numJobs pkg lbi lib' libClbi
490 -- NB: need to enable multiple instances here, because on 7.10+
491 -- the package name is the same as the library, and we still
492 -- want the registration to go through.
493 registerPackage
494 verbosity
495 (compiler lbi)
496 (withPrograms lbi)
497 (mbWorkDirLBI lbi)
498 (withPackageDB lbi)
500 HcPkg.defaultRegisterOptions
501 { HcPkg.registerMultiInstance = True
503 let ebi = buildInfo exe
504 -- NB: The stub executable is linked against the test-library
505 -- which already contains all `other-modules`, so we need
506 -- to remove those from the stub-exe's build-info
507 exe' = exe{buildInfo = (addExtraCSources ebi extras){otherModules = []}}
508 buildExe verbosity numJobs pkg_descr lbi exe' exeClbi
509 return Nothing -- Can't depend on test suite
510 buildComponent
511 flags
512 numJobs
513 pkg_descr
515 suffixHandlers
516 comp
517 clbi
518 distPref =
520 let verbosity = fromFlag $ buildVerbosity flags
521 preprocessComponent pkg_descr comp lbi clbi False verbosity suffixHandlers
522 extras <- preprocessExtras verbosity comp lbi
523 setupMessage'
524 verbosity
525 "Building"
526 (packageId pkg_descr)
527 (componentLocalName clbi)
528 (maybeComponentInstantiatedWith clbi)
529 case comp of
530 CLib lib -> do
531 let libbi = libBuildInfo lib
532 lib' =
534 { libBuildInfo =
535 flip addExtraAsmSources extras $
536 flip addExtraCmmSources extras $
537 flip addExtraCxxSources extras $
538 flip addExtraCSources extras $
539 flip addExtraJsSources extras $
540 libbi
543 buildLib flags numJobs pkg_descr lbi lib' clbi
545 let oneComponentRequested (OneComponentRequestedSpec _) = True
546 oneComponentRequested _ = False
547 -- Don't register inplace if we're only building a single component;
548 -- it's not necessary because there won't be any subsequent builds
549 -- that need to tag us
550 if (not (oneComponentRequested (componentEnabledSpec lbi)))
551 then do
552 -- Register the library in-place, so exes can depend
553 -- on internally defined libraries.
554 inplaceDir <- absoluteWorkingDirLBI lbi
556 -- The in place registration uses the "-inplace" suffix, not an ABI hash
557 installedPkgInfo =
558 inplaceInstalledPackageInfo
559 inplaceDir
560 distPref
561 pkg_descr
562 -- NB: Use a fake ABI hash to avoid
563 -- needing to recompute it every build.
564 (mkAbiHash "inplace")
565 lib'
567 clbi
568 debug verbosity $ "Registering inplace:\n" ++ (IPI.showInstalledPackageInfo installedPkgInfo)
569 registerPackage
570 verbosity
571 (compiler lbi)
572 (withPrograms lbi)
573 (flagToMaybe $ buildWorkingDir flags)
574 (withPackageDB lbi)
575 installedPkgInfo
576 HcPkg.defaultRegisterOptions
577 { HcPkg.registerMultiInstance = True
579 return (Just installedPkgInfo)
580 else return Nothing
581 CFLib flib -> do
582 buildFLib verbosity numJobs pkg_descr lbi flib clbi
583 return Nothing
584 CExe exe -> do
585 let ebi = buildInfo exe
586 exe' = exe{buildInfo = addExtraCSources ebi extras}
587 buildExe verbosity numJobs pkg_descr lbi exe' clbi
588 return Nothing
589 CTest test@TestSuite{testInterface = TestSuiteExeV10{}} -> do
590 let exe = testSuiteExeV10AsExe test
591 (genDir, generatedExtras) <- generateCode (testCodeGenerators test) (testName test) pkg_descr (testBuildInfo test) lbi clbi verbosity
592 let ebi = buildInfo exe
593 exe' = exe{buildInfo = addSrcDir (addExtraOtherModules (addExtraCSources ebi extras) generatedExtras) genDir} -- todo extend hssrcdirs
594 buildExe verbosity numJobs pkg_descr lbi exe' clbi
595 return Nothing
596 CBench bm@Benchmark{benchmarkInterface = BenchmarkExeV10{}} -> do
597 let exe = benchmarkExeV10asExe bm
598 let ebi = buildInfo exe
599 exe' = exe{buildInfo = addExtraCSources ebi extras}
600 buildExe verbosity numJobs pkg_descr lbi exe' clbi
601 return Nothing
602 #if __GLASGOW_HASKELL__ < 811
603 -- silence pattern-match warnings prior to GHC 9.0
604 _ -> error "impossible"
605 #endif
607 generateCode
608 :: [String]
609 -> UnqualComponentName
610 -> PackageDescription
611 -> BuildInfo
612 -> LocalBuildInfo
613 -> ComponentLocalBuildInfo
614 -> Verbosity
615 -> IO (SymbolicPath Pkg (Dir Source), [ModuleName.ModuleName])
616 generateCode codeGens nm pdesc bi lbi clbi verbosity = do
617 when (not . null $ codeGens) $ createDirectoryIfMissingVerbose verbosity True $ i tgtDir
618 (\x -> (tgtDir, x)) . concat <$> mapM go codeGens
619 where
620 allLibs = (maybe id (:) $ library pdesc) (subLibraries pdesc)
621 dependencyLibs = filter (const True) allLibs -- intersect with componentPackageDeps of clbi
622 srcDirs = concatMap (hsSourceDirs . libBuildInfo) dependencyLibs
623 nm' = unUnqualComponentName nm
624 mbWorkDir = mbWorkDirLBI lbi
625 i = interpretSymbolicPath mbWorkDir -- See Note [Symbolic paths] in Distribution.Utils.Path
626 tgtDir = buildDir lbi </> makeRelativePathEx (nm' </> nm' ++ "-gen")
627 go :: String -> IO [ModuleName.ModuleName]
628 go codeGenProg =
629 fmap fromString . lines
630 <$> getDbProgramOutputCwd
631 verbosity
632 mbWorkDir
633 (simpleProgram codeGenProg)
634 (withPrograms lbi)
635 ( map interpretSymbolicPathCWD (tgtDir : srcDirs)
636 ++ ( "--"
637 : GHC.renderGhcOptions (compiler lbi) (hostPlatform lbi) (GHC.componentGhcOptions verbosity lbi bi clbi tgtDir)
641 -- | Add extra C sources generated by preprocessing to build
642 -- information.
643 addExtraCSources :: BuildInfo -> [SymbolicPath Pkg File] -> BuildInfo
644 addExtraCSources bi extras = bi{cSources = new}
645 where
646 new = ordNub (extras ++ cSources bi)
648 -- | Add extra C++ sources generated by preprocessing to build
649 -- information.
650 addExtraCxxSources :: BuildInfo -> [SymbolicPath Pkg File] -> BuildInfo
651 addExtraCxxSources bi extras = bi{cxxSources = new}
652 where
653 new = ordNub (extras ++ cxxSources bi)
655 -- | Add extra C-- sources generated by preprocessing to build
656 -- information.
657 addExtraCmmSources :: BuildInfo -> [SymbolicPath Pkg File] -> BuildInfo
658 addExtraCmmSources bi extras = bi{cmmSources = new}
659 where
660 new = ordNub (extras ++ cmmSources bi)
662 -- | Add extra ASM sources generated by preprocessing to build
663 -- information.
664 addExtraAsmSources :: BuildInfo -> [SymbolicPath Pkg File] -> BuildInfo
665 addExtraAsmSources bi extras = bi{asmSources = new}
666 where
667 new = ordNub (extras ++ asmSources bi)
669 -- | Add extra JS sources generated by preprocessing to build
670 -- information.
671 addExtraJsSources :: BuildInfo -> [SymbolicPath Pkg File] -> BuildInfo
672 addExtraJsSources bi extras = bi{jsSources = new}
673 where
674 new = ordNub (extras ++ jsSources bi)
676 -- | Add extra HS modules generated by preprocessing to build
677 -- information.
678 addExtraOtherModules :: BuildInfo -> [ModuleName.ModuleName] -> BuildInfo
679 addExtraOtherModules bi extras = bi{otherModules = new}
680 where
681 new = ordNub (extras ++ otherModules bi)
683 -- | Add extra source dir for generated modules.
684 addSrcDir :: BuildInfo -> SymbolicPath Pkg (Dir Source) -> BuildInfo
685 addSrcDir bi extra = bi{hsSourceDirs = new}
686 where
687 new = ordNub (extra : hsSourceDirs bi)
689 replComponent
690 :: ReplFlags
691 -> Verbosity
692 -> PackageDescription
693 -> LocalBuildInfo
694 -> [PPSuffixHandler]
695 -> Component
696 -> ComponentLocalBuildInfo
697 -> SymbolicPath Pkg (Dir Dist)
698 -> IO ()
699 replComponent _ verbosity _ _ _ (CTest TestSuite{testInterface = TestSuiteUnsupported tt}) _ _ =
700 dieWithException verbosity $ NoSupportBuildingTestSuite tt
701 replComponent _ verbosity _ _ _ (CBench Benchmark{benchmarkInterface = BenchmarkUnsupported tt}) _ _ =
702 dieWithException verbosity $ NoSupportBuildingBenchMark tt
703 replComponent
704 replFlags
705 verbosity
706 pkg_descr
707 lbi0
708 suffixHandlers
709 comp@( CTest
710 test@TestSuite{testInterface = TestSuiteLibV09{}}
712 clbi
713 distPref = do
714 inplaceDir <- absoluteWorkingDirLBI lbi0
715 let (pkg, lib, libClbi, lbi, _, _, _) =
716 testSuiteLibV09AsLibAndExe pkg_descr test clbi lbi0 inplaceDir distPref
717 preprocessComponent pkg_descr comp lbi clbi False verbosity suffixHandlers
718 extras <- preprocessExtras verbosity comp lbi
719 let libbi = libBuildInfo lib
720 lib' = lib{libBuildInfo = libbi{cSources = cSources libbi ++ extras}}
721 replLib replFlags pkg lbi lib' libClbi
722 replComponent
723 replFlags
724 verbosity
725 pkg_descr
727 suffixHandlers
728 comp
729 clbi
732 preprocessComponent pkg_descr comp lbi clbi False verbosity suffixHandlers
733 extras <- preprocessExtras verbosity comp lbi
734 case comp of
735 CLib lib -> do
736 let libbi = libBuildInfo lib
737 lib' = lib{libBuildInfo = libbi{cSources = cSources libbi ++ extras}}
738 replLib replFlags pkg_descr lbi lib' clbi
739 CFLib flib ->
740 replFLib replFlags pkg_descr lbi flib clbi
741 CExe exe -> do
742 let ebi = buildInfo exe
743 exe' = exe{buildInfo = ebi{cSources = cSources ebi ++ extras}}
744 replExe replFlags pkg_descr lbi exe' clbi
745 CTest test@TestSuite{testInterface = TestSuiteExeV10{}} -> do
746 let exe = testSuiteExeV10AsExe test
747 let ebi = buildInfo exe
748 exe' = exe{buildInfo = ebi{cSources = cSources ebi ++ extras}}
749 replExe replFlags pkg_descr lbi exe' clbi
750 CBench bm@Benchmark{benchmarkInterface = BenchmarkExeV10{}} -> do
751 let exe = benchmarkExeV10asExe bm
752 let ebi = buildInfo exe
753 exe' = exe{buildInfo = ebi{cSources = cSources ebi ++ extras}}
754 replExe replFlags pkg_descr lbi exe' clbi
755 #if __GLASGOW_HASKELL__ < 811
756 -- silence pattern-match warnings prior to GHC 9.0
757 _ -> error "impossible"
758 #endif
760 ----------------------------------------------------
761 -- Shared code for buildComponent and replComponent
764 -- | Translate a exe-style 'TestSuite' component into an exe for building
765 testSuiteExeV10AsExe :: TestSuite -> Executable
766 testSuiteExeV10AsExe test@TestSuite{testInterface = TestSuiteExeV10 _ mainFile} =
767 Executable
768 { exeName = testName test
769 , modulePath = mainFile
770 , exeScope = ExecutablePublic
771 , buildInfo = testBuildInfo test
773 testSuiteExeV10AsExe TestSuite{} = error "testSuiteExeV10AsExe: wrong kind"
775 -- | Translate a exe-style 'Benchmark' component into an exe for building
776 benchmarkExeV10asExe :: Benchmark -> Executable
777 benchmarkExeV10asExe bm@Benchmark{benchmarkInterface = BenchmarkExeV10 _ mainFile} =
778 Executable
779 { exeName = benchmarkName bm
780 , modulePath = mainFile
781 , exeScope = ExecutablePublic
782 , buildInfo = benchmarkBuildInfo bm
784 benchmarkExeV10asExe Benchmark{} = error "benchmarkExeV10asExe: wrong kind"
786 -- | Translate a lib-style 'TestSuite' component into a lib + exe for building
787 testSuiteLibV09AsLibAndExe
788 :: PackageDescription
789 -> TestSuite
790 -> ComponentLocalBuildInfo
791 -> LocalBuildInfo
792 -> AbsolutePath (Dir Pkg)
793 -- ^ absolute inplace dir
794 -> SymbolicPath Pkg (Dir Dist)
795 -> ( PackageDescription
796 , Library
797 , ComponentLocalBuildInfo
798 , LocalBuildInfo
799 , IPI.InstalledPackageInfo
800 , Executable
801 , ComponentLocalBuildInfo
803 testSuiteLibV09AsLibAndExe
804 pkg_descr
805 test@TestSuite{testInterface = TestSuiteLibV09 _ m}
806 clbi
808 inplaceDir
809 distPref =
810 (pkg, lib, libClbi, lbi, ipi, exe, exeClbi)
811 where
812 bi = testBuildInfo test
813 lib =
814 Library
815 { libName = LMainLibName
816 , exposedModules = [m]
817 , reexportedModules = []
818 , signatures = []
819 , libExposed = True
820 , libVisibility = LibraryVisibilityPrivate
821 , libBuildInfo = bi
823 -- This is, like, the one place where we use a CTestName for a library.
824 -- Should NOT use library name, since that could conflict!
825 PackageIdentifier pkg_name pkg_ver = package pkg_descr
826 -- Note: we do make internal library from the test!
827 compat_name = MungedPackageName pkg_name (LSubLibName (testName test))
828 compat_key = computeCompatPackageKey (compiler lbi) compat_name pkg_ver (componentUnitId clbi)
829 libClbi =
830 LibComponentLocalBuildInfo
831 { componentPackageDeps = componentPackageDeps clbi
832 , componentInternalDeps = componentInternalDeps clbi
833 , componentIsIndefinite_ = False
834 , componentExeDeps = componentExeDeps clbi
835 , componentLocalName = CLibName $ LSubLibName $ testName test
836 , componentIsPublic = False
837 , componentIncludes = componentIncludes clbi
838 , componentUnitId = componentUnitId clbi
839 , componentComponentId = componentComponentId clbi
840 , componentInstantiatedWith = []
841 , componentCompatPackageName = compat_name
842 , componentCompatPackageKey = compat_key
843 , componentExposedModules = [IPI.ExposedModule m Nothing]
845 pkgName' = mkPackageName $ prettyShow compat_name
846 pkg =
847 pkg_descr
848 { package = (package pkg_descr){pkgName = pkgName'}
849 , executables = []
850 , testSuites = []
851 , subLibraries = [lib]
853 ipi = inplaceInstalledPackageInfo inplaceDir distPref pkg (mkAbiHash "") lib lbi libClbi
854 testLibDep =
855 Dependency
856 pkgName'
857 (thisVersion $ pkgVersion $ package pkg_descr)
858 mainLibSet
859 exe =
860 Executable
861 { exeName = mkUnqualComponentName $ stubName test
862 , modulePath = makeRelativePathEx $ stubFilePath test
863 , exeScope = ExecutablePublic
864 , buildInfo =
865 (testBuildInfo test)
866 { hsSourceDirs = [coerceSymbolicPath $ testBuildDir lbi test]
867 , targetBuildDepends =
868 testLibDep
869 : targetBuildDepends (testBuildInfo test)
872 -- \| The stub executable needs a new 'ComponentLocalBuildInfo'
873 -- that exposes the relevant test suite library.
874 deps =
875 (IPI.installedUnitId ipi, mungedId ipi)
876 : ( filter
877 ( \(_, x) ->
878 let name = prettyShow $ mungedName x
879 in name == "Cabal" || name == "base"
881 (componentPackageDeps clbi)
883 exeClbi =
884 ExeComponentLocalBuildInfo
885 { -- TODO: this is a hack, but as long as this is unique
886 -- (doesn't clobber something) we won't run into trouble
887 componentUnitId = mkUnitId (stubName test)
888 , componentComponentId = mkComponentId (stubName test)
889 , componentInternalDeps = [componentUnitId clbi]
890 , componentExeDeps = []
891 , componentLocalName = CExeName $ mkUnqualComponentName $ stubName test
892 , componentPackageDeps = deps
893 , -- Assert DefUnitId invariant!
894 -- Executable can't be indefinite, so dependencies must
895 -- be definite packages.
896 componentIncludes =
897 map ((,defaultRenaming) . DefiniteUnitId . unsafeMkDefUnitId . fst) deps
899 testSuiteLibV09AsLibAndExe _ TestSuite{} _ _ _ _ = error "testSuiteLibV09AsLibAndExe: wrong kind"
901 -- | Initialize a new package db file for libraries defined
902 -- internally to the package.
903 createInternalPackageDB
904 :: Verbosity
905 -> LocalBuildInfo
906 -> SymbolicPath Pkg (Dir Dist)
907 -> IO PackageDB
908 createInternalPackageDB verbosity lbi distPref = do
909 existsAlready <- doesPackageDBExist dbPath
910 when existsAlready $ deletePackageDB dbPath
911 createPackageDB verbosity (compiler lbi) (withPrograms lbi) False dbPath
912 return (SpecificPackageDB dbRelPath)
913 where
914 dbRelPath = internalPackageDBPath lbi distPref
915 dbPath = interpretSymbolicPathLBI lbi dbRelPath
917 -- | Update the program database to include any build-tool-depends specified
918 -- in the given 'BuildInfo' on build tools internal to the current package.
920 -- This function:
922 -- - adds these internal build tools to the 'ProgramDb', including
923 -- paths to their respective data directories,
924 -- - adds their paths to the current 'progSearchPath', and adds the data
925 -- directory environment variable for the current package to the current
926 -- 'progOverrideEnv', so that any programs configured from now on will be
927 -- able to invoke these build tools.
928 addInternalBuildTools
929 :: PackageDescription
930 -> LocalBuildInfo
931 -> BuildInfo
932 -> ProgramDb
933 -> ProgramDb
934 addInternalBuildTools pkg lbi bi progs =
935 prependProgramSearchPathNoLogging
936 internalToolPaths
937 [pkgDataDirVar]
938 $ foldr updateProgram progs internalBuildTools
939 where
940 internalToolPaths = map (takeDirectory . programPath) internalBuildTools
941 pkgDataDirVar = (pkgPathEnvVar pkg "datadir", Just dataDirPath)
942 internalBuildTools =
943 [ (simpleConfiguredProgram toolName' (FoundOnSystem toolLocation))
944 { programOverrideEnv = [pkgDataDirVar]
946 | toolName <- getAllInternalToolDependencies pkg bi
947 , let toolName' = unUnqualComponentName toolName
948 , let toolLocation =
949 interpretSymbolicPathLBI lbi $
950 buildDir lbi
951 </> makeRelativePathEx (toolName' </> toolName' <.> exeExtension (hostPlatform lbi))
953 mbWorkDir = mbWorkDirLBI lbi
954 rawDataDir = dataDir pkg
955 dataDirPath
956 | null $ getSymbolicPath rawDataDir =
957 interpretSymbolicPath mbWorkDir sameDirectory
958 | otherwise =
959 interpretSymbolicPath mbWorkDir rawDataDir
961 -- TODO: build separate libs in separate dirs so that we can build
962 -- multiple libs, e.g. for 'LibTest' library-style test suites
963 buildLib
964 :: BuildFlags
965 -> Flag ParStrat
966 -> PackageDescription
967 -> LocalBuildInfo
968 -> Library
969 -> ComponentLocalBuildInfo
970 -> IO ()
971 buildLib flags numJobs pkg_descr lbi lib clbi =
972 let verbosity = fromFlag $ buildVerbosity flags
973 in case compilerFlavor (compiler lbi) of
974 GHC -> GHC.buildLib flags numJobs pkg_descr lbi lib clbi
975 GHCJS -> GHCJS.buildLib verbosity numJobs pkg_descr lbi lib clbi
976 UHC -> UHC.buildLib verbosity pkg_descr lbi lib clbi
977 HaskellSuite{} -> HaskellSuite.buildLib verbosity pkg_descr lbi lib clbi
978 _ -> dieWithException verbosity BuildingNotSupportedWithCompiler
980 -- | Build a foreign library
982 -- NOTE: We assume that we already checked that we can actually build the
983 -- foreign library in configure.
984 buildFLib
985 :: Verbosity
986 -> Flag ParStrat
987 -> PackageDescription
988 -> LocalBuildInfo
989 -> ForeignLib
990 -> ComponentLocalBuildInfo
991 -> IO ()
992 buildFLib verbosity numJobs pkg_descr lbi flib clbi =
993 case compilerFlavor (compiler lbi) of
994 GHC -> GHC.buildFLib verbosity numJobs pkg_descr lbi flib clbi
995 _ -> dieWithException verbosity BuildingNotSupportedWithCompiler
997 buildExe
998 :: Verbosity
999 -> Flag ParStrat
1000 -> PackageDescription
1001 -> LocalBuildInfo
1002 -> Executable
1003 -> ComponentLocalBuildInfo
1004 -> IO ()
1005 buildExe verbosity numJobs pkg_descr lbi exe clbi =
1006 case compilerFlavor (compiler lbi) of
1007 GHC -> GHC.buildExe verbosity numJobs pkg_descr lbi exe clbi
1008 GHCJS -> GHCJS.buildExe verbosity numJobs pkg_descr lbi exe clbi
1009 UHC -> UHC.buildExe verbosity pkg_descr lbi exe clbi
1010 _ -> dieWithException verbosity BuildingNotSupportedWithCompiler
1012 replLib
1013 :: ReplFlags
1014 -> PackageDescription
1015 -> LocalBuildInfo
1016 -> Library
1017 -> ComponentLocalBuildInfo
1018 -> IO ()
1019 replLib replFlags pkg_descr lbi lib clbi =
1020 let verbosity = fromFlag $ replVerbosity replFlags
1021 opts = replReplOptions replFlags
1022 in case compilerFlavor (compiler lbi) of
1023 -- 'cabal repl' doesn't need to support 'ghc --make -j', so we just pass
1024 -- NoFlag as the numJobs parameter.
1025 GHC -> GHC.replLib replFlags NoFlag pkg_descr lbi lib clbi
1026 GHCJS -> GHCJS.replLib (replOptionsFlags opts) verbosity NoFlag pkg_descr lbi lib clbi
1027 _ -> dieWithException verbosity REPLNotSupported
1029 replExe
1030 :: ReplFlags
1031 -> PackageDescription
1032 -> LocalBuildInfo
1033 -> Executable
1034 -> ComponentLocalBuildInfo
1035 -> IO ()
1036 replExe flags pkg_descr lbi exe clbi =
1037 let verbosity = fromFlag $ replVerbosity flags
1038 in case compilerFlavor (compiler lbi) of
1039 GHC -> GHC.replExe flags NoFlag pkg_descr lbi exe clbi
1040 GHCJS ->
1041 GHCJS.replExe
1042 (replOptionsFlags $ replReplOptions flags)
1043 verbosity
1044 NoFlag
1045 pkg_descr
1048 clbi
1049 _ -> dieWithException verbosity REPLNotSupported
1051 replFLib
1052 :: ReplFlags
1053 -> PackageDescription
1054 -> LocalBuildInfo
1055 -> ForeignLib
1056 -> ComponentLocalBuildInfo
1057 -> IO ()
1058 replFLib flags pkg_descr lbi exe clbi =
1059 let verbosity = fromFlag $ replVerbosity flags
1060 in case compilerFlavor (compiler lbi) of
1061 GHC -> GHC.replFLib flags NoFlag pkg_descr lbi exe clbi
1062 _ -> dieWithException verbosity REPLNotSupported
1064 -- | Runs 'componentInitialBuildSteps' on every configured component.
1066 -- Legacy function: does not run pre-build hooks or pre-processors. This function
1067 -- is insufficient on its own to prepare the build for a package.
1069 -- Consumers wanting to prepare the sources of a package, e.g. in order to
1070 -- launch a REPL session, are advised to run @Setup repl --repl-multi-file=<fn>@
1071 -- instead.
1072 initialBuildSteps
1073 :: FilePath
1074 -- ^ "dist" prefix
1075 -> PackageDescription
1076 -- ^ mostly information from the .cabal file
1077 -> LocalBuildInfo
1078 -- ^ Configuration information
1079 -> Verbosity
1080 -- ^ The verbosity to use
1081 -> IO ()
1082 initialBuildSteps distPref pkg_descr lbi verbosity =
1083 withAllComponentsInBuildOrder pkg_descr lbi $ \_comp clbi ->
1084 componentInitialBuildSteps distPref pkg_descr lbi clbi verbosity
1085 {-# DEPRECATED
1086 initialBuildSteps
1087 "This function does not prepare all source files for a package. Suggestion: use 'Setup repl --repl-multi-file=<fn>'."
1090 -- | Creates the autogenerated files for a particular configured component.
1092 -- Legacy function: does not run pre-build hooks or pre-processors. This function
1093 -- is insufficient on its own to prepare the build for a component.
1095 -- Consumers wanting to prepare the sources of a component, e.g. in order to
1096 -- launch a REPL session, are advised to run
1097 -- @Setup repl <compName> --repl-multi-file=<fn>@ instead.
1098 componentInitialBuildSteps
1099 :: FilePath
1100 -- ^ "dist" prefix
1101 -> PackageDescription
1102 -- ^ mostly information from the .cabal file
1103 -> LocalBuildInfo
1104 -- ^ Configuration information
1105 -> ComponentLocalBuildInfo
1106 -- ^ Build info about the component
1107 -> Verbosity
1108 -- ^ The verbosity to use
1109 -> IO ()
1110 componentInitialBuildSteps _distPref pkg_descr lbi clbi verbosity = do
1111 let compBuildDir = interpretSymbolicPathLBI lbi $ componentBuildDir lbi clbi
1112 createDirectoryIfMissingVerbose verbosity True compBuildDir
1113 writeBuiltinAutogenFiles verbosity pkg_descr lbi clbi
1114 {-# DEPRECATED
1115 componentInitialBuildSteps
1116 "This function does not prepare all source files for a component. Suggestion: use 'Setup repl <compName> --repl-multi-file=<fn>'."
1119 -- | Creates the autogenerated files for a particular configured component,
1120 -- and runs the pre-build hook.
1121 preBuildComponent
1122 :: (LocalBuildInfo -> TargetInfo -> IO ())
1123 -- ^ pre-build hook
1124 -> Verbosity
1125 -> LocalBuildInfo
1126 -- ^ Configuration information
1127 -> TargetInfo
1128 -> IO ()
1129 preBuildComponent preBuildHook verbosity lbi tgt = do
1130 let pkg_descr = localPkgDescr lbi
1131 clbi = targetCLBI tgt
1132 compBuildDir = interpretSymbolicPathLBI lbi $ componentBuildDir lbi clbi
1133 createDirectoryIfMissingVerbose verbosity True compBuildDir
1134 writeBuiltinAutogenFiles verbosity pkg_descr lbi clbi
1135 preBuildHook lbi tgt
1137 -- | Generate and write to disk all built-in autogenerated files
1138 -- for the specified component. These files will be put in the
1139 -- autogenerated module directory for this component
1140 -- (see 'autogenComponentsModuleDir').
1142 -- This includes:
1144 -- - @Paths_<pkg>.hs@,
1145 -- - @PackageInfo_<pkg>.hs@,
1146 -- - Backpack signature files for components that are not fully instantiated,
1147 -- - @cabal_macros.h@.
1148 writeBuiltinAutogenFiles
1149 :: Verbosity
1150 -> PackageDescription
1151 -> LocalBuildInfo
1152 -> ComponentLocalBuildInfo
1153 -> IO ()
1154 writeBuiltinAutogenFiles verbosity pkg lbi clbi =
1155 writeAutogenFiles verbosity lbi clbi $ builtinAutogenFiles pkg lbi clbi
1157 -- | Built-in autogenerated files and their contents. This includes:
1159 -- - @Paths_<pkg>.hs@,
1160 -- - @PackageInfo_<pkg>.hs@,
1161 -- - Backpack signature files for components that are not fully instantiated,
1162 -- - @cabal_macros.h@.
1163 builtinAutogenFiles
1164 :: PackageDescription
1165 -> LocalBuildInfo
1166 -> ComponentLocalBuildInfo
1167 -> Map AutogenFile AutogenFileContents
1168 builtinAutogenFiles pkg lbi clbi =
1169 Map.insert pathsFile pathsContents $
1170 Map.insert packageInfoFile packageInfoContents $
1171 Map.insert cppHeaderFile cppHeaderContents $
1172 emptySignatureModules clbi
1173 where
1174 pathsFile = AutogenModule (autogenPathsModuleName pkg) (Suffix "hs")
1175 pathsContents = toUTF8LBS $ generatePathsModule pkg lbi clbi
1176 packageInfoFile = AutogenModule (autogenPackageInfoModuleName pkg) (Suffix "hs")
1177 packageInfoContents = toUTF8LBS $ generatePackageInfoModule pkg lbi
1178 cppHeaderFile = AutogenFile $ toShortText cppHeaderName
1179 cppHeaderContents = toUTF8LBS $ generateCabalMacrosHeader pkg lbi clbi
1181 -- | An empty @".hsig"@ Backpack signature module for each requirement, so that
1182 -- GHC has a source file to look at it when it needs to typecheck
1183 -- a signature. It's harmless to generate these modules, even when
1184 -- there is a real @hsig@ file written by the user, since
1185 -- include path ordering ensures that the real @hsig@ file
1186 -- will always be picked up before the autogenerated one.
1187 emptySignatureModules
1188 :: ComponentLocalBuildInfo
1189 -> Map AutogenFile AutogenFileContents
1190 emptySignatureModules clbi =
1191 case clbi of
1192 LibComponentLocalBuildInfo{componentInstantiatedWith = insts} ->
1193 Map.fromList
1194 [ ( AutogenModule modName (Suffix "hsig")
1195 , emptyHsigFile modName
1197 | (modName, _) <- insts
1199 _ -> Map.empty
1200 where
1201 emptyHsigFile :: ModuleName -> AutogenFileContents
1202 emptyHsigFile modName =
1203 toUTF8LBS $
1204 "{-# OPTIONS_GHC -w #-}\n"
1205 ++ "{-# LANGUAGE NoImplicitPrelude #-}\n"
1206 ++ "signature "
1207 ++ prettyShow modName
1208 ++ " where"
1210 data AutogenFile
1211 = AutogenModule !ModuleName !Suffix
1212 | AutogenFile !ShortText
1213 deriving (Show, Eq, Ord)
1215 -- | A representation of the contents of an autogenerated file.
1216 type AutogenFileContents = LBS.ByteString
1218 -- | Write the given autogenerated files in the autogenerated modules
1219 -- directory for the component.
1220 writeAutogenFiles
1221 :: Verbosity
1222 -> LocalBuildInfo
1223 -> ComponentLocalBuildInfo
1224 -> Map AutogenFile AutogenFileContents
1225 -> IO ()
1226 writeAutogenFiles verbosity lbi clbi autogenFiles = do
1227 -- Ensure that the overall autogenerated files directory exists.
1228 createDirectoryIfMissingVerbose verbosity True autogenDir
1229 for_ (Map.assocs autogenFiles) $ \(file, contents) -> do
1230 let path = case file of
1231 AutogenModule modName (Suffix ext) ->
1232 autogenDir </> ModuleName.toFilePath modName <.> ext
1233 AutogenFile fileName ->
1234 autogenDir </> fromShortText fileName
1235 dir = takeDirectory path
1236 -- Ensure that the directory subtree for this autogenerated file exists.
1237 createDirectoryIfMissingVerbose verbosity True dir
1238 -- Write the contents of the file.
1239 rewriteFileLBS verbosity path contents
1240 where
1241 autogenDir = interpretSymbolicPathLBI lbi $ autogenComponentModulesDir lbi clbi