Skip to content

Commit 35d43dd

Browse files
committed
wip
1 parent 445ecd3 commit 35d43dd

File tree

5 files changed

+151
-93
lines changed

5 files changed

+151
-93
lines changed

cabal-install-solver/cabal-install-solver.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,8 @@ library
9595
Distribution.Solver.Types.SolverId
9696
Distribution.Solver.Types.SolverPackage
9797
Distribution.Solver.Types.SourcePackage
98-
Distribution.Solver.Types.System
98+
Distribution.Solver.Types.Stage
99+
Distribution.Solver.Types.Toolchain
99100
Distribution.Solver.Types.Variable
100101

101102
build-depends:
Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
{-# LANGUAGE DeriveGeneric #-}
2+
3+
module Distribution.Solver.Types.Stage
4+
( Stage (..)
5+
) where
6+
7+
import Distribution.Compat.Prelude
8+
import Prelude ()
9+
10+
data Stage
11+
= -- | -- The system where the build is running
12+
Build
13+
| -- | -- The system where the built artifacts will run
14+
Host
15+
deriving (Eq, Read, Show, Generic, Typeable)
16+
17+
instance Binary Stage
18+
instance Structured Stage
Lines changed: 49 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,49 @@
1+
{-# LANGUAGE DeriveGeneric #-}
2+
3+
module Distribution.Solver.Types.Toolchain
4+
( Toolchain (..)
5+
, Toolchains (..)
6+
, toolchainFor
7+
) where
8+
9+
import Distribution.Compat.Prelude
10+
import Prelude ()
11+
12+
import Distribution.Simple.Compiler
13+
import Distribution.Simple.Program.Db
14+
import Distribution.Solver.Types.Stage (Stage (..))
15+
import Distribution.System
16+
17+
---------------------------
18+
-- Toolchain
19+
--
20+
21+
data Toolchain = Toolchain
22+
{ toolchainPlatform :: Platform
23+
, toolchainCompiler :: Compiler
24+
, toolchainProgramDb :: ProgramDb
25+
}
26+
deriving (Show, Generic, Typeable)
27+
28+
-- TODO: review this
29+
instance Eq Toolchain where
30+
lhs == rhs =
31+
(((==) `on` toolchainPlatform) lhs rhs)
32+
&& (((==) `on` toolchainCompiler) lhs rhs)
33+
&& ((((==)) `on` (configuredPrograms . toolchainProgramDb)) lhs rhs)
34+
35+
instance Binary Toolchain
36+
instance Structured Toolchain
37+
38+
data Toolchains = Toolchains
39+
{ buildToolchain :: Toolchain
40+
, hostToolchain :: Toolchain
41+
}
42+
deriving (Eq, Show, Generic, Typeable)
43+
44+
toolchainFor :: Stage -> Toolchains -> Toolchain
45+
toolchainFor Build = buildToolchain
46+
toolchainFor Host = hostToolchain
47+
48+
instance Binary Toolchains
49+
instance Structured Toolchains

cabal-install/src/Distribution/Client/ProjectPlanning.hs

Lines changed: 77 additions & 77 deletions
Original file line numberDiff line numberDiff line change
@@ -221,6 +221,8 @@ import qualified Distribution.Simple.InstallDirs as InstallDirs
221221
import qualified Distribution.Simple.LocalBuildInfo as Cabal
222222
import qualified Distribution.Simple.Setup as Cabal
223223
import qualified Distribution.Solver.Types.ComponentDeps as CD
224+
import Distribution.Solver.Types.Stage
225+
import Distribution.Solver.Types.Toolchain
224226

225227
import qualified Distribution.Compat.Graph as Graph
226228

@@ -1611,18 +1613,7 @@ elaborateInstallPlan
16111613
elaborateInstallPlan
16121614
verbosity
16131615
hookHashes
1614-
toolchains@Toolchains
1615-
{ buildToolchain =
1616-
Toolchain
1617-
{ toolchainCompiler = compiler
1618-
, toolchainProgramDb = compilerprogdb
1619-
}
1620-
, hostToolchain =
1621-
Toolchain
1622-
{ toolchainCompiler = hostCompiler
1623-
, toolchainPlatform = hostPlatform
1624-
}
1625-
}
1616+
toolchains
16261617
pkgConfigDB
16271618
distDirLayout@DistDirLayout{..}
16281619
storeDirLayout@StoreDirLayout{storePackageDBStack}
@@ -2201,12 +2192,19 @@ elaborateInstallPlan
22012192

22022193
elabIsCanonical = True
22032194
elabPkgSourceId = pkgid
2195+
2196+
-- TODO: temporarily set everything to build on build
2197+
elabStage = Build
2198+
elabCompiler = toolchainCompiler (toolchainFor elabStage toolchains)
2199+
elabPlatform = toolchainPlatform (toolchainFor elabStage toolchains)
2200+
elabProgramDb = toolchainProgramDb (toolchainFor elabStage toolchains)
2201+
22042202
elabPkgDescription = case PD.finalizePD
22052203
flags
22062204
elabEnabledSpec
22072205
(const Satisfied)
2208-
hostPlatform
2209-
(compilerInfo hostCompiler)
2206+
elabPlatform
2207+
(compilerInfo elabCompiler)
22102208
[]
22112209
gdesc of
22122210
Right (desc, _) -> desc
@@ -2281,6 +2279,10 @@ elaborateInstallPlan
22812279
deps0
22822280
elabSetupPackageDBStack = buildAndRegisterDbs
22832281

2282+
inplacePackageDbs = corePackageDbs ++ [distPackageDB (compilerId elabCompiler)]
2283+
2284+
corePackageDbs = storePackageDBStack elabCompiler (projectConfigPackageDBs sharedPackageConfig)
2285+
22842286
elabInplaceBuildPackageDBStack = inplacePackageDbs
22852287
elabInplaceRegisterPackageDBStack = inplacePackageDbs
22862288
elabInplaceSetupPackageDBStack = inplacePackageDbs
@@ -2291,17 +2293,21 @@ elaborateInstallPlan
22912293

22922294
elabPkgDescriptionOverride = descOverride
22932295

2296+
pkgsUseSharedLibrary :: Set PackageId
2297+
pkgsUseSharedLibrary =
2298+
packagesWithLibDepsDownwardClosedProperty (needsSharedLib elabCompiler)
2299+
22942300
elabBuildOptions =
22952301
LBC.BuildOptions
22962302
{ withVanillaLib = perPkgOptionFlag pkgid True packageConfigVanillaLib -- TODO: [required feature]: also needs to be handled recursively
2297-
, withSharedLib = canBuildSharedLibs && pkgid `Set.member` pkgsUseSharedLibrary
2303+
, withSharedLib = canBuildSharedLibs elabCompiler && pkgid `Set.member` pkgsUseSharedLibrary
22982304
, withStaticLib = perPkgOptionFlag pkgid False packageConfigStaticLib
22992305
, withDynExe = perPkgOptionFlag pkgid False packageConfigDynExe
23002306
, withFullyStaticExe = perPkgOptionFlag pkgid False packageConfigFullyStaticExe
23012307
, withGHCiLib = perPkgOptionFlag pkgid False packageConfigGHCiLib -- TODO: [required feature] needs to default to enabled on windows still
23022308
, withProfExe = perPkgOptionFlag pkgid False packageConfigProf
2303-
, withProfLib = canBuildProfilingLibs && pkgid `Set.member` pkgsUseProfilingLibrary
2304-
, withProfLibShared = canBuildProfilingSharedLibs && pkgid `Set.member` pkgsUseProfilingLibraryShared
2309+
, withProfLib = canBuildProfilingLibs elabCompiler && pkgid `Set.member` pkgsUseProfilingLibrary
2310+
, withProfLibShared = canBuildProfilingSharedLibs elabCompiler && pkgid `Set.member` pkgsUseProfilingLibraryShared
23052311
, exeCoverage = perPkgOptionFlag pkgid False packageConfigCoverage
23062312
, libCoverage = perPkgOptionFlag pkgid False packageConfigCoverage
23072313
, withOptimization = perPkgOptionFlag pkgid NormalOptimisation packageConfigOptimization
@@ -2334,13 +2340,13 @@ elaborateInstallPlan
23342340
elabProgramPaths =
23352341
Map.fromList
23362342
[ (programId prog, programPath prog)
2337-
| prog <- configuredPrograms compilerprogdb
2343+
| prog <- configuredPrograms elabProgramDb
23382344
]
23392345
<> perPkgOptionMapLast pkgid packageConfigProgramPaths
23402346
elabProgramArgs =
23412347
Map.fromList
23422348
[ (programId prog, args)
2343-
| prog <- configuredPrograms compilerprogdb
2349+
| prog <- configuredPrograms elabProgramDb
23442350
, let args = programOverrideArgs $ addHaddockIfDocumentationEnabled prog
23452351
, not (null args)
23462352
]
@@ -2422,12 +2428,6 @@ elaborateInstallPlan
24222428
mempty
24232429
perpkg = maybe mempty f (Map.lookup (packageName pkg) perPackageConfig)
24242430

2425-
inplacePackageDbs =
2426-
corePackageDbs
2427-
++ [distPackageDB (compilerId compiler)]
2428-
2429-
corePackageDbs = storePackageDBStack compiler (projectConfigPackageDBs sharedPackageConfig)
2430-
24312431
-- For this local build policy, every package that lives in a local source
24322432
-- dir (as opposed to a tarball), or depends on such a package, will be
24332433
-- built inplace into a shared dist dir. Tarball packages that depend on
@@ -2458,13 +2458,13 @@ elaborateInstallPlan
24582458
-- TODO: localPackages is a misnomer, it's all project packages
24592459
-- here is where we decide which ones will be local!
24602460

2461-
pkgsUseSharedLibrary :: Set PackageId
2462-
pkgsUseSharedLibrary =
2463-
packagesWithLibDepsDownwardClosedProperty needsSharedLib
2461+
pkgsUseProfilingLibrary :: Set PackageId
2462+
pkgsUseProfilingLibrary =
2463+
packagesWithLibDepsDownwardClosedProperty needsProfilingLib
24642464

2465-
needsSharedLib pkgid =
2465+
needsSharedLib compiler pkgid =
24662466
fromMaybe
2467-
compilerShouldUseSharedLibByDefault
2467+
(compilerShouldUseSharedLibByDefault compiler)
24682468
-- Case 1: --enable-shared or --disable-shared is passed explicitly, honour that.
24692469
( case pkgSharedLib of
24702470
Just v -> Just v
@@ -2475,7 +2475,7 @@ elaborateInstallPlan
24752475
-- Case 3: If --enable-profiling is passed, then we are going to
24762476
-- build profiled dynamic, so no need for shared libraries.
24772477
case pkgProf of
2478-
Just True -> if canBuildProfilingSharedLibs then Nothing else Just True
2478+
Just True -> if canBuildProfilingSharedLibs compiler then Nothing else Just True
24792479
_ -> Just True
24802480
-- But don't necessarily turn off shared library generation if
24812481
-- --disable-executable-dynamic is passed. The shared objects might
@@ -2487,52 +2487,7 @@ elaborateInstallPlan
24872487
pkgDynExe = perPkgOptionMaybe pkgid packageConfigDynExe
24882488
pkgProf = perPkgOptionMaybe pkgid packageConfigProf
24892489

2490-
-- TODO: [code cleanup] move this into the Cabal lib. It's currently open
2491-
-- coded in Distribution.Simple.Configure, but should be made a proper
2492-
-- function of the Compiler or CompilerInfo.
2493-
compilerShouldUseSharedLibByDefault =
2494-
case compilerFlavor compiler of
2495-
GHC -> GHC.compilerBuildWay compiler == DynWay && canBuildSharedLibs
2496-
GHCJS -> GHCJS.isDynamic compiler
2497-
_ -> False
2498-
2499-
compilerShouldUseProfilingLibByDefault =
2500-
case compilerFlavor compiler of
2501-
GHC -> GHC.compilerBuildWay compiler == ProfWay && canBuildProfilingLibs
2502-
_ -> False
2503-
2504-
compilerShouldUseProfilingSharedLibByDefault =
2505-
case compilerFlavor compiler of
2506-
GHC -> GHC.compilerBuildWay compiler == ProfDynWay && canBuildProfilingSharedLibs
2507-
_ -> False
2508-
2509-
-- Returns False if we definitely can't build shared libs
2510-
canBuildWayLibs predicate = case predicate compiler of
2511-
Just can_build -> can_build
2512-
-- If we don't know for certain, just assume we can
2513-
-- which matches behaviour in previous cabal releases
2514-
Nothing -> True
2515-
2516-
canBuildSharedLibs = canBuildWayLibs dynamicSupported
2517-
canBuildProfilingLibs = canBuildWayLibs profilingVanillaSupported
2518-
canBuildProfilingSharedLibs = canBuildWayLibs profilingDynamicSupported
2519-
2520-
wayWarnings pkg = do
2521-
when
2522-
(needsProfilingLib pkg && not canBuildProfilingLibs)
2523-
(warnProgress (text "Compiler does not support building p libraries, profiling is disabled"))
2524-
when
2525-
(needsSharedLib pkg && not canBuildSharedLibs)
2526-
(warnProgress (text "Compiler does not support building dyn libraries, dynamic libraries are disabled"))
2527-
when
2528-
(needsProfilingLibShared pkg && not canBuildProfilingSharedLibs)
2529-
(warnProgress (text "Compiler does not support building p_dyn libraries, profiling dynamic libraries are disabled."))
2530-
2531-
pkgsUseProfilingLibrary :: Set PackageId
2532-
pkgsUseProfilingLibrary =
2533-
packagesWithLibDepsDownwardClosedProperty needsProfilingLib
2534-
2535-
needsProfilingLib pkg =
2490+
needsProfilingLib compiler pkg =
25362491
fromFlagOrDefault compilerShouldUseProfilingLibByDefault (profBothFlag <> profLibFlag)
25372492
where
25382493
pkgid = packageId pkg
@@ -2590,6 +2545,51 @@ elaborateInstallPlan
25902545
-- package config validation/resolution pass.
25912546
]
25922547

2548+
-- TODO: [code cleanup] move this into the Cabal lib. It's currently open
2549+
-- coded in Distribution.Simple.Configure, but should be made a proper
2550+
-- function of the Compiler or CompilerInfo.
2551+
compilerShouldUseSharedLibByDefault :: Compiler -> Bool
2552+
compilerShouldUseSharedLibByDefault compiler =
2553+
case compilerFlavor compiler of
2554+
GHC -> GHC.compilerBuildWay compiler == DynWay && canBuildSharedLibs compiler
2555+
GHCJS -> GHCJS.isDynamic compiler
2556+
_ -> False
2557+
2558+
-- TODO: [code cleanup] move this into the Cabal lib.
2559+
compilerShouldUseProfilingLibByDefault :: Compiler -> Bool
2560+
compilerShouldUseProfilingLibByDefault compiler =
2561+
case compilerFlavor compiler of
2562+
GHC -> GHC.compilerBuildWay compiler == ProfWay && canBuildProfilingLibs compiler
2563+
_ -> False
2564+
2565+
-- TODO: [code cleanup] move this into the Cabal lib.
2566+
compilerShouldUseProfilingSharedLibByDefault :: Compiler -> Bool
2567+
compilerShouldUseProfilingSharedLibByDefault compiler =
2568+
case compilerFlavor compiler of
2569+
GHC -> GHC.compilerBuildWay compiler == ProfDynWay && canBuildProfilingSharedLibs compiler
2570+
_ -> False
2571+
2572+
-- Returns False if we definitely can't build shared libs
2573+
-- TODO: [code cleanup] move this into the Cabal lib.
2574+
canBuildWayLibs :: (t -> Maybe Bool) -> t -> Bool
2575+
canBuildWayLibs predicate compiler = case predicate compiler of
2576+
Just can_build -> can_build
2577+
-- If we don't know for certain, just assume we can
2578+
-- which matches behaviour in previous cabal releases
2579+
Nothing -> True
2580+
2581+
-- TODO: [code cleanup] move this into the Cabal lib.
2582+
canBuildSharedLibs :: Compiler -> Bool
2583+
canBuildSharedLibs = canBuildWayLibs dynamicSupported
2584+
2585+
-- TODO: [code cleanup] move this into the Cabal lib.
2586+
canBuildProfilingLibs :: Compiler -> Bool
2587+
canBuildProfilingLibs = canBuildWayLibs profilingVanillaSupported
2588+
2589+
-- TODO: [code cleanup] move this into the Cabal lib.
2590+
canBuildProfilingSharedLibs :: Compiler -> Bool
2591+
canBuildProfilingSharedLibs = canBuildWayLibs profilingDynamicSupported
2592+
25932593
-- TODO: [nice to have] config consistency checking:
25942594
-- + profiling libs & exes, exe needs lib, recursive
25952595
-- + shared libs & exes, exe needs lib, recursive

cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs

Lines changed: 5 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -112,7 +112,8 @@ import Distribution.Simple.Setup
112112
)
113113
import Distribution.Simple.Utils (ordNub)
114114
import Distribution.Solver.Types.ComponentDeps (ComponentDeps)
115-
import Distribution.Solver.Types.System
115+
import Distribution.Solver.Types.Stage
116+
import Distribution.Solver.Types.Toolchain
116117
import qualified Distribution.Solver.Types.ComponentDeps as CD
117118
import Distribution.Solver.Types.OptionalStanza
118119
import Distribution.Types.ComponentRequestedSpec
@@ -250,7 +251,9 @@ data ElaboratedConfiguredPackage = ElaboratedConfiguredPackage
250251
-- to disable. This tells us which ones we build by default, and
251252
-- helps with error messages when the user asks to build something
252253
-- they explicitly disabled.
253-
--
254+
255+
, elabStage :: Stage
256+
254257
-- TODO: The 'Bool' here should be refined into an ADT with three
255258
-- cases: NotRequested, ExplicitlyRequested and
256259
-- ImplicitlyRequested. A stanza is explicitly requested if
@@ -911,19 +914,6 @@ componentOptionalStanza (CD.ComponentTest _) = Just TestStanzas
911914
componentOptionalStanza (CD.ComponentBench _) = Just BenchStanzas
912915
componentOptionalStanza _ = Nothing
913916

914-
---------------------------
915-
-- Toolchain
916-
--
917-
918-
data Toolchains = Toolchains
919-
{ buildToolchain :: Toolchain
920-
, hostToolchain :: Toolchain
921-
}
922-
deriving (Eq, Show, Generic, Typeable)
923-
924-
instance Binary Toolchains
925-
instance Structured Toolchains
926-
927917
---------------------------
928918
-- Setup.hs script policy
929919
--

0 commit comments

Comments
 (0)