1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE RankNTypes #-}
4 -----------------------------------------------------------------------------
7 -- Module : Distribution.Simple.Build
8 -- Copyright : Isaac Jones 2003-2005,
10 -- Duncan Coutts 2007-2008, 2012
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
25 , createInternalPackageDB
26 , componentInitialBuildSteps
30 import Distribution
.Compat
.Prelude
31 import Distribution
.Utils
.Generic
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
(..))
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.
105 :: PackageDescription
106 -- ^ Mostly information from the .cabal file
108 -- ^ Configuration information
110 -- ^ Flags that the user passed to build
112 -- ^ preprocessors to run before compiling
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
)
119 "Component build order: "
123 (showComponentName
. componentLocalName
. targetCLBI
)
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
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
)
147 { withPrograms
= progs
'
148 , withPackageDB
= withPackageDB lbi
++ [internalPackageDB
]
149 , installedPkgs
= index
152 toFlag
<$> case buildUseSemaphore flags
of
153 Flag sem_name
-> case buildNumJobs flags
of
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
172 return (maybe index (Index
.insert `
flip`
index) mb_ipi
)
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.
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
201 -- ^ Configuration information
203 -- ^ Flags that the user passed to build
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
211 "Dump build information for: "
215 (showComponentName
. componentLocalName
. targetCLBI
)
218 pwd
<- getCurrentDirectory
220 (compilerProg
, _
) <- case flavorToProgram
(compilerFlavor
(compiler lbi
)) of
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
) $
229 "Encountered warnings while dumping build-info:\n"
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
)
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
251 :: PackageDescription
252 -- ^ Mostly information from the .cabal file
254 -- ^ Configuration information
256 -- ^ Flags that the user passed to build
258 -- ^ preprocessors to run before compiling
261 repl pkg_descr lbi flags suffixes args
= do
262 let distPref
= fromFlag
(replDistPref flags
)
263 verbosity
= fromFlag
(replVerbosity flags
)
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
]
275 "Component build order: "
279 (showComponentName
. componentLocalName
. targetCLBI
)
283 internalPackageDB
<- createInternalPackageDB verbosity lbi distPref
285 let lbiForComponent comp lbi
' =
287 { withPackageDB
= withPackageDB lbi
++ [internalPackageDB
]
289 addInternalBuildTools
292 (componentBuildInfo comp
)
296 -- build any dependent components
299 let clbi
= targetCLBI subtarget
300 comp
= targetComponent subtarget
301 lbi
' = lbiForComponent comp lbi
302 componentInitialBuildSteps distPref pkg_descr lbi clbi verbosity
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.
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
340 -> PackageDescription
344 -> ComponentLocalBuildInfo
346 -> IO (Maybe InstalledPackageInfo
)
356 preprocessComponent pkg_descr comp lbi clbi
False verbosity suffixes
357 extras
<- preprocessExtras verbosity comp lbi
361 (packageId pkg_descr
)
362 (componentLocalName clbi
)
363 (maybeComponentInstantiatedWith clbi
)
364 let libbi
= libBuildInfo lib
368 flip addExtraAsmSources extras
$
369 flip addExtraCmmSources extras
$
370 flip addExtraCxxSources extras
$
371 flip addExtraCSources extras
$
372 flip addExtraJsSources extras
$
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
)))
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
391 inplaceInstalledPackageInfo
395 -- NB: Use a fake ABI hash to avoid
396 -- needing to recompute it every build.
397 (mkAbiHash
"inplace")
402 debug verbosity
$ "Registering inplace:\n" ++ (IPI
.showInstalledPackageInfo installedPkgInfo
)
409 HcPkg
.defaultRegisterOptions
410 { HcPkg
.registerMultiInstance
= True
412 return (Just installedPkgInfo
)
423 preprocessComponent pkg_descr comp lbi clbi
False verbosity suffixes
427 (packageId pkg_descr
)
428 (componentLocalName clbi
)
429 (maybeComponentInstantiatedWith clbi
)
430 buildFLib verbosity numJobs pkg_descr lbi flib clbi
441 preprocessComponent pkg_descr comp lbi clbi
False verbosity suffixes
442 extras
<- preprocessExtras verbosity comp lbi
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
459 comp
@(CTest test
@TestSuite
{testInterface
= TestSuiteExeV10
{}})
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
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
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
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
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.
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
531 (CTest TestSuite
{testInterface
= TestSuiteUnsupported tt
})
534 dieWithException verbosity
$ NoSupportBuildingTestSuite tt
541 comp
@(CBench bm
@Benchmark
{benchmarkInterface
= BenchmarkExeV10
{}})
544 let exe
= benchmarkExeV10asExe bm
545 preprocessComponent pkg_descr comp lbi clbi
False verbosity suffixes
546 extras
<- preprocessExtras verbosity comp lbi
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
563 (CBench Benchmark
{benchmarkInterface
= BenchmarkUnsupported tt
})
566 dieWithException verbosity
$ NoSupportBuildingBenchMark tt
570 -> UnqualComponentName
571 -> PackageDescription
574 -> ComponentLocalBuildInfo
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
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
]
588 fmap fromString
. lines
589 <$> getDbProgramOutput
591 (simpleProgram codeGenProg
)
593 ( (tgtDir
: map getSymbolicPath srcDirs
)
595 : GHC
.renderGhcOptions
(compiler lbi
) (hostPlatform lbi
) (GHC
.componentGhcOptions verbosity lbi bi clbi tgtDir
)
599 -- | Add extra C sources generated by preprocessing to build
601 addExtraCSources
:: BuildInfo
-> [FilePath] -> BuildInfo
602 addExtraCSources bi extras
= bi
{cSources
= new
}
604 new
= ordNub
(extras
++ cSources bi
)
606 -- | Add extra C++ sources generated by preprocessing to build
608 addExtraCxxSources
:: BuildInfo
-> [FilePath] -> BuildInfo
609 addExtraCxxSources bi extras
= bi
{cxxSources
= new
}
611 new
= ordNub
(extras
++ cxxSources bi
)
613 -- | Add extra C-- sources generated by preprocessing to build
615 addExtraCmmSources
:: BuildInfo
-> [FilePath] -> BuildInfo
616 addExtraCmmSources bi extras
= bi
{cmmSources
= new
}
618 new
= ordNub
(extras
++ cmmSources bi
)
620 -- | Add extra ASM sources generated by preprocessing to build
622 addExtraAsmSources
:: BuildInfo
-> [FilePath] -> BuildInfo
623 addExtraAsmSources bi extras
= bi
{asmSources
= new
}
625 new
= ordNub
(extras
++ asmSources bi
)
627 -- | Add extra JS sources generated by preprocessing to build
629 addExtraJsSources
:: BuildInfo
-> [FilePath] -> BuildInfo
630 addExtraJsSources bi extras
= bi
{jsSources
= new
}
632 new
= ordNub
(extras
++ jsSources bi
)
634 -- | Add extra HS modules generated by preprocessing to build
636 addExtraOtherModules
:: BuildInfo
-> [ModuleName
.ModuleName
] -> BuildInfo
637 addExtraOtherModules bi extras
= bi
{otherModules
= new
}
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
}
645 new
= ordNub
(unsafeMakeSymbolicPath extra
: hsSourceDirs bi
)
650 -> PackageDescription
654 -> ComponentLocalBuildInfo
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
680 preprocessComponent pkg_descr comp lbi clbi
False verbosity suffixes
681 replFLib replFlags verbosity pkg_descr lbi flib clbi
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
702 comp
@(CTest test
@TestSuite
{testInterface
= TestSuiteExeV10
{}})
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
718 test
@TestSuite
{testInterface
= TestSuiteLibV09
{}}
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
736 (CTest TestSuite
{testInterface
= TestSuiteUnsupported tt
})
739 dieWithException verbosity
$ NoSupportBuildingTestSuite tt
746 comp
@(CBench bm
@Benchmark
{benchmarkInterface
= BenchmarkExeV10
{}})
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
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
} =
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
} =
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
796 -> ComponentLocalBuildInfo
800 -> ( PackageDescription
802 , ComponentLocalBuildInfo
804 , IPI
.InstalledPackageInfo
806 , ComponentLocalBuildInfo
808 testSuiteLibV09AsLibAndExe
810 test
@TestSuite
{testInterface
= TestSuiteLibV09 _ m
}
815 (pkg
, lib
, libClbi
, lbi
, ipi
, exe
, exeClbi
)
817 bi
= testBuildInfo test
820 { libName
= LMainLibName
821 , exposedModules
= [m
]
822 , reexportedModules
= []
825 , libVisibility
= LibraryVisibilityPrivate
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
)
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
853 { package
= (package pkg_descr
){pkgName
= pkgName
'}
856 , subLibraries
= [lib
]
858 ipi
= inplaceInstalledPackageInfo pwd distPref pkg
(mkAbiHash
"") lib lbi libClbi
867 (thisVersion
$ pkgVersion
$ package pkg_descr
)
871 { exeName
= mkUnqualComponentName
$ stubName test
872 , modulePath
= stubFilePath test
873 , exeScope
= ExecutablePublic
876 { hsSourceDirs
= [unsafeMakeSymbolicPath testDir
]
877 , targetBuildDepends
=
879 : targetBuildDepends
(testBuildInfo test
)
882 -- \| The stub executable needs a new 'ComponentLocalBuildInfo'
883 -- that exposes the relevant test suite library.
885 (IPI
.installedUnitId ipi
, mungedId ipi
)
888 let name
= prettyShow
$ mungedName x
889 in name
== "Cabal" || name
== "base"
891 (componentPackageDeps clbi
)
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.
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
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
)
926 dbPath
= internalPackageDBPath lbi distPref
928 addInternalBuildTools
929 :: PackageDescription
934 addInternalBuildTools pkg lbi bi progs
=
935 foldr updateProgram progs 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
949 -> PackageDescription
952 -> ComponentLocalBuildInfo
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.
969 -> PackageDescription
972 -> ComponentLocalBuildInfo
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
982 -> PackageDescription
985 -> ComponentLocalBuildInfo
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
997 -> PackageDescription
1000 -> ComponentLocalBuildInfo
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
1013 -> PackageDescription
1016 -> ComponentLocalBuildInfo
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
1027 -> PackageDescription
1030 -> ComponentLocalBuildInfo
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.
1041 -> PackageDescription
1042 -- ^ mostly information from the .cabal file
1044 -- ^ Configuration information
1046 -- ^ The verbosity to use
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
1056 -> PackageDescription
1057 -- ^ mostly information from the .cabal file
1059 -- ^ Configuration information
1060 -> ComponentLocalBuildInfo
1062 -- ^ The verbosity to use
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
1072 -> PackageDescription
1074 -> ComponentLocalBuildInfo
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
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
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"
1113 ++ prettyShow mod_name
1117 let cppHeaderPath
= autogenComponentModulesDir lbi clbi
</> cppHeaderName
1118 rewriteFileEx verbosity cppHeaderPath
(generateCabalMacrosHeader pkg lbi clbi
)